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

Data.Effect.Unlift

Description

Realizes unliftio in the form of higher-order effects.

Documentation

pattern WithRunInIO :: ((f ~> IO) -> IO a) -> UnliftIO f a Source #

withRunInIO :: forall es ff a c. (UnliftIO :> es, Free c ff) => ((Eff ff es ~> IO) -> IO a) -> Eff ff es a Source #

withRunInBase :: forall (b :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (UnliftBase b) es) => ((forall (x :: Type). f x -> b x) -> b a) -> f a Source #

runUnliftBase :: forall b ff a c. (c b, Free c ff) => Eff ff '[UnliftBase b, Emb b] a -> b a Source #

runUnliftIO :: (MonadUnliftIO m, Free c ff, c m) => Eff ff '[UnliftIO, Emb m] a -> m a Source #

withRunInBase' :: forall key (b :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, Has key (UnliftBase b) es) => ((forall (x :: Type). f x -> b x) -> b a) -> f a Source #

withRunInBase'' :: forall tag (b :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, (:>) (Tagged tag (UnliftBase b)) es) => ((forall (x :: Type). f x -> b x) -> b a) -> f a Source #

withRunInBase'_ :: forall (b :: Type -> Type) (a :: Type) f es ff c. (Free c ff, f ~ Eff ff es, In (UnliftBase b) es) => ((forall (x :: Type). f x -> b x) -> b a) -> f a Source #

data UnliftBase (b :: Type -> Type) (f :: Type -> Type) a where #

Constructors

WithRunInBase :: forall (f :: Type -> Type) (b :: Type -> Type) a. ((forall x. f x -> b x) -> b a) -> UnliftBase b f a 

Instances

Instances details
HFunctor (UnliftBase b) 
Instance details

Defined in Data.Effect

Methods

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

type LabelOf (UnliftBase b) 
Instance details

Defined in Data.Effect

type OrderOf (UnliftBase b) 
Instance details

Defined in Data.Effect