Safe Haskell | None |
---|---|
Language | Haskell2010 |
TypedSession.State.Pipeline
Documentation
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 #
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 #
data PipeResult r bst Source #
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 #