libraft-0.1.1.0: Raft consensus algorithm

Safe HaskellNone
LanguageHaskell2010

Raft.Log

Synopsis

Documentation

data EntryIssuer Source #

Instances
Show EntryIssuer Source # 
Instance details

Defined in Raft.Log

Generic EntryIssuer Source # 
Instance details

Defined in Raft.Log

Associated Types

type Rep EntryIssuer :: Type -> Type #

Serialize EntryIssuer Source # 
Instance details

Defined in Raft.Log

type Rep EntryIssuer Source # 
Instance details

Defined in Raft.Log

data EntryValue v Source #

Constructors

EntryValue v 
NoValue

Used as a first committed entry of a new term

Instances
Show v => Show (EntryValue v) Source # 
Instance details

Defined in Raft.Log

Generic (EntryValue v) Source # 
Instance details

Defined in Raft.Log

Associated Types

type Rep (EntryValue v) :: Type -> Type #

Methods

from :: EntryValue v -> Rep (EntryValue v) x #

to :: Rep (EntryValue v) x -> EntryValue v #

Serialize v => Serialize (EntryValue v) Source # 
Instance details

Defined in Raft.Log

Methods

put :: Putter (EntryValue v) #

get :: Get (EntryValue v) #

type Rep (EntryValue v) Source # 
Instance details

Defined in Raft.Log

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

data Entry v Source #

Representation of an entry in the replicated log

Constructors

Entry 

Fields

Instances
Show v => Show (Entry v) Source # 
Instance details

Defined in Raft.Log

Methods

showsPrec :: Int -> Entry v -> ShowS #

show :: Entry v -> String #

showList :: [Entry v] -> ShowS #

Generic (Entry v) Source # 
Instance details

Defined in Raft.Log

Associated Types

type Rep (Entry v) :: Type -> Type #

Methods

from :: Entry v -> Rep (Entry v) x #

to :: Rep (Entry v) x -> Entry v #

Serialize v => Serialize (Entry v) Source # 
Instance details

Defined in Raft.Log

Methods

put :: Putter (Entry v) #

get :: Get (Entry v) #

type Rep (Entry v) Source # 
Instance details

Defined in Raft.Log

type Entries v = Seq (Entry v) Source #

class Monad m => RaftWriteLog m v where Source #

Provides an interface for nodes to write log entries to storage.

Associated Types

type RaftWriteLogError m Source #

Methods

writeLogEntries :: Exception (RaftWriteLogError m) => Entries v -> m (Either (RaftWriteLogError m) ()) Source #

Write the given log entries to storage

data DeleteSuccess v Source #

Constructors

DeleteSuccess 

class Monad m => RaftDeleteLog m v where Source #

Provides an interface for nodes to delete log entries from storage.

Associated Types

type RaftDeleteLogError m Source #

Methods

deleteLogEntriesFrom :: Exception (RaftDeleteLogError m) => Index -> m (Either (RaftDeleteLogError m) (DeleteSuccess v)) Source #

Delete log entries from a given index; e.g. 'deleteLogEntriesFrom 7' should delete every log entry with an index >= 7.

class Monad m => RaftReadLog m v where Source #

Provides an interface for nodes to read log entries from storage.

Minimal complete definition

readLogEntry, readLastLogEntry

Associated Types

type RaftReadLogError m Source #

Methods

readLogEntry :: Exception (RaftReadLogError m) => Index -> m (Either (RaftReadLogError m) (Maybe (Entry v))) Source #

Read the log at a given index

readLogEntriesFrom :: Exception (RaftReadLogError m) => Index -> m (Either (RaftReadLogError m) (Entries v)) Source #

Read log entries from a specific index onwards, including the specific index

readLastLogEntry :: Exception (RaftReadLogError m) => m (Either (RaftReadLogError m) (Maybe (Entry v))) Source #

Read the last log entry in the log

readLogEntriesFrom :: Exception (RaftReadLogError m) => Index -> m (Either (RaftReadLogError m) (Entries v)) Source #

Read log entries from a specific index onwards, including the specific index

data RaftLogError m Source #

Representation of possible errors that come from reading, writing or deleting logs from the persistent storage