nitro-0.2.2.4: Haskell bindings for Nitro

Portabilitynon-portable
Stabilityexperimental
MaintainerErin Dahlgren <edahlgren@bu.mp>
Safe HaskellNone

System.Nitro

Contents

Description

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 (https://github.com/bumptech/nitro).

Synopsis

How to use Nitro sockets

 {-# 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

nitroRuntimeStart :: IO ()Source

Start the Nitro runtime manager. This function must be called and must return before calling any other Nitro functions.

type NitroSocket = Ptr ()Source

A Nitro socket

data SocketOptions Source

Constructors

SocketOptions 

Fields

wantFd :: Bool
 

defaultOpts :: SocketOptionsSource

Default socket options

 defaultOpts = SocketOptions {
       wantFd = False
 }

bind :: String -> SocketOptions -> IO NitroSocketSource

Create a Nitro socket bound to a TCP address.

connect :: String -> SocketOptions -> IO NitroSocketSource

Create a Nitro socket connected to a TCP address.

withSocket :: IO NitroSocket -> (NitroSocket -> IO a) -> IO aSource

Run an action with a Nitro socket. The socket is garaunteed to close when the action finishes or when an error occurs.

close :: NitroSocket -> IO ()Source

Close a Nitro socket that is either connected or bound.

Distributing messages

 {-# 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

type NitroFrame = ForeignPtr ()Source

A Nitro frame, which contains a message and routing information about the message's sender.

bstrToFrame :: ByteString -> IO NitroFrameSource

Convert a strict bytestring to a NitroFrame.

frameToBstr :: NitroFrame -> IO ByteStringSource

Convert a NitroFrame to a strict bytestring.

recv :: NitroSocket -> [Flag] -> IO NitroFrameSource

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.

send :: NitroSocket -> NitroFrame -> [Flag] -> IO ()Source

Send a strict bytestring on a Nitro socket. Nitro sockets do not set a high water mark by default.

Routing messages

 {-# 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.

reply :: NitroSocket -> NitroFrame -> NitroFrame -> [Flag] -> IO ()Source

Reply to the sender of a NitroFrame. The first NitroFrame is the the sent NitroFrame, and the second NitroFrame is the response.

Proxying messages

 {-# 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

relayFw :: NitroSocket -> NitroFrame -> NitroFrame -> [Flag] -> IO ()Source

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.

relayBk :: NitroSocket -> NitroFrame -> NitroFrame -> [Flag] -> IO ()Source

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.

Pub/Sub messages

 {-# 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

sub :: NitroSocket -> ByteString -> IO ()Source

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.

unsub :: NitroSocket -> ByteString -> IO ()Source

Unsubscribe a Nitro socket from a channel prefix. The channel prefix is a strict bytestring.

pub :: NitroSocket -> NitroFrame -> ByteString -> [Flag] -> IO IntSource

Publish a NitroFrame to a channel on a Nitro socket. Any sockets connected to the same location can subscribe to updates from this publisher.

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.

fileno :: NitroSocket -> IO IntSource

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 }

Types

data Flag Source

Constructors

NoWait 

Instances