data-effects-0.4.2.0: A basic framework for effect systems based on effects represented by GADTs.
Copyright(c) 2025 Sayo contributors
LicenseMPL-2.0 (see the file LICENSE)
Maintainerymdfield@outlook.jp
Safe HaskellNone
LanguageGHC2021

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 #

Constructors

Fail :: forall (a :: Type -> Type) b. String -> Fail a b 

Instances

Instances details
FirstOrder Fail 
Instance details

Defined in Data.Effect

PolyHFunctor Fail 
Instance details

Defined in Data.Effect

HFunctor Fail 
Instance details

Defined in Data.Effect

Methods

hfmap :: (forall x. f x -> g x) -> Fail f a -> Fail g a #

type FormOf Fail 
Instance details

Defined in Data.Effect

type LabelOf Fail 
Instance details

Defined in Data.Effect

type OrderOf Fail 
Instance details

Defined in Data.Effect