Copyright | (c) Moritz Clasmeier 2017 2018 |
---|---|
License | BSD3 |
Maintainer | mtesseract@silverratio.net |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Network.Nakadi.Types
Description
This module provides the Nakadi API Types.
Synopsis
- module Network.Nakadi.Types.Config
- module Network.Nakadi.Types.Exceptions
- module Network.Nakadi.Types.Logger
- module Network.Nakadi.Types.Problem
- module Network.Nakadi.Types.Service
- data CommitStrategy
- data CommitBufferingStrategy
- newtype CommitTimeout = CommitTimeout {}
- class (Monad b, Monad m) => MonadNakadiBase b m where
- nakadiLiftBase :: b a -> m a
- class (MonadNakadiBase b m, MonadThrow b, MonadMask b, MonadThrow m, MonadCatch m) => MonadNakadi b m | m -> b where
- class HasNakadiConfig b r | r -> b where
- nakadiConfig :: r -> Config b
- data NakadiT b m a
- runNakadiT :: Config b -> NakadiT b m a -> m a
Documentation
module Network.Nakadi.Types.Config
module Network.Nakadi.Types.Logger
module Network.Nakadi.Types.Problem
module Network.Nakadi.Types.Service
data CommitStrategy Source #
This type encodes the supported strategies for subscription cursor committing.
Constructors
CommitSync | This strategy synchronously commits every cursor. |
CommitAsync CommitBufferingStrategy | This strategy sends cursors to be committed to a dedicated thread responsible for committing them. Cursors are commited one by one, without special buffering logic. |
Instances
HasNakadiCommitStrategy (Config m) CommitStrategy | |
Defined in Network.Nakadi.Internal.Lenses Methods commitStrategy :: Lens' (Config m) CommitStrategy |
data CommitBufferingStrategy Source #
This type encodes the supported buffering strategies for asynchronous subscription cursor committing.
Constructors
CommitNoBuffer | No buffering at all. |
CommitTimeBuffer Int32 | Buffer for the specified duration, given in milliseconds. |
CommitSmartBuffer | Buffer for a fixed duration, but
committing cursors immediately if the
number of events processed since the
last commit crosses a threshold derived
from |
newtype CommitTimeout Source #
This type is used for specifying subscription commit timeouts in seconds.
Constructors
CommitTimeout | |
Fields |
Instances
Eq CommitTimeout Source # | |
Defined in Network.Nakadi.Internal.Types.Subscriptions Methods (==) :: CommitTimeout -> CommitTimeout -> Bool # (/=) :: CommitTimeout -> CommitTimeout -> Bool # | |
Ord CommitTimeout Source # | |
Defined in Network.Nakadi.Internal.Types.Subscriptions Methods compare :: CommitTimeout -> CommitTimeout -> Ordering # (<) :: CommitTimeout -> CommitTimeout -> Bool # (<=) :: CommitTimeout -> CommitTimeout -> Bool # (>) :: CommitTimeout -> CommitTimeout -> Bool # (>=) :: CommitTimeout -> CommitTimeout -> Bool # max :: CommitTimeout -> CommitTimeout -> CommitTimeout # min :: CommitTimeout -> CommitTimeout -> CommitTimeout # | |
Show CommitTimeout Source # | |
Defined in Network.Nakadi.Internal.Types.Subscriptions Methods showsPrec :: Int -> CommitTimeout -> ShowS # show :: CommitTimeout -> String # showList :: [CommitTimeout] -> ShowS # | |
HasNakadiCommitTimeout (Config m) (Maybe CommitTimeout) | |
Defined in Network.Nakadi.Internal.Lenses Methods commitTimeout :: Lens' (Config m) (Maybe CommitTimeout) |
class (Monad b, Monad m) => MonadNakadiBase b m where Source #
Minimal complete definition
Nothing
Methods
nakadiLiftBase :: b a -> m a Source #
nakadiLiftBase :: (MonadNakadiBase b n, MonadTrans t, m ~ t n) => b a -> m a Source #
Instances
class (MonadNakadiBase b m, MonadThrow b, MonadMask b, MonadThrow m, MonadCatch m) => MonadNakadi b m | m -> b where Source #
The MonadNakadi
typeclass is implemented by monads in which
Nakadi can be called. The first parameter (b
) denotes the `base
monad`. This is the monad in which the core actions are run. This
includes executing (non-streaming) HTTP requests and running
user-provided callbacks. The typeclass provides methods for
* retrieving the Nakadi configuration
* locally changing the Nakadi configuration
* extracting specific Nakadi configuration values
* lifting actions from the
The MonadNakadi
typeclass is modelled closely after MonadReader
.
Minimal complete definition
Nothing
Methods
nakadiAsk :: m (Config b) Source #
nakadiAsk :: (MonadNakadi b n, MonadTrans t, m ~ t n) => m (Config b) Source #
Instances
MonadNakadi IO IO Source # | |
MonadNakadi b m => MonadNakadi b (ResourceT m) Source # | |
MonadNakadi b m => MonadNakadi b (NoLoggingT m) Source # | |
Defined in Network.Nakadi.Internal.Types Methods nakadiAsk :: NoLoggingT m (Config b) Source # | |
MonadNakadi b m => MonadNakadi b (LoggingT m) Source # | |
MonadNakadi b m => MonadNakadi b (StateT s m) Source # |
|
MonadNakadi b m => MonadNakadi b (StateT s m) Source # |
|
(MonadNakadi b m, Monoid w) => MonadNakadi b (WriterT w m) Source # |
|
(MonadNakadi b m, Monoid w) => MonadNakadi b (WriterT w m) Source # |
|
(MonadCatch m, MonadMask b, MonadNakadiBase b (NakadiT b m)) => MonadNakadi b (NakadiT b m) Source # | |
(MonadMask b, MonadCatch m, MonadNakadiBase b (ReaderT r m), HasNakadiConfig b r) => MonadNakadi b (ReaderT r m) Source # | |
class HasNakadiConfig b r | r -> b where Source #
Methods
nakadiConfig :: r -> Config b Source #
Instances
runNakadiT :: Config b -> NakadiT b m a -> m a Source #