cloudi-1.7.3: Haskell CloudI API

Safe HaskellNone
LanguageHaskell2010

Foreign.CloudI

Description

Haskell CloudI API. Example usage is available in the integration tests.

Synopsis

Documentation

data RequestType #

provided when handling a service request

Constructors

ASYNC 
SYNC 
Instances
Eq RequestType # 
Instance details

Defined in Foreign.CloudI.Instance

Show RequestType # 
Instance details

Defined in Foreign.CloudI.Instance

type Source = Pid #

the Erlang pid that is the source of the service request

data Response s #

service request callback function return type

Constructors

Response (ByteString, s, T s) 
ResponseInfo (ByteString, ByteString, s, T s) 
Forward (ByteString, ByteString, ByteString, s, T s) 
Forward_ (ByteString, ByteString, ByteString, Int, Int, s, T s) 
Null (s, T s) 
NullError (String, s, T s) 
Instances
Show s => Show (Response s) # 
Instance details

Defined in Foreign.CloudI.Instance

Methods

showsPrec :: Int -> Response s -> ShowS #

show :: Response s -> String #

showList :: [Response s] -> ShowS #

type Callback s = RequestType -> ByteString -> ByteString -> ByteString -> ByteString -> Int -> Int -> ByteString -> Source -> s -> T s -> IO (Response s) #

a function to handle a service request

data T s #

an instance of the CloudI API

Instances
Show (T s) # 
Instance details

Defined in Foreign.CloudI.Instance

Methods

showsPrec :: Int -> T s -> ShowS #

show :: T s -> String #

showList :: [T s] -> ShowS #

transIdNull :: ByteString #

a null trans_id is used to check for a timeout or to get the oldest response with recv_async

data Exception s #

Instances
Show (Exception s) # 
Instance details

Defined in Foreign.CloudI

Typeable s => Exception (Exception s) # 
Instance details

Defined in Foreign.CloudI

type Result a = Either String a #

api :: Typeable s => Int -> s -> IO (Result (T s)) #

creates an instance of the CloudI API

threadCount :: IO (Result Int) #

returns the thread count from the service configuration

subscribe :: T s -> ByteString -> Callback s -> IO (Result (T s)) #

subscribes to a service name pattern with a callback

subscribeCount :: Typeable s => T s -> ByteString -> IO (Result (Int, T s)) #

returns the number of subscriptions for a single service name pattern

unsubscribe :: T s -> ByteString -> IO (Result (T s)) #

unsubscribes from a service name pattern once

sendAsync :: Typeable s => T s -> ByteString -> ByteString -> Maybe Int -> Maybe ByteString -> Maybe Int -> IO (Result (ByteString, T s)) #

sends an asynchronous service request

sendSync :: Typeable s => T s -> ByteString -> ByteString -> Maybe Int -> Maybe ByteString -> Maybe Int -> IO (Result (ByteString, ByteString, ByteString, T s)) #

sends a synchronous service request

mcastAsync :: Typeable s => T s -> ByteString -> ByteString -> Maybe Int -> Maybe ByteString -> Maybe Int -> IO (Result (Array Int ByteString, T s)) #

sends asynchronous service requests to all subscribers of the matching service name pattern

forward_ :: Typeable s => T s -> RequestType -> ByteString -> ByteString -> ByteString -> Int -> Int -> ByteString -> Source -> IO () #

forwards a service request to a different service name

forwardAsync :: Typeable s => T s -> ByteString -> ByteString -> ByteString -> Int -> Int -> ByteString -> Source -> IO () #

forwards an asynchronous service request to a different service name

forwardSync :: Typeable s => T s -> ByteString -> ByteString -> ByteString -> Int -> Int -> ByteString -> Source -> IO () #

forwards a synchronous service request to a different service name

return_ :: Typeable s => T s -> RequestType -> ByteString -> ByteString -> ByteString -> ByteString -> Int -> ByteString -> Source -> IO () #

provides a response to a service request

returnAsync :: Typeable s => T s -> ByteString -> ByteString -> ByteString -> ByteString -> Int -> ByteString -> Source -> IO () #

provides a response to an asynchronous service request

returnSync :: Typeable s => T s -> ByteString -> ByteString -> ByteString -> ByteString -> Int -> ByteString -> Source -> IO () #

provides a response to a synchronous service request

recvAsync :: Typeable s => T s -> Maybe Int -> Maybe ByteString -> Maybe Bool -> IO (Result (ByteString, ByteString, ByteString, T s)) #

blocks to receive an asynchronous service request response

processIndex :: T s -> Int #

returns the 0-based index of this process in the service instance

processCount :: T s -> Int #

returns the current process count based on the service configuration

processCountMax :: T s -> Int #

returns the count_process_dynamic maximum count based on the service configuration

processCountMin :: T s -> Int #

returns the count_process_dynamic minimum count based on the service configuration

prefix :: T s -> ByteString #

returns the service name pattern prefix from the service configuration

timeoutInitialize :: T s -> Int #

returns the service initialization timeout from the service configuration

timeoutAsync :: T s -> Int #

returns the default asynchronous service request send timeout from the service configuration

timeoutSync :: T s -> Int #

returns the default synchronous service request send timeout from the service configuration

timeoutTerminate :: T s -> Int #

returns the service termination timeout based on the service configuration

poll :: Typeable s => T s -> Int -> IO (Result (Bool, T s)) #

blocks to process incoming CloudI service requests

threadCreate :: (Int -> IO ()) -> Int -> IO ThreadId #

simplifies thread creation and join

Concurrent.setNumCapabilities threadCount
mapM_ (CloudI.threadCreate task) [0..threadCount - 1]
CloudI.threadsWait

threadsWait :: IO () #

wait for threads to join after being created by threadCreate

infoKeyValueParse :: ByteString -> Map ByteString [ByteString] #

parses "text_pairs" in service request info