-- GENERATED by C->Haskell Compiler, version 0.16.3 Crystal Seed, 24 Jan 2009 (Haskell) -- Edit the ORIGNAL .chs file instead! {-# LINE 1 "./System/Nitro.chs" #-} -- | -- Module: System.Nitro -- License: BSD3 -- Maintainer: Erin Dahlgren -- Stability: experimental -- Portability: non-portable -- -- Nitro is a fast, secure transport layer for sending messages across TCP and Inproc sockets. It is ideal for building scalable network applications. -- Nitro depends on the c libraries nitro and nitronacl (). module System.Nitro ( -- * How to use Nitro sockets -- $use nitroRuntimeStart , NitroSocket , SocketOptions(..) , defaultOpts , bind , connect , withSocket , close -- * Distributing messages -- $distributed , NitroFrame , bstrToFrame , frameToBstr , recv , send -- * Routing messages -- $routing , reply -- * Proxying messages -- $proxying , relayFw , relayBk -- * Pub/Sub messages -- $pubsub , sub , unsub , pub -- * Advanced -- $advanced , fileno -- * Types , Flag(NoWait) , NitroError(..) ) where import Foreign.C.Types import Foreign.Ptr import Foreign.ForeignPtr import Foreign.Storable import Foreign.C.String import qualified Foreign.Concurrent as FC import Foreign.Marshal.Alloc import Data.IORef import Data.Bits import qualified Data.ByteString as BS import Data.ByteString.Internal import Control.Monad (when) import Control.Exception (bracket) -- $use -- -- > {-# LANGUAGE OverloadedStrings, ForeignFunctionInterface #-} -- > import System.Nitro -- > -- > main = do -- > nitroRuntimeStart -- > -- > server <- bind "tcp://127.0.0.1:7777" defaultOpts -- > client <- connect "tcp://127.0.0.1:7777" defaultOpts -- > -- > fr <- bstrToFrame "Hi I'm a client" -- > send client fr [] -- > recv server [] >>= frameToBstr >>= print -- $distributed -- -- > {-# LANGUAGE OverloadedStrings, ForeignFunctionInterface #-} -- > import System.Nitro -- > import Control.Concurrent (forkIO, threadDelay) -- > import Control.Monad (forever) -- > -- > main = do -- > nitroRuntimeStart -- > -- > server <- bind "tcp://*:7777" defaultOpts -- > -- > let serverWorker = (\i -> forkIO $ forever $ do -- > fr <- recv server [] -- > threadDelay 1000000 -- > print ("Thread #" ++ (show i)) -- > print . frameToBstr $ msg -- > ) -- > -- > mapM_ serverWorker [1..2] -- > -- > client <- connect "tcp://127.0.0.1:7777" client -- > fr1 <- bstrToFrame "Here's a request" -- > send client fr1 [] -- > fr2 <- bstrToFrame "Here's another request" -- > send client fr2 [] -- > -- > threadDelay 2000000 -- -- Nitro wraps messages in a transport layer called a NitroFrame. NitroFrames encode routing information about the sender of a message. When you receive a NitroFrame you can use it to reply to the original sender. -- Compile all multithreaded Nitro code with ghc-option: -threaded -- $routing -- -- > {-# LANGUAGE OverloadedStrings, ForeignFunctionInterface #-} -- > import System.Nitro -- > import Control.Concurrent (forkIO, threadDelay) -- > import Control.Monad (forever) -- > -- > main = do -- > nitroRuntimeStart -- > -- > client1 <- connect "tcp://127.0.0.1:7777" defaultOpts -- > client2 <- connect "tcp://127.0.0.1:7777" defaultOpts -- > -- > fr1 <- bstrToFrame "Hi I want a response" -- > send client1 fr1 [] -- > fr2 <- bstrToFrame "Hi I also want a response" -- > send client2 fr2 [] -- > -- > forkIO $ withSocket (bind "tcp://127.0.0.1:7777" defaultOpts) -- > (\echoServer -> forever $ do -- > frame <- recv echoServer [] -- > reply echoServer frame frame [] -- > ) -- > -- > recv client1 [] >>= frameToBstr >>= print -- > recv client2 [] >>= frameToBstr >>= print -- -- Nitro sockets are threadsafe. Many worker threads can receive messages on a shared socket without overlap. -- $proxying -- -- > {-# LANGUAGE OverloadedStrings, ForeignFunctionInterface #-} -- > import System.Nitro -- > import Data.ByteString as BS -- > import Control.Concurrent (threadDelay, forkIO) -- > import Control.Monad (forever, when) -- > -- > proxy = withSocket (bind "tcp://127.0.0.1:7777" defaultOpts) -- > (\proxyRecv -> do -- > withSocket (connect "tcp://127.0.0.1:7778" defaultOpts) -- > (\proxySend -> forever $ do -- > frame <- recv proxyRecv [] -- > msg <- frameToBstr -- > when (BS.length msg < 50) $ -- > relayFw proxySend frame frame [] -- > ) -- > ) -- > -- > server = withSocket (bind "tcp://127.0.0.1:7778" defaultOpts) -- > (\server -> forever $ do -- > fr <- recv server [] -- > print . frameToBstr $ fr -- > ) -- > -- > main = do -- > nitroRuntimeStart -- > -- > forkIO $ server -- > forkIO $ proxy -- > -- > client <- connect "tcp://127.0.0.1:7777" defaultOpts -- > fr1 <- bstrToFrame "Here's a short message" -- > send client fr1 [] -- > fr2 <- "This message is too long for our server, it will be blocked" -- > send client fr2 [] -- > threadDelay 1000000 -- $pubsub -- -- > {-# LANGUAGE OverloadedStrings, ForeignFunctionInterface #-} -- > import System.Nitro -- > import Control.Concurrent (threadDelay) -- > -- > main = do -- > nitroRuntimeStart -- > -- > server <- bind "tcp://127.0.0.1:7777" defaultOpts -- > client <- connect "tcp://127.0.0.1:7777" defaultOpts -- > -- > sub client "con" -- > threadDelay 1000000 -- > -- > fr <- bstrToFrame "You don't understand" -- > pub server fr "contender" [] -- > -- > recv client [] >>= frameToBstr >>= print -- $advanced -- -- Nitro sockets support a NoWait flag, which makes calls to recv nonblocking. To make this useful, Nitro exposes an Int that represents the file descriptor of a Nitro socket. Registering an intent to read from this file descriptor using the GHC event manager is one way to know when it is safe to do a nonblocking recv. -- | A Nitro frame, which contains a message and routing information about the message's sender. type NitroFrame = ForeignPtr () type NitroFrameInternal = Ptr (()) {-# LINE 216 "./System/Nitro.chs" #-} -- | A Nitro socket type NitroSocket = Ptr (()) {-# LINE 219 "./System/Nitro.chs" #-} type NitroSockOpt = Ptr (()) {-# LINE 221 "./System/Nitro.chs" #-} -- void nitro_runtime_start() -- | Start the Nitro runtime manager. This function must be called and must return before calling any other Nitro functions. nitroRuntimeStart :: IO () nitroRuntimeStart = nitroRuntimeStart'_ >>= \res -> return () {-# LINE 226 "./System/Nitro.chs" #-} -- nitro_frame_t *nitro_frame_new_copy(void *d, uint32_t size) nitroFrameNewCopy :: Ptr () -> CUInt -> IO (NitroFrameInternal) nitroFrameNewCopy a1 a2 = let {a1' = id a1} in let {a2' = id a2} in nitroFrameNewCopy'_ a1' a2' >>= \res -> let {res' = id res} in return (res') {-# LINE 230 "./System/Nitro.chs" #-} -- void *nitro_frame_data(nitro_frame_t *f) nitroFrameData :: NitroFrameInternal -> IO (Ptr ()) nitroFrameData a1 = let {a1' = id a1} in nitroFrameData'_ a1' >>= \res -> let {res' = id res} in return (res') {-# LINE 234 "./System/Nitro.chs" #-} -- uint32_t nitro_frame_size(nitro_frame_t *f) nitroFrameSize :: NitroFrameInternal -> IO (CUInt) nitroFrameSize a1 = let {a1' = id a1} in nitroFrameSize'_ a1' >>= \res -> let {res' = id res} in return (res') {-# LINE 238 "./System/Nitro.chs" #-} -- nitro_socket_t * nitro_socket_bind(char *location, nitro_sockopt_t *opt) nitroSocketBind :: String -> NitroSockOpt -> IO (NitroSocket) nitroSocketBind a1 a2 = withCString a1 $ \a1' -> let {a2' = id a2} in nitroSocketBind'_ a1' a2' >>= \res -> let {res' = id res} in return (res') {-# LINE 242 "./System/Nitro.chs" #-} -- nitro_socket_t * nitro_socket_connect(char *location, nitro_sockopt_t *opt) nitroSocketConnect :: String -> NitroSockOpt -> IO (NitroSocket) nitroSocketConnect a1 a2 = withCString a1 $ \a1' -> let {a2' = id a2} in nitroSocketConnect'_ a1' a2' >>= \res -> let {res' = id res} in return (res') {-# LINE 246 "./System/Nitro.chs" #-} -- nitro_sockopt_t *nitro_sockopt_new() nitroSockoptNew :: IO (NitroSockOpt) nitroSockoptNew = nitroSockoptNew'_ >>= \res -> let {res' = id res} in return (res') {-# LINE 250 "./System/Nitro.chs" #-} -- void nitro_sockopt_set_hwm(nitro_sockopt_t *opt, int hwm) nitroSockoptSetHwm :: NitroSockOpt -> Int -> IO () nitroSockoptSetHwm a1 a2 = let {a1' = id a1} in let {a2' = fromIntegral a2} in nitroSockoptSetHwm'_ a1' a2' >>= \res -> return () {-# LINE 254 "./System/Nitro.chs" #-} -- void nitro_sockopt_set_want_eventfd(nitro_sockopt_t *opt, int want_eventfd) nitroSockoptSetWantEventfd :: NitroSockOpt -> Int -> IO () nitroSockoptSetWantEventfd a1 a2 = let {a1' = id a1} in let {a2' = fromIntegral a2} in nitroSockoptSetWantEventfd'_ a1' a2' >>= \res -> return () {-# LINE 258 "./System/Nitro.chs" #-} nitroSocketClose :: NitroSocket -> IO () nitroSocketClose a1 = let {a1' = id a1} in nitroSocketClose'_ a1' >>= \res -> return () {-# LINE 261 "./System/Nitro.chs" #-} nitroSend :: NitroFrameInternal -> NitroSocket -> Int -> IO (Int) nitroSend a1 a2 a3 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = fromIntegral a3} in nitroSend'_ a1' a2' a3' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 324 "./System/Nitro.chs" #-} nitroRecv :: NitroSocket -> Int -> IO (NitroFrameInternal) nitroRecv a1 a2 = let {a1' = id a1} in let {a2' = fromIntegral a2} in nitroRecv'_ a1' a2' >>= \res -> let {res' = id res} in return (res') {-# LINE 327 "./System/Nitro.chs" #-} nitroReply :: NitroFrameInternal -> NitroFrameInternal -> NitroSocket -> Int -> IO (Int) nitroReply a1 a2 a3 a4 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = id a3} in let {a4' = fromIntegral a4} in nitroReply'_ a1' a2' a3' a4' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 330 "./System/Nitro.chs" #-} nitroRelayFw :: NitroFrameInternal -> NitroFrameInternal -> NitroSocket -> Int -> IO (Int) nitroRelayFw a1 a2 a3 a4 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = id a3} in let {a4' = fromIntegral a4} in nitroRelayFw'_ a1' a2' a3' a4' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 333 "./System/Nitro.chs" #-} nitroRelayBk :: NitroFrameInternal -> NitroFrameInternal -> NitroSocket -> Int -> IO (Int) nitroRelayBk a1 a2 a3 a4 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = id a3} in let {a4' = fromIntegral a4} in nitroRelayBk'_ a1' a2' a3' a4' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 336 "./System/Nitro.chs" #-} nitroSub :: NitroSocket -> Ptr CUChar -> CULong -> IO (Int) nitroSub a1 a2 a3 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = id a3} in nitroSub'_ a1' a2' a3' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 339 "./System/Nitro.chs" #-} nitroUnsub :: NitroSocket -> Ptr CUChar -> CULong -> IO (Int) nitroUnsub a1 a2 a3 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = id a3} in nitroUnsub'_ a1' a2' a3' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 342 "./System/Nitro.chs" #-} nitroPub :: NitroFrameInternal -> Ptr CUChar -> CULong -> NitroSocket -> Int -> IO (Int) nitroPub a1 a2 a3 a4 a5 = let {a1' = id a1} in let {a2' = id a2} in let {a3' = id a3} in let {a4' = id a4} in let {a5' = fromIntegral a5} in nitroPub'_ a1' a2' a3' a4' a5' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 345 "./System/Nitro.chs" #-} nitroEventfd :: NitroSocket -> IO (Int) nitroEventfd a1 = let {a1' = id a1} in nitroEventfd'_ a1' >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 348 "./System/Nitro.chs" #-} nitroFrameDestroy :: NitroFrameInternal -> IO () nitroFrameDestroy a1 = let {a1' = id a1} in nitroFrameDestroy'_ a1' >>= \res -> return () {-# LINE 351 "./System/Nitro.chs" #-} --flags api data Flag = NoFlag | Reuse | NoWait deriving (Show,Eq,Enum) toflag :: Flag -> [Flag] -> Int toflag baseFlag = fromIntegral . foldr ((.|.) . fromEnum) (fromEnum baseFlag) --error api data NitroError = NitroErrNone | NitroErrErrno | NitroErrAlreadyRunning | NitroErrNotRunning | NitroErrTcpLocNocolon | NitroErrTcpLocBadport | NitroErrTcpLocBadipv4 | NitroErrParseBadTransport | NitroErrTcpBadAny | NitroErrEagain | NitroErrNoRecipient | NitroErrEncrypt | NitroErrDecrypt | NitroErrInvalidClear | NitroErrMaxFrameExceeded | NitroErrBadProtocolVersion | NitroErrDoubleHandshake | NitroErrNoHandshake | NitroErrBadSub | NitroErrBadHandshake | NitroErrInvalidCert | NitroErrBadInprocOpt | NitroErrBadSecure | NitroErrInprocAlreadyBound | NitroErrInprocNotBound | NitroErrInprocNoConnections | NitroErrSubAlready | NitroErrSubMissing deriving (Enum,Show,Eq) {-# LINE 365 "./System/Nitro.chs" #-} nitroError :: IO (Int) nitroError = nitroError'_ >>= \res -> let {res' = fromIntegral res} in return (res') {-# LINE 368 "./System/Nitro.chs" #-} nitroErrmsg :: Int -> IO (String) nitroErrmsg a1 = let {a1' = fromIntegral a1} in nitroErrmsg'_ a1' >>= \res -> peekCString res >>= \res' -> return (res') {-# LINE 371 "./System/Nitro.chs" #-} throwNitroError fname e = case e == (fromEnum NitroErrEagain) of True -> error $ fname ++ ": " ++ "Nitro Empty" False -> do msg <- nitroErrmsg e error $ fname ++ ": " ++ msg -- API data SocketOptions = SocketOptions { wantFd :: Bool } -- | Default socket options -- -- > defaultOpts = SocketOptions { -- > wantFd = False -- > } defaultOpts = SocketOptions { wantFd = False } -- | Set the WantFd flag on a Nitro socket to True or False. Once the socket is connected or bound, calling fileno on the socket will give an Int representing a valid file descriptor for the socket. setWantFd :: NitroSockOpt -> Bool -> IO () setWantFd opt v = nitroSockoptSetWantEventfd opt (if v then (1 :: Int) else (0 :: Int)) -- | Set the high water mark on a Nitro socket. setHighWaterMark :: NitroSockOpt -> Int -> IO () setHighWaterMark opt hwm = nitroSockoptSetHwm opt hwm setSockOpts :: NitroSockOpt -> SocketOptions -> IO () setSockOpts opt setopts = setWantFd opt (wantFd setopts) newNitroSockOpt :: SocketOptions -> IO NitroSockOpt newNitroSockOpt opts = do newOpt <- nitroSockoptNew when (newOpt == nullPtr) $ error "socket: sock opt points to null" setSockOpts newOpt opts return newOpt -- | Create a Nitro socket bound to a TCP address. bind :: String -> SocketOptions -> IO NitroSocket bind location opts = do bound <- nitroSocketBind location =<< newNitroSockOpt opts when (bound == nullPtr) $ error "bind: socket points to null" return bound -- | Create a Nitro socket connected to a TCP address. connect :: String -> SocketOptions -> IO NitroSocket connect location opts = do connected <- nitroSocketConnect location =<< newNitroSockOpt opts when (connected == nullPtr) $ error "connect: socket points to null" return connected -- | Run an action with a Nitro socket. The socket is garaunteed to close when the action finishes or when an error occurs. withSocket :: (IO NitroSocket) -> (NitroSocket -> IO a) -> IO a withSocket create action = bracket create close action -- | Close a Nitro socket that is either connected or bound. close :: NitroSocket -> IO () close = nitroSocketClose -- | Get the Int representation of a Nitro socket's file descriptor. If wantFd has not been set to True at the creation the Nitro socket, this Int will be meaningless. -- -- > defaultOpt { wantFd = True } -- fileno :: NitroSocket -> IO Int fileno = nitroEventfd -- | Receive a NitroFrame on a Nitro socket. The NitroFrame includes routing information about the sender of the bytestring. The NitroFrame can be given to reply or to the relaying functions in order to route responses back to the sender. recv :: NitroSocket -> [Flag] -> IO NitroFrame recv s flags = do fr <- nitroRecv s (toflag NoFlag flags) fp <- FC.newForeignPtr fr (nitroFrameDestroy fr) when (fr == nullPtr) $ do e <- nitroError throwNitroError "recv" e bstr <- frameToBstr fp return fp -- | Convert a NitroFrame to a strict bytestring. frameToBstr :: NitroFrame -> IO ByteString frameToBstr fp = withForeignPtr fp $ \fr -> do data' <- nitroFrameData fr size <- nitroFrameSize fr fptr <- newForeignPtr_ (castPtr data') return $ BS.copy (PS fptr 0 (fromIntegral size)) -- | Send a strict bytestring on a Nitro socket. Nitro sockets do not set a high water mark by default. send :: NitroSocket -> NitroFrame -> [Flag] -> IO () send s fp flags = do withForeignPtr fp $ \fr -> do e <- nitroSend fr s (toflag Reuse flags) when (e < 0) $ throwNitroError "send" e -- | Convert a strict bytestring to a NitroFrame. bstrToFrame :: ByteString -> IO NitroFrame bstrToFrame (PS ps off size) = do fr <- withForeignPtr ps $ \p -> nitroFrameNewCopy (castPtr p `plusPtr` off) (fromIntegral size) FC.newForeignPtr fr (nitroFrameDestroy fr) -- | Reply to the sender of a NitroFrame. The first NitroFrame is the the sent NitroFrame, and the second NitroFrame is the response. reply :: NitroSocket -> NitroFrame -> NitroFrame -> [Flag] -> IO () reply s snd fr flags = withForeignPtr snd $ \ptr1 -> withForeignPtr fr $ \ptr2 -> do e <- nitroReply ptr1 ptr2 s (toflag Reuse flags) when (e < 0) $ throwNitroError "reply" e -- | Forward a NitroFrame to a new destination, passing along the routing information of the original sender. The first NitroFrame is from the original sender, and the second NitroFrame contains the message to be forwarded. Useful for building proxies. relayFw :: NitroSocket -> NitroFrame -> NitroFrame -> [Flag] -> IO () relayFw s snd fr flags = do withForeignPtr snd $ \ptr1 -> withForeignPtr fr $ \ptr2 -> do e <- nitroRelayFw ptr1 ptr2 s (toflag Reuse flags) when (e < 0) $ throwNitroError "relayFw" e -- | Relay back a NitroFrame by passing along the routing information from a reply. The first NitroFrame is from the replier, and the second NitroFrame contains the message to be relayed back. Useful for building proxies. relayBk :: NitroSocket -> NitroFrame -> NitroFrame -> [Flag] -> IO () relayBk s snd fr flags = do withForeignPtr snd $ \ptr1 -> withForeignPtr fr $ \ptr2 -> do e <- nitroRelayBk ptr1 ptr2 s (toflag Reuse flags) when (e < 0) $ throwNitroError "relayBk" e -- | Subscribe a Nitro socket to a channel prefix. The channel prefix is a strict bytestring. This socket can then receive messages on any channel containing that prefix. sub :: NitroSocket -> ByteString -> IO () sub s (PS key off size) = do e <- withForeignPtr key $ \k -> nitroSub s (castPtr k `plusPtr` off) (fromIntegral size) when (e < 0) $ throwNitroError "sub" e -- | Unsubscribe a Nitro socket from a channel prefix. The channel prefix is a strict bytestring. unsub :: NitroSocket -> ByteString -> IO () unsub s (PS key off size) = do e <- withForeignPtr key $ \k -> nitroSub s (castPtr k `plusPtr` off) (fromIntegral size) when (e < 0) $ throwNitroError "unsub" e -- | Publish a NitroFrame to a channel on a Nitro socket. Any sockets connected to the same location can subscribe to updates from this publisher. pub :: NitroSocket -> NitroFrame -> ByteString -> [Flag] -> IO Int pub s fp (PS key offk sizek) flags = do withForeignPtr fp $ \fr -> withForeignPtr key $ \k -> nitroPub fr (castPtr k `plusPtr` offk) (fromIntegral sizek) s (toflag Reuse flags) foreign import ccall safe "System/Nitro.chs.h nitro_runtime_start" nitroRuntimeStart'_ :: (IO CInt) foreign import ccall safe "System/Nitro.chs.h nitro_frame_new_copy" nitroFrameNewCopy'_ :: ((Ptr ()) -> (CUInt -> (IO (NitroFrameInternal)))) foreign import ccall safe "System/Nitro.chs.h nitro_frame_data" nitroFrameData'_ :: ((NitroFrameInternal) -> (IO (Ptr ()))) foreign import ccall safe "System/Nitro.chs.h nitro_frame_size" nitroFrameSize'_ :: ((NitroFrameInternal) -> (IO CUInt)) foreign import ccall safe "System/Nitro.chs.h nitro_socket_bind" nitroSocketBind'_ :: ((Ptr CChar) -> ((NitroSockOpt) -> (IO (NitroSocket)))) foreign import ccall safe "System/Nitro.chs.h nitro_socket_connect" nitroSocketConnect'_ :: ((Ptr CChar) -> ((NitroSockOpt) -> (IO (NitroSocket)))) foreign import ccall safe "System/Nitro.chs.h nitro_sockopt_new" nitroSockoptNew'_ :: (IO (NitroSockOpt)) foreign import ccall safe "System/Nitro.chs.h nitro_sockopt_set_hwm" nitroSockoptSetHwm'_ :: ((NitroSockOpt) -> (CInt -> (IO ()))) foreign import ccall safe "System/Nitro.chs.h nitro_sockopt_set_want_eventfd" nitroSockoptSetWantEventfd'_ :: ((NitroSockOpt) -> (CInt -> (IO ()))) foreign import ccall safe "System/Nitro.chs.h nitro_socket_close" nitroSocketClose'_ :: ((NitroSocket) -> (IO ())) foreign import ccall safe "System/Nitro.chs.h nitro_send_" nitroSend'_ :: ((NitroFrameInternal) -> ((NitroSocket) -> (CInt -> (IO CInt)))) foreign import ccall safe "System/Nitro.chs.h nitro_recv_" nitroRecv'_ :: ((NitroSocket) -> (CInt -> (IO (NitroFrameInternal)))) foreign import ccall safe "System/Nitro.chs.h nitro_reply_" nitroReply'_ :: ((NitroFrameInternal) -> ((NitroFrameInternal) -> ((NitroSocket) -> (CInt -> (IO CInt))))) foreign import ccall safe "System/Nitro.chs.h nitro_relay_fw_" nitroRelayFw'_ :: ((NitroFrameInternal) -> ((NitroFrameInternal) -> ((NitroSocket) -> (CInt -> (IO CInt))))) foreign import ccall safe "System/Nitro.chs.h nitro_relay_bk_" nitroRelayBk'_ :: ((NitroFrameInternal) -> ((NitroFrameInternal) -> ((NitroSocket) -> (CInt -> (IO CInt))))) foreign import ccall safe "System/Nitro.chs.h nitro_sub_" nitroSub'_ :: ((NitroSocket) -> ((Ptr CUChar) -> (CULong -> (IO CInt)))) foreign import ccall safe "System/Nitro.chs.h nitro_unsub_" nitroUnsub'_ :: ((NitroSocket) -> ((Ptr CUChar) -> (CULong -> (IO CInt)))) foreign import ccall safe "System/Nitro.chs.h nitro_pub_" nitroPub'_ :: ((NitroFrameInternal) -> ((Ptr CUChar) -> (CULong -> ((NitroSocket) -> (CInt -> (IO CInt)))))) foreign import ccall safe "System/Nitro.chs.h nitro_eventfd_" nitroEventfd'_ :: ((NitroSocket) -> (IO CInt)) foreign import ccall safe "System/Nitro.chs.h nitro_frame_destroy_" nitroFrameDestroy'_ :: ((NitroFrameInternal) -> (IO ())) foreign import ccall safe "System/Nitro.chs.h nitro_error" nitroError'_ :: (IO CInt) foreign import ccall safe "System/Nitro.chs.h nitro_errmsg" nitroErrmsg'_ :: (CInt -> (IO (Ptr CChar)))