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

Data.Effect.NonDet

Description

Effects that realize non-deterministic computations.

Synopsis

Documentation

empty :: forall b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Empty :> es) => a b Source #

choice :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Choose :> es, Empty :> es, Monad (Eff ff es), Free c ff) => [a] -> Eff ff es a Source #

Selects one element from the list nondeterministically, branching the control as many times as the number of elements.

choose :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Choose :> es) => a Bool Source #

runChooseH :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Choose :> es, Monad (Eff ff es), Free c ff) => Eff ff (ChooseH ': es) a -> Eff ff es a Source #

ChooseH effect elaborator.

Convert a higher-order effect of the form

chooseH :: m a -> m a -> m a

into a first-order effect of the form:

choose :: m Bool

branch :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Choose :> es, Monad (Eff ff es), Free c ff) => Eff ff es a -> Eff ff es a -> Eff ff es a infixl 3 Source #

Faster than <|>.

choiceH :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (ChooseH :> es, Empty :> es, Monad (Eff ff es), Free c ff) => [a] -> Eff ff es a Source #

Selects one element from the list nondeterministically, branching the control as many times as the number of elements. Uses ChooseH.

runNonDetShift :: forall ans a (es :: [Effect]) (ref :: Type -> Type) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Monoid ans, Shift ans ref :> es, forall (f :: Type -> Type). Monad (ff f), Free c ff) => Eff ff (Choose ': (Empty ': es)) a -> Eff ff es a Source #

runNonDetIO :: forall (es :: [Effect]) a (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (UnliftIO :> es, Emb IO :> es, forall (f :: [Effect]). Monad (Eff ff f), Free c ff) => Eff ff (ChooseH ': (Empty ': es)) a -> Eff ff es (Either SomeException a) Source #

Interprets the NonDet effects using IO-level exceptions.

When empty occurs, an EmptyException is thrown, and unless all branches from chooseH fail due to IO-level exceptions, only the leftmost result is returned as the final result.

empty' :: 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 Empty es) => a b Source #

empty'' :: 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 Empty :> es) => a b Source #

empty'_ :: forall b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In Empty es) => a b Source #

choose' :: forall {k} (key :: k) a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Has key Choose es) => a Bool Source #

choose'' :: forall {k} (tag :: k) a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, Tagged tag Choose :> es) => a Bool Source #

choose'_ :: forall a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In Choose es) => a Bool Source #

chooseH :: forall b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, ChooseH :> es) => a b -> a b -> a b Source #

chooseH' :: 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 ChooseH es) => a b -> a b -> a b Source #

chooseH'' :: 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 ChooseH :> es) => a b -> a b -> a b Source #

chooseH'_ :: forall b a (es :: [Effect]) (ff :: (Type -> Type) -> Type -> Type) (c :: (Type -> Type) -> Constraint). (Free c ff, a ~ Eff ff es, In ChooseH es) => a b -> a b -> a b Source #

data Empty (a :: Type -> Type) b where #

An effect that eliminates a branch by causing the current branch context of a non-deterministic computation to fail.

Constructors

Empty :: forall (a :: Type -> Type) b. Empty a b

Eliminates a branch by causing the current branch context of a non-deterministic computation to fail.

Instances

Instances details
FirstOrder Empty 
Instance details

Defined in Data.Effect

PolyHFunctor Empty 
Instance details

Defined in Data.Effect

HFunctor Empty 
Instance details

Defined in Data.Effect

Methods

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

type FormOf Empty 
Instance details

Defined in Data.Effect

type LabelOf Empty 
Instance details

Defined in Data.Effect

type OrderOf Empty 
Instance details

Defined in Data.Effect

data Choose (a :: Type -> Type) b where #

An effect that splits the computation into two branches.

Constructors

Choose :: forall (a :: Type -> Type). Choose a Bool

Splits the computation into two branches. As a result of executing choose, the world branches into one where False is returned and one where True is returned.

Instances

Instances details
FirstOrder Choose 
Instance details

Defined in Data.Effect

PolyHFunctor Choose 
Instance details

Defined in Data.Effect

HFunctor Choose 
Instance details

Defined in Data.Effect

Methods

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

type FormOf Choose 
Instance details

Defined in Data.Effect

type LabelOf Choose 
Instance details

Defined in Data.Effect

type OrderOf Choose 
Instance details

Defined in Data.Effect

data ChooseH (a :: Type -> Type) b where #

An effect that executes two branches as scopes. A higher-order version of the Choose effect.

Constructors

ChooseH :: forall (a :: Type -> Type) b. a b -> a b -> ChooseH a b

Executes the given two scopes as branches. Even if one fails due to the empty operation, the whole does not fail as long as the other does not fail.

Instances

Instances details
PolyHFunctor ChooseH 
Instance details

Defined in Data.Effect

HFunctor ChooseH 
Instance details

Defined in Data.Effect

Methods

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

type FormOf ChooseH 
Instance details

Defined in Data.Effect

type LabelOf ChooseH 
Instance details

Defined in Data.Effect

type OrderOf ChooseH 
Instance details

Defined in Data.Effect