Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Data.Effect.Chronicle
Documentation
data ChronicleF c a where Source #
Constructors
Dictate :: c -> ChronicleF c () | |
Confess :: c -> ChronicleF c a |
data ChronicleH c f a where Source #
Constructors
Memento :: f a -> ChronicleH c f (Either c a) | |
Absolve :: a -> f a -> ChronicleH c f a | |
Condemn :: f a -> ChronicleH c f a |
Instances
() => HFunctor (ChronicleH c) Source # | |
Defined in Data.Effect.Chronicle Methods hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> ChronicleH c f :-> ChronicleH c g # |
type LChronicleF c = LiftIns (ChronicleF c) Source #
condemn'' :: forall key (a :: Type) (c :: Type) f. SendSigBy key (ChronicleH c) f => f a -> f a Source #
condemn' :: forall tag (a :: Type) (c :: Type) f. SendSig (TagH (ChronicleH c) tag) f => f a -> f a Source #
absolve'' :: forall key (a :: Type) (c :: Type) f. SendSigBy key (ChronicleH c) f => a -> f a -> f a Source #
absolve' :: forall tag (a :: Type) (c :: Type) f. SendSig (TagH (ChronicleH c) tag) f => a -> f a -> f a Source #
memento'' :: forall key (a :: Type) (c :: Type) f. SendSigBy key (ChronicleH c) f => f a -> f (Either c a) Source #
memento' :: forall tag (a :: Type) (c :: Type) f. SendSig (TagH (ChronicleH c) tag) f => f a -> f (Either c a) Source #
memento :: forall (a :: Type) (c :: Type) f. SendSig (ChronicleH c) f => f a -> f (Either c a) Source #
pattern LConfess :: () => (a ~ a, ()) => c -> LiftIns (ChronicleF c) f a Source #
pattern LDictate :: () => (a ~ (), ()) => c -> LiftIns (ChronicleF c) f a Source #
confess'' :: forall key (c :: Type) (a :: Type) f. SendInsBy key (ChronicleF c) f => c -> f a Source #
confess' :: forall tag (c :: Type) (a :: Type) f. SendIns (Tag (ChronicleF c) tag) f => c -> f a Source #
chronicle :: (ChronicleF c <: f, Applicative f) => These c a -> f a Source #