libraft-0.1.1.0: Raft consensus algorithm

Safe HaskellNone
LanguageHaskell2010

Raft.NodeState

Synopsis

Documentation

data Mode Source #

Constructors

Follower 
Candidate 
Leader 
Instances
Show Mode Source # 
Instance details

Defined in Raft.NodeState

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

data ResultState init where Source #

Existential type hiding the result type of a transition

Constructors

ResultState :: Transition init res -> NodeState res -> ResultState init 
Instances
Show (ResultState init) Source # 
Instance details

Defined in Raft.NodeState

Methods

showsPrec :: Int -> ResultState init -> ShowS #

show :: ResultState init -> String #

showList :: [ResultState init] -> ShowS #

data RaftNodeState where Source #

Existential type hiding the internal node state

Constructors

RaftNodeState 

Fields

Instances
Show RaftNodeState Source # 
Instance details

Defined in Raft.NodeState

initRaftNodeState :: RaftNodeState Source #

A node in Raft begins as a follower

data NodeState (a :: Mode) where Source #

The volatile state of a Raft Node

Instances
Show (NodeState v) Source # 
Instance details

Defined in Raft.NodeState

data CurrentLeader Source #

Representation of the current leader in the cluster. The system is considered to be unavailable if there is no leader

Instances
Eq CurrentLeader Source # 
Instance details

Defined in Raft.NodeState

Show CurrentLeader Source # 
Instance details

Defined in Raft.NodeState

Generic CurrentLeader Source # 
Instance details

Defined in Raft.NodeState

Associated Types

type Rep CurrentLeader :: Type -> Type #

Serialize CurrentLeader Source # 
Instance details

Defined in Raft.NodeState

type Rep CurrentLeader Source # 
Instance details

Defined in Raft.NodeState

type Rep CurrentLeader = D1 (MetaData "CurrentLeader" "Raft.NodeState" "libraft-0.1.1.0-8nwazCMBvi7EUIW9UIbZhF" False) (C1 (MetaCons "CurrentLeader" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LeaderId)) :+: C1 (MetaCons "NoLeader" PrefixI False) (U1 :: Type -> Type))

data FollowerState Source #

Constructors

FollowerState 

Fields

Instances
Show FollowerState Source # 
Instance details

Defined in Raft.NodeState

data CandidateState Source #

Constructors

CandidateState 

Fields

Instances
Show CandidateState Source # 
Instance details

Defined in Raft.NodeState

data LeaderState Source #

Constructors

LeaderState 

Fields

Instances
Show LeaderState Source # 
Instance details

Defined in Raft.NodeState

setLastLogEntryData :: NodeState ns -> Entries v -> NodeState ns Source #

Update the last log entry in the node's log

getLastLogEntryData :: NodeState ns -> (Index, Term) Source #

Get the last applied index and the commit index of the last log entry in the node's log

getLastAppliedAndCommitIndex :: NodeState ns -> (Index, Index) Source #

Get the index of highest log entry applied to state machine and the index of highest log entry known to be committed

isFollower :: NodeState s -> Bool Source #

Check if node is in a follower state

isCandidate :: NodeState s -> Bool Source #

Check if node is in a candidate state

isLeader :: NodeState s -> Bool Source #

Check if node is in a leader state