| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Franz.Network
Synopsis
- startServer :: Double -> Double -> PortNumber -> FilePath -> Maybe FilePath -> IO ()
- defaultPort :: PortNumber
- data Connection
- withConnection :: String -> PortNumber -> ByteString -> (Connection -> IO r) -> IO r
- connect :: String -> PortNumber -> ByteString -> IO Connection
- disconnect :: Connection -> IO ()
- data Query = Query {
- reqStream :: !ByteString
- reqFrom :: !ItemRef
- reqTo :: !ItemRef
- reqType :: !RequestType
- data ItemRef
- = BySeqNum !Int
- | ByIndex !ByteString !Int
- data RequestType
- defQuery :: ByteString -> Query
- type Response = Either Contents (STM Contents)
- awaitResponse :: STM (Either a (STM a)) -> STM a
- type SomeIndexMap = HashMap ByteString Int64
- type Contents = [(Int, SomeIndexMap, ByteString)]
- fetch :: Connection -> Query -> (STM Response -> IO r) -> IO r
- fetchTraverse :: Traversable t => Connection -> t Query -> (STM (Either (t Contents) (STM (t Contents))) -> IO r) -> IO r
- fetchSimple :: Connection -> Int -> Query -> IO Contents
- atomicallyWithin :: Int -> STM a -> IO (Maybe a)
- data FranzException
Documentation
startServer :: Double -> Double -> PortNumber -> FilePath -> Maybe FilePath -> IO () Source #
data Connection Source #
withConnection :: String -> PortNumber -> ByteString -> (Connection -> IO r) -> IO r Source #
connect :: String -> PortNumber -> ByteString -> IO Connection Source #
disconnect :: Connection -> IO () Source #
Constructors
| Query | |
Fields
| |
Instances
| Show Query Source # | |
| Generic Query Source # | |
| Serialize Query Source # | |
| type Rep Query Source # | |
Defined in Database.Franz.Reader type Rep Query = D1 (MetaData "Query" "Database.Franz.Reader" "franz-0.2.1-DMs1sFxJDSYKCecIbcBQYI" False) (C1 (MetaCons "Query" PrefixI True) ((S1 (MetaSel (Just "reqStream") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Just "reqFrom") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ItemRef)) :*: (S1 (MetaSel (Just "reqTo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ItemRef) :*: S1 (MetaSel (Just "reqType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RequestType)))) | |
Constructors
| BySeqNum !Int | sequential number |
| ByIndex !ByteString !Int | index name and value |
Instances
| Show ItemRef Source # | |
| Generic ItemRef Source # | |
| Serialize ItemRef Source # | |
| type Rep ItemRef Source # | |
Defined in Database.Franz.Reader type Rep ItemRef = D1 (MetaData "ItemRef" "Database.Franz.Reader" "franz-0.2.1-DMs1sFxJDSYKCecIbcBQYI" False) (C1 (MetaCons "BySeqNum" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "ByIndex" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int))) | |
data RequestType Source #
Instances
| Show RequestType Source # | |
Defined in Database.Franz.Reader Methods showsPrec :: Int -> RequestType -> ShowS # show :: RequestType -> String # showList :: [RequestType] -> ShowS # | |
| Generic RequestType Source # | |
Defined in Database.Franz.Reader Associated Types type Rep RequestType :: Type -> Type # | |
| Serialize RequestType Source # | |
Defined in Database.Franz.Reader | |
| type Rep RequestType Source # | |
defQuery :: ByteString -> Query Source #
type Response = Either Contents (STM Contents) Source #
When it is Right, it might block until the content arrives.
type SomeIndexMap = HashMap ByteString Int64 Source #
type Contents = [(Int, SomeIndexMap, ByteString)] Source #
(seqno, indices, payloads)
Arguments
| :: Connection | |
| -> Query | |
| -> (STM Response -> IO r) | running the STM action blocks until the response arrives |
| -> IO r |
Fetch requested data from the server. Termination of the continuation cancels the request, allowing flexible control of its lifetime.
fetchTraverse :: Traversable t => Connection -> t Query -> (STM (Either (t Contents) (STM (t Contents))) -> IO r) -> IO r Source #
Queries in traversable t form an atomic request. The response will become
available once all the elements are available.
Generalisation to Traversable guarantees that the response preserves the shape of the request.
Arguments
| :: Connection | |
| -> Int | timeout in microseconds |
| -> Query | |
| -> IO Contents |
Send a single query and wait for the result. If it timeouts, it returns an empty list.
data FranzException Source #
Constructors
| MalformedRequest !String | |
| StreamNotFound !FilePath | |
| IndexNotFound !ByteString ![ByteString] | |
| InternalError !String | |
| ClientError !String |