typed-session-state-algorithm-0.3.0.1: Automatically generate status for typed-session.
Safe HaskellNone
LanguageHaskell2010

TypedSession.State.Pipeline

Documentation

newtype Index Source #

Constructors

Index Int 

Instances

Instances details
Num Index Source # 
Instance details

Defined in TypedSession.State.Pipeline

Show Index Source # 
Instance details

Defined in TypedSession.State.Pipeline

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Eq Index Source # 
Instance details

Defined in TypedSession.State.Pipeline

Methods

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

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

Ord Index Source # 
Instance details

Defined in TypedSession.State.Pipeline

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 #

addIdxXTraverse :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (State Int :+: (State Index :+: (State (Set Int) :+: Error (ProtocolError r bst)))) sig m, Enum r, Bounded r, Ord r) => XTraverse m Creat Idx r bst Source #

addNumsXTraverse :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (Error (ProtocolError r bst)) sig m, Enum r, Bounded r, Ord r) => XTraverse m Idx AddNums r bst Source #

data CurrSt Source #

Constructors

Decide 
Undecide 

Instances

Instances details
Show CurrSt Source # 
Instance details

Defined in TypedSession.State.Pipeline

Eq CurrSt Source # 
Instance details

Defined in TypedSession.State.Pipeline

Methods

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

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

Ord CurrSt Source # 
Instance details

Defined in TypedSession.State.Pipeline

getRCurrSt :: forall r (sig :: (Type -> Type) -> Type -> Type) m. (Has (State (Map r CurrSt)) sig m, Ord r) => r -> m CurrSt Source #

restoreWrapper1 :: forall r (sig :: (Type -> Type) -> Type -> Type) m a. Has (State (Map r CurrSt) :+: State r) sig m => m a -> m a Source #

checkProtXFold :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (State (Map r CurrSt) :+: (State r :+: Error (ProtocolError r bst))) sig m, Eq r, Ord r, Enum r, Bounded r) => XFold m (GenConst r) r bst Source #

genConstrXFold :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (State (IntMap [Int]) :+: (State [Int] :+: (Writer (Seq Constraint) :+: Error (ProtocolError r bst)))) sig m, Enum r) => XFold m (GenConst r) r bst Source #

verifyProtXFold :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (State (IntMap (r, r)) :+: Error (ProtocolError r bst)) sig m, Enum r, Eq r) => XFold m (GenConst r) r bst Source #

collectBranchDynValXFold :: forall (sig :: (Type -> Type) -> Type -> Type) m r bst. (Has (State (Set Int)) sig m, Enum r) => XFold m (GenConst r) r bst Source #

genT :: forall bst (sig :: (Type -> Type) -> Type -> Type) m. Has (Reader (Set Int) :+: State bst) sig m => (bst -> Int -> T bst) -> Int -> m (T bst) Source #

genMsgTXTraverse :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (Reader (Set Int) :+: State bst) sig m, Enum r, Eq r, Bounded r) => XTraverse m (GenConst r) (MsgT r bst) r bst Source #

getFirstXV :: Protocol (MsgT r bst) r bst -> [T bst] Source #

genMsgT1XTraverse :: (Monad m, Enum r) => XTraverse m (MsgT r bst) (MsgT1 r bst) r bst Source #

data PipeResult r bst Source #

Constructors

PipeResult 

Fields

pipe' :: forall r bst (sig :: (Type -> Type) -> Type -> Type) m. (Has (Error (ProtocolError r bst)) sig m, Enum r, Bounded r, Eq r, Ord r) => (Tracer r bst -> m ()) -> Protocol Creat r bst -> m (PipeResult r bst) Source #

pipe :: (Enum r, Bounded r, Eq r, Ord r) => Protocol Creat r bst -> Either (ProtocolError r bst) (PipeResult r bst) Source #

pipeWithTracer :: (Enum r, Bounded r, Eq r, Ord r) => Protocol Creat r bst -> (Seq (Tracer r bst), Either (ProtocolError r bst) (PipeResult r bst)) Source #

genGraph :: (Enum r, Bounded r, Show bst, Ord r, Show r) => PipeResult r bst -> String Source #