| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Franz.Reader
Documentation
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 # | |
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))) | |
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
| Stream | |
Fields
| |
addActivity :: Activity -> Activity Source #
removeActivity :: Stream -> IO () Source #
closeStream :: Stream -> IO () Source #
createStream :: WatchManager -> FilePath -> IO Stream Source #
Arguments
| :: Int | from |
| -> Int | to |
| -> RequestType | |
| -> IntMap Int | offsets |
| -> (Bool, QueryResult) |
data FranzException Source #
Constructors
| MalformedRequest !String | |
| StreamNotFound !FilePath | |
| IndexNotFound !ByteString ![ByteString] | |
| InternalError !String | |
| ClientError !String |
Instances
data FranzReader Source #
Constructors
| FranzReader | |
Fields
| |
withFranzReader :: FilePath -> (FranzReader -> IO ()) -> IO () Source #
handleQuery :: FranzReader -> FilePath -> Query -> IO (Stream, STM (Bool, QueryResult)) Source #