Copyright | (c) 2025 Sayo contributors |
---|---|
License | MPL-2.0 (see the file LICENSE) |
Maintainer | ymdfield@outlook.jp |
Safe Haskell | None |
Language | GHC2021 |
Data.Effect.Fail
Description
Documentation
fail :: forall b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Fail :> es) => String -> a b Source #
runFailIO :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Emb IO :> es, Monad (Eff ff es), Free c ff) => Eff ff (Fail ': es) a -> Eff ff es a Source #
fail' :: forall {k} (key :: k) b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key Fail es) => String -> a b Source #
fail'' :: forall {k} (tag :: k) b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag Fail :> es) => String -> a b Source #
fail'_ :: forall b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In Fail es) => String -> a b Source #
data Fail (a :: Type -> Type) b where #
Instances
FirstOrder Fail | |
Defined in Data.Effect | |
PolyHFunctor Fail | |
Defined in Data.Effect | |
HFunctor Fail | |
Defined in Data.Effect | |
type FormOf Fail | |
Defined in Data.Effect | |
type LabelOf Fail | |
Defined in Data.Effect | |
type OrderOf Fail | |
Defined in Data.Effect |