fused-effects-1.1.1.3: A fast, flexible, fused effect system.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Carrier.NonDet.Church

Description

Provides NonDetC, a carrier for NonDet effects providing choice and failure.

Under the hood, it uses a Church-encoded structure and a binary tree to prevent the problems associated with a naïve list-based implementation.

Since: 1.0.0.0

Synopsis

NonDet carrier

runNonDet Source #

Arguments

:: (m b -> m b -> m b)

Handles choice (<|>)

-> (a -> m b)

Handles embedding results (pure)

-> m b

Handles failure (empty)

-> NonDetC m a

A nondeterministic computation to execute

-> m b 

Run a NonDet effect, using the provided functions to interpret choice, leaf results, and failure.

runNonDet fork leaf nil (pure a <|> empty) = leaf a `fork` nil

Since: 1.0.0.0

runNonDetA :: (Alternative f, Applicative m) => NonDetC m a -> m (f a) Source #

Run a NonDet effect, collecting all branches’ results into an Alternative functor.

Using [] as the Alternative functor will produce all results, while Maybe will return only the first. However, unless used with cull, this will still enumerate the entire search space before returning, meaning that it will diverge for infinite search spaces, even when using Maybe.

runNonDetA (pure a) = pure [a]
runNonDetA (pure a) = pure (Just a)

Since: 1.0.0.0

runNonDetM :: (Applicative m, Monoid b) => (a -> b) -> NonDetC m a -> m b Source #

Run a NonDet effect, mapping results into a Monoid.

Since: 1.0.0.0

newtype NonDetC m a Source #

A carrier for NonDet effects based on Ralf Hinze’s design described in Deriving Backtracking Monad Transformers.

Since: 1.0.0.0

Constructors

NonDetC (forall b. (m b -> m b -> m b) -> (a -> m b) -> m b -> m b) 

Instances

Instances details
MonadTrans NonDetC Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

lift :: Monad m => m a -> NonDetC m a #

MonadFail m => MonadFail (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

fail :: String -> NonDetC m a #

MonadFix m => MonadFix (NonDetC m) Source #

Separate fixpoints are computed for each branch.

Instance details

Defined in Control.Carrier.NonDet.Church

Methods

mfix :: (a -> NonDetC m a) -> NonDetC m a #

MonadIO m => MonadIO (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

liftIO :: IO a -> NonDetC m a #

Alternative (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

empty :: NonDetC m a #

(<|>) :: NonDetC m a -> NonDetC m a -> NonDetC m a #

some :: NonDetC m a -> NonDetC m [a] #

many :: NonDetC m a -> NonDetC m [a] #

Applicative (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

pure :: a -> NonDetC m a #

(<*>) :: NonDetC m (a -> b) -> NonDetC m a -> NonDetC m b #

liftA2 :: (a -> b -> c) -> NonDetC m a -> NonDetC m b -> NonDetC m c #

(*>) :: NonDetC m a -> NonDetC m b -> NonDetC m b #

(<*) :: NonDetC m a -> NonDetC m b -> NonDetC m a #

Functor (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

fmap :: (a -> b) -> NonDetC m a -> NonDetC m b #

(<$) :: a -> NonDetC m b -> NonDetC m a #

Monad (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

(>>=) :: NonDetC m a -> (a -> NonDetC m b) -> NonDetC m b #

(>>) :: NonDetC m a -> NonDetC m b -> NonDetC m b #

return :: a -> NonDetC m a #

MonadPlus (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

mzero :: NonDetC m a #

mplus :: NonDetC m a -> NonDetC m a -> NonDetC m a #

Algebra sig m => Algebra (NonDet :+: sig) (NonDetC m) Source # 
Instance details

Defined in Control.Carrier.NonDet.Church

Methods

alg :: forall ctx (n :: Type -> Type) a. Functor ctx => Handler ctx n (NonDetC m) -> (NonDet :+: sig) n a -> ctx () -> NonDetC m (ctx a) Source #

NonDet effects