libraft-0.5.0.0: Raft consensus algorithm

Safe HaskellNone
LanguageHaskell2010

Raft.Types

Synopsis

Documentation

type NodeId = ByteString Source #

Unique identifier of a Raft node

newtype ClientId Source #

Unique identifier of a client

Constructors

ClientId NodeId 
Instances
Eq ClientId Source # 
Instance details

Defined in Raft.Types

Ord ClientId Source # 
Instance details

Defined in Raft.Types

Read ClientId Source # 
Instance details

Defined in Raft.Types

Show ClientId Source # 
Instance details

Defined in Raft.Types

Generic ClientId Source # 
Instance details

Defined in Raft.Types

Associated Types

type Rep ClientId :: Type -> Type #

Methods

from :: ClientId -> Rep ClientId x #

to :: Rep ClientId x -> ClientId #

Serialize ClientId Source # 
Instance details

Defined in Raft.Types

type Rep ClientId Source # 
Instance details

Defined in Raft.Types

type Rep ClientId = D1 (MetaData "ClientId" "Raft.Types" "libraft-0.5.0.0-J9sQlo4v2xjSwCkwompQR" True) (C1 (MetaCons "ClientId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeId)))

newtype LeaderId Source #

Unique identifier of a leader

Constructors

LeaderId 

Fields

Instances
Eq LeaderId Source # 
Instance details

Defined in Raft.Types

Read LeaderId Source # 
Instance details

Defined in Raft.Types

Show LeaderId Source # 
Instance details

Defined in Raft.Types

Generic LeaderId Source # 
Instance details

Defined in Raft.Types

Associated Types

type Rep LeaderId :: Type -> Type #

Methods

from :: LeaderId -> Rep LeaderId x #

to :: Rep LeaderId x -> LeaderId #

Serialize LeaderId Source # 
Instance details

Defined in Raft.Types

type Rep LeaderId Source # 
Instance details

Defined in Raft.Types

type Rep LeaderId = D1 (MetaData "LeaderId" "Raft.Types" "libraft-0.5.0.0-J9sQlo4v2xjSwCkwompQR" True) (C1 (MetaCons "LeaderId" PrefixI True) (S1 (MetaSel (Just "unLeaderId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NodeId)))

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.Types

Show CurrentLeader Source # 
Instance details

Defined in Raft.Types

Generic CurrentLeader Source # 
Instance details

Defined in Raft.Types

Associated Types

type Rep CurrentLeader :: Type -> Type #

Serialize CurrentLeader Source # 
Instance details

Defined in Raft.Types

type Rep CurrentLeader Source # 
Instance details

Defined in Raft.Types

type Rep CurrentLeader = D1 (MetaData "CurrentLeader" "Raft.Types" "libraft-0.5.0.0-J9sQlo4v2xjSwCkwompQR" False) (C1 (MetaCons "CurrentLeader" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 LeaderId)) :+: C1 (MetaCons "NoLeader" PrefixI False) (U1 :: Type -> Type))

data Mode Source #

Constructors

Follower 
Candidate 
Leader 
Instances
Read Mode Source # 
Instance details

Defined in Raft.Types

Show Mode Source # 
Instance details

Defined in Raft.Types

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

newtype Term Source #

Representation of monotonic election terms

Constructors

Term Natural 
Instances
Enum Term Source # 
Instance details

Defined in Raft.Types

Methods

succ :: Term -> Term #

pred :: Term -> Term #

toEnum :: Int -> Term #

fromEnum :: Term -> Int #

enumFrom :: Term -> [Term] #

enumFromThen :: Term -> Term -> [Term] #

enumFromTo :: Term -> Term -> [Term] #

enumFromThenTo :: Term -> Term -> Term -> [Term] #

Eq Term Source # 
Instance details

Defined in Raft.Types

Methods

(==) :: Term -> Term -> Bool #

(/=) :: Term -> Term -> Bool #

Ord Term Source # 
Instance details

Defined in Raft.Types

Methods

compare :: Term -> Term -> Ordering #

(<) :: Term -> Term -> Bool #

(<=) :: Term -> Term -> Bool #

(>) :: Term -> Term -> Bool #

(>=) :: Term -> Term -> Bool #

max :: Term -> Term -> Term #

min :: Term -> Term -> Term #

Show Term Source # 
Instance details

Defined in Raft.Types

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

Generic Term Source # 
Instance details

Defined in Raft.Types

Associated Types

type Rep Term :: Type -> Type #

Methods

from :: Term -> Rep Term x #

to :: Rep Term x -> Term #

Serialize Term Source # 
Instance details

Defined in Raft.Types

Methods

put :: Putter Term #

get :: Get Term #

FromField Term Source # 
Instance details

Defined in Raft.Types

ToField Term Source # 
Instance details

Defined in Raft.Types

Methods

toField :: Term -> Action #

type Rep Term Source # 
Instance details

Defined in Raft.Types

type Rep Term = D1 (MetaData "Term" "Raft.Types" "libraft-0.5.0.0-J9sQlo4v2xjSwCkwompQR" True) (C1 (MetaCons "Term" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

term0 :: Term Source #

Initial term. Terms start at 0

newtype Index Source #

Representation of monotonic indices

Constructors

Index Natural 
Instances
Enum Index Source # 
Instance details

Defined in Raft.Types

Eq Index Source # 
Instance details

Defined in Raft.Types

Methods

(==) :: Index -> Index -> Bool #

(/=) :: Index -> Index -> Bool #

Integral Index Source # 
Instance details

Defined in Raft.Types

Num Index Source # 
Instance details

Defined in Raft.Types

Ord Index Source # 
Instance details

Defined in Raft.Types

Methods

compare :: Index -> Index -> Ordering #

(<) :: Index -> Index -> Bool #

(<=) :: Index -> Index -> Bool #

(>) :: Index -> Index -> Bool #

(>=) :: Index -> Index -> Bool #

max :: Index -> Index -> Index #

min :: Index -> Index -> Index #

Read Index Source # 
Instance details

Defined in Raft.Types

Real Index Source # 
Instance details

Defined in Raft.Types

Methods

toRational :: Index -> Rational #

Show Index Source # 
Instance details

Defined in Raft.Types

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Generic Index Source # 
Instance details

Defined in Raft.Types

Associated Types

type Rep Index :: Type -> Type #

Methods

from :: Index -> Rep Index x #

to :: Rep Index x -> Index #

Serialize Index Source # 
Instance details

Defined in Raft.Types

Methods

put :: Putter Index #

get :: Get Index #

FromField Index Source # 
Instance details

Defined in Raft.Types

ToField Index Source # 
Instance details

Defined in Raft.Types

Methods

toField :: Index -> Action #

type Rep Index Source # 
Instance details

Defined in Raft.Types

type Rep Index = D1 (MetaData "Index" "Raft.Types" "libraft-0.5.0.0-J9sQlo4v2xjSwCkwompQR" True) (C1 (MetaCons "Index" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))

index0 :: Index Source #

Initial index. Indeces start at 0

decrIndexWithDefault0 :: Index -> Index Source #

Decrement index. If the given index is 0, return the given index

newtype SerialNum Source #

Constructors

SerialNum Natural 
Instances
Enum SerialNum Source # 
Instance details

Defined in Raft.Types

Eq SerialNum Source # 
Instance details

Defined in Raft.Types

Num SerialNum Source # 
Instance details

Defined in Raft.Types

Ord SerialNum Source # 
Instance details

Defined in Raft.Types

Read SerialNum Source # 
Instance details

Defined in Raft.Types

Show SerialNum Source # 
Instance details

Defined in Raft.Types

Generic SerialNum Source # 
Instance details

Defined in Raft.Types

Associated Types

type Rep SerialNum :: Type -> Type #

Serialize SerialNum Source # 
Instance details

Defined in Raft.Types

type Rep SerialNum Source # 
Instance details

Defined in Raft.Types

type Rep SerialNum = D1 (MetaData "SerialNum" "Raft.Types" "libraft-0.5.0.0-J9sQlo4v2xjSwCkwompQR" True) (C1 (MetaCons "SerialNum" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Natural)))