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

Data.Effect.CC

Description

 

Documentation

callCC :: forall a ref es ff c. (CC ref :> es, Monad (Eff ff es), Free c ff) => ((forall b. a -> Eff ff es b) -> Eff ff es a) -> Eff ff es a Source #

jump :: forall (ref :: Type -> Type) (a1 :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (CC ref) es) => ref a1 -> a1 -> a b Source #

getCC :: forall a ref es ff c. (CC ref :> es, Monad (Eff ff es), Free c ff) => Eff ff es (Eff ff es a) Source #

subFork :: forall (ref :: Type -> Type) (a1 :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (CC ref) es) => a (Either (ref a1) a1) Source #

subFork' :: forall key (ref :: Type -> Type) (a1 :: Type) a es ff c. (Free c ff, a ~ Eff ff es, Has key (CC ref) es) => a (Either (ref a1) a1) Source #

subFork'' :: forall tag (ref :: Type -> Type) (a1 :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Tagged tag (CC ref)) es) => a (Either (ref a1) a1) Source #

subFork'_ :: forall (ref :: Type -> Type) (a1 :: Type) a es ff c. (Free c ff, a ~ Eff ff es, In (CC ref) es) => a (Either (ref a1) a1) Source #

jump' :: forall key (ref :: Type -> Type) (a1 :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, Has key (CC ref) es) => ref a1 -> a1 -> a b Source #

jump'' :: forall tag (ref :: Type -> Type) (a1 :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, (:>) (Tagged tag (CC ref)) es) => ref a1 -> a1 -> a b Source #

jump'_ :: forall (ref :: Type -> Type) (a1 :: Type) (b :: Type) a es ff c. (Free c ff, a ~ Eff ff es, In (CC ref) es) => ref a1 -> a1 -> a b Source #

data CC (ref :: Type -> Type) (a :: Type -> Type) b where #

Constructors

SubFork :: forall (ref :: Type -> Type) (a :: Type -> Type) a1. CC ref a (Either (ref a1) a1) 
Jump :: forall (ref :: Type -> Type) a1 (a :: Type -> Type) b. ref a1 -> a1 -> CC ref a b 

Instances

Instances details
FirstOrder (CC ref) 
Instance details

Defined in Data.Effect

HFunctor (CC ref) 
Instance details

Defined in Data.Effect

Methods

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

type LabelOf (CC ref) 
Instance details

Defined in Data.Effect

type LabelOf (CC ref) = CCLabel
type OrderOf (CC ref) 
Instance details

Defined in Data.Effect

type OrderOf (CC ref) = 'FirstOrder

callCC_ :: forall (ref :: Type -> Type) a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => ((a -> Eff ff es b) -> Eff ff es a) -> Eff ff es a #

sub :: forall ref a b (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (CC ref :> es, Monad (Eff ff es), Free c ff) => (ref a -> Eff ff es b) -> (a -> Eff ff es b) -> Eff ff es b #