1 -- SPDX-FileCopyrightText: 2022 Frank Doepper
3 -- SPDX-License-Identifier: GPL-3.0-only
5 {-# LANGUAGE OverloadedStrings #-}
7 -- generic AMQP rpc server
8 import Control.Concurrent
9 import qualified Control.Exception as X
11 import qualified Data.ByteString.Char8 as BS
12 import Data.Map (singleton)
14 import qualified Data.Text as T
16 import Data.Version (showVersion)
18 import Network.AMQP.Types
19 import Network.AMQP.Utils.Connection
20 import Network.AMQP.Utils.Helpers
21 import Network.AMQP.Utils.Options
22 import Paths_amqp_utils (version)
23 import System.Environment
29 args <- getArgs >>= parseargs 'r'
31 (printparam "worker" $ fromJust $ fileProcess args)
32 (error "-X option required")
33 printparam "cleanup temp file" $ cleanupTmpFile args
34 let addiArgs = reverse $ additionalArgs args
35 printparam "client version" ["amqp-utils", showVersion version]
36 (conn, chan) <- connect args
37 addChannelExceptionHandler chan (X.throwTo tid)
39 printparam "prefetch" $ preFetch args
40 qos chan 0 (preFetch args) False
45 newQueue {queueExclusive = True, queueName = (T.pack $ tmpQName args)} >>=
46 (\(x, _, _) -> return x))
48 (fmap T.pack (qName args))
49 printparam "queue name" queue
50 if (currentExchange args /= "")
52 printparam "exchange" $ currentExchange args
53 bindQueue chan queue (T.pack $ currentExchange args) queue
62 (rpcServerCallback tid args addiArgs chan)
63 printparam "consumer tag" ctag
64 printparam "send acks" $ ack args
65 printparam "requeue if rejected" $ (ack args) && (requeuenack args)
66 hr "entering main loop"
67 sleepingBeauty >>= printparam "exception"
69 hr "connection closed"
72 ThreadId -> Args -> [String] -> Channel -> (Message, Envelope) -> IO ()
73 rpcServerCallback tid a addi c m@(msg, env) = do
74 let numstring = show $ envDeliveryTag env
75 hr $ "BEGIN " ++ numstring
77 (callbackoptions, callbackenv) <-
79 (printmsg Nothing m (anRiss a) now)
80 (\x -> X.throwTo tid (x :: X.IOException) >> return ([], []))
81 either (\e -> printparam "ERROR" (e :: X.IOException)) return =<<
92 hr $ "END " ++ numstring
99 (fromJust $ msgReplyTo msg)
102 , msgCorrelationID = msgCorrelationID msg
103 , msgTimestamp = msgTimestamp msg
104 , msgExpiration = msgExpiration msg
107 FieldTable $ singleton "exitcode" $ FVString $ BS.pack $ show e