Safe Haskell | None |
---|---|
Language | Haskell2010 |
Raft.Monad
Synopsis
- type MonadRaft v m = (MonadRaftChan v m, MonadRaftFork m)
- class Monad m => MonadRaftChan v m where
- type RaftEventChan v m
- readRaftChan :: RaftEventChan v m -> m (Event v)
- writeRaftChan :: RaftEventChan v m -> Event v -> m ()
- newRaftChan :: m (RaftEventChan v m)
- data RaftThreadRole
- class Monad m => MonadRaftFork m where
- type RaftThreadId m
- raftFork :: RaftThreadRole -> m () -> m (RaftThreadId m)
- data RaftEnv v m = RaftEnv {
- eventChan :: RaftEventChan v m
- resetElectionTimer :: m ()
- resetHeartbeatTimer :: m ()
- raftNodeConfig :: RaftNodeConfig
- raftNodeLogCtx :: LogCtx (RaftT v m)
- raftNodeMetrics :: Metrics
- initializeRaftEnv :: MonadIO m => RaftEventChan v m -> m () -> m () -> RaftNodeConfig -> LogCtx (RaftT v m) -> m (RaftEnv v m)
- data RaftT v m a
- runRaftT :: Monad m => RaftNodeState v -> RaftEnv v m -> RaftT v m a -> m a
- logInfo :: MonadIO m => Text -> RaftT v m ()
- logDebug :: MonadIO m => Text -> RaftT v m ()
- logCritical :: MonadIO m => Text -> RaftT v m ()
- logAndPanic :: MonadIO m => Text -> RaftT v m a
Documentation
type MonadRaft v m = (MonadRaftChan v m, MonadRaftFork m) Source #
class Monad m => MonadRaftChan v m where Source #
The typeclass specifying the datatype used as the core event channel in the main raft event loop, as well as functions for creating, reading, and writing to the channel, and how to fork a computation that performs some action with the channel.
Note: This module uses AllowAmbiguousTypes which removes the necessity for Proxy value arguments in lieu of TypeApplication. For example:
newRaftChan @v
instead of
newRaftChan (Proxy :: Proxy v)
Associated Types
type RaftEventChan v m Source #
Methods
readRaftChan :: RaftEventChan v m -> m (Event v) Source #
writeRaftChan :: RaftEventChan v m -> Event v -> m () Source #
newRaftChan :: m (RaftEventChan v m) Source #
Instances
data RaftThreadRole Source #
Constructors
RPCHandler | |
ClientRequestHandler | |
CustomThreadRole Text |
Instances
Show RaftThreadRole Source # | |
Defined in Raft.Monad Methods showsPrec :: Int -> RaftThreadRole -> ShowS # show :: RaftThreadRole -> String # showList :: [RaftThreadRole] -> ShowS # |
class Monad m => MonadRaftFork m where Source #
The typeclass encapsulating the concurrency operations necessary for the implementation of the main event handling loop.
Associated Types
type RaftThreadId m Source #
Methods
Arguments
:: RaftThreadRole | The role of the current thread being forked |
-> m () | The action to fork |
-> m (RaftThreadId m) |
Instances
The raft server environment composed of the concurrent variables used in the effectful raft layer.
Constructors
RaftEnv | |
Fields
|
initializeRaftEnv :: MonadIO m => RaftEventChan v m -> m () -> m () -> RaftNodeConfig -> LogCtx (RaftT v m) -> m (RaftEnv v m) Source #