Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data StreamStatus
- data Stream = Stream {
- streamPath :: FilePath
- vOffsets :: !(TVar (IntMap Int))
- indexNames :: !(Vector IndexName)
- indices :: !(HashMap IndexName (TVar (IntMap Int)))
- vCount :: !(TVar Int)
- vStatus :: !(TVar StreamStatus)
- followThread :: !ThreadId
- indexHandle :: !Handle
- payloadHandle :: !Handle
- vActivity :: !(TVar Activity)
- type Activity = Either Double Int
- addActivity :: Stream -> STM ()
- removeActivity :: Stream -> IO ()
- closeStream :: Stream -> IO ()
- createStream :: WatchManager -> FilePath -> IO Stream
- type QueryResult = ((Int, Int), (Int, Int))
- isEmptyResult :: QueryResult -> Bool
- range :: Int -> Int -> RequestType -> IntMap Int -> (Bool, QueryResult)
- splitR :: Int -> IntMap a -> (IntMap a, IntMap a)
- data FranzReader = FranzReader {}
- data ReaperState = ReaperState {
- prunedStreams :: !Int
- totalStreams :: !Int
- reaper :: Double -> Double -> FranzReader -> IO ()
- withFranzReader :: (FranzReader -> IO ()) -> IO ()
- newFranzReader :: IO FranzReader
- closeFranzReader :: FranzReader -> IO ()
- newtype FranzPrefix = FranzPrefix {}
- newtype FranzDirectory = FranzDirectory FilePath
- getFranzDirectory :: FranzPrefix -> FranzDirectory -> FilePath
- getFranzStreamPath :: FranzPrefix -> FranzDirectory -> StreamName -> FilePath
- handleQuery :: FranzPrefix -> FranzReader -> FranzDirectory -> Query -> (FranzException -> IO r) -> (Stream -> STM (Maybe QueryResult) -> IO r) -> IO r
Documentation
data StreamStatus Source #
Instances
Eq StreamStatus Source # | |
Defined in Database.Franz.Internal.Reader (==) :: StreamStatus -> StreamStatus -> Bool # (/=) :: StreamStatus -> StreamStatus -> Bool # |
Stream | |
|
addActivity :: Stream -> STM () Source #
removeActivity :: Stream -> IO () Source #
closeStream :: Stream -> IO () Source #
createStream :: WatchManager -> FilePath -> IO Stream Source #
isEmptyResult :: QueryResult -> Bool Source #
:: Int | from |
-> Int | to |
-> RequestType | |
-> IntMap Int | offsets |
-> (Bool, QueryResult) |
data FranzReader Source #
data ReaperState Source #
ReaperState | |
|
withFranzReader :: (FranzReader -> IO ()) -> IO () Source #
closeFranzReader :: FranzReader -> IO () Source #
newtype FranzPrefix Source #
Globally-configured path which contains franz directories.
Instances
Eq FranzPrefix Source # | |
Defined in Database.Franz.Internal.Reader (==) :: FranzPrefix -> FranzPrefix -> Bool # (/=) :: FranzPrefix -> FranzPrefix -> Bool # | |
Hashable FranzPrefix Source # | |
Defined in Database.Franz.Internal.Reader hashWithSalt :: Int -> FranzPrefix -> Int # hash :: FranzPrefix -> Int # |
newtype FranzDirectory Source #
Directory which contains franz streams. Values of this type serve two purposes:
- Arbitrary prefix so that clients don't have to specify the full path
Instances
Eq FranzDirectory Source # | |
Defined in Database.Franz.Internal.Reader (==) :: FranzDirectory -> FranzDirectory -> Bool # (/=) :: FranzDirectory -> FranzDirectory -> Bool # | |
Hashable FranzDirectory Source # | |
Defined in Database.Franz.Internal.Reader hashWithSalt :: Int -> FranzDirectory -> Int # hash :: FranzDirectory -> Int # |
getFranzStreamPath :: FranzPrefix -> FranzDirectory -> StreamName -> FilePath Source #
handleQuery :: FranzPrefix -> FranzReader -> FranzDirectory -> Query -> (FranzException -> IO r) -> (Stream -> STM (Maybe QueryResult) -> IO r) -> IO r Source #