in-other-words-0.2.0.0: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Effect.Internal.NonDet

Synopsis

Documentation

newtype NonDet :: Effect where Source #

An effect for nondeterministic computations

Constructors

FromList :: [a] -> NonDet m a 

newtype Cull :: Effect where Source #

An effect for culling nondeterministic computations.

Constructors

Cull :: m a -> Cull m a 

data Cut :: Effect where Source #

An effect to delimit backtracking within nondeterministic contexts.

Constructors

Cutfail :: Cut m a 
Call :: m a -> Cut m a 

type Logic = Bundle '[NonDet, Cull, Cut, Split] Source #

A pseudo-effect for connected NonDet, Cull, Cut, and Split effects.

Logic should only ever be used inside of Eff and Effs constraints. It is not a real effect! See Bundle.

type NonDetThreads = Threads ListT Source #

NonDetThreads accepts the following primitive effects:

newtype LogicC m a Source #

Constructors

LogicC 

Fields

Instances

Instances details
MonadTrans LogicC Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

MonadBase b m => MonadBase b (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

liftBase :: b α -> LogicC m α #

Monad (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

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

return :: a -> LogicC m a #

Functor (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

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

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

Defined in Control.Effect.Internal.NonDet

Methods

fail :: String -> LogicC m a #

Applicative (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

pure :: a -> LogicC m a #

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

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

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

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

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

Defined in Control.Effect.Internal.NonDet

Methods

liftIO :: IO a -> LogicC m a #

MonadThrow m => MonadThrow (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

throwM :: Exception e => e -> LogicC m a #

MonadCatch m => MonadCatch (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

catch :: Exception e => LogicC m a -> (e -> LogicC m a) -> LogicC m a #

(Carrier m, Threads ListT (Prims m)) => Carrier (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Associated Types

type Derivs (LogicC m) :: [Effect] Source #

type Prims (LogicC m) :: [Effect] Source #

type Derivs (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

type Derivs (LogicC m) = Split ': (Cull ': (Cut ': (NonDet ': Derivs m)))
type Prims (LogicC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

type Prims (LogicC m) = Split ': (Regional CullOrCall ': Prims m)

data CullOrCall Source #

Constructors

DoCull 
DoCall 

newtype CullCutC m a Source #

Constructors

CullCutC 

Fields

Instances

Instances details
MonadTrans CullCutC Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

MonadBase b m => MonadBase b (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

liftBase :: b α -> CullCutC m α #

Monad (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

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

return :: a -> CullCutC m a #

Functor (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

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

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

Defined in Control.Effect.Internal.NonDet

Methods

fail :: String -> CullCutC m a #

Applicative (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

pure :: a -> CullCutC m a #

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

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

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

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

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

Defined in Control.Effect.Internal.NonDet

Methods

liftIO :: IO a -> CullCutC m a #

MonadThrow m => MonadThrow (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

throwM :: Exception e => e -> CullCutC m a #

MonadCatch m => MonadCatch (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

catch :: Exception e => CullCutC m a -> (e -> CullCutC m a) -> CullCutC m a #

(Carrier m, Threads ListT (Prims m)) => Carrier (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Associated Types

type Derivs (CullCutC m) :: [Effect] Source #

type Prims (CullCutC m) :: [Effect] Source #

type Derivs (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

type Derivs (CullCutC m) = Cull ': (Cut ': (NonDet ': Derivs m))
type Prims (CullCutC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

newtype NonDetC m a Source #

Constructors

NonDetC 

Fields

Instances

Instances details
MonadTrans NonDetC Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

MonadBase b m => MonadBase b (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

liftBase :: b α -> NonDetC m α #

Monad (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

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 #

Functor (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Methods

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

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

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

Defined in Control.Effect.Internal.NonDet

Methods

fail :: String -> NonDetC m a #

Applicative (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

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 #

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

Defined in Control.Effect.Internal.NonDet

Methods

liftIO :: IO a -> NonDetC m a #

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

Defined in Control.Effect.Internal.NonDet

Methods

throwM :: Exception e => e -> NonDetC m a #

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

Defined in Control.Effect.Internal.NonDet

Methods

catch :: Exception e => NonDetC m a -> (e -> NonDetC m a) -> NonDetC m a #

(Carrier m, Threads ListT (Prims m)) => Carrier (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

Associated Types

type Derivs (NonDetC m) :: [Effect] Source #

type Prims (NonDetC m) :: [Effect] Source #

type Derivs (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

type Derivs (NonDetC m) = NonDet ': Derivs m
type Prims (NonDetC m) Source # 
Instance details

Defined in Control.Effect.Internal.NonDet

type Prims (NonDetC m) = Prims m

runNonDet :: forall f m a p. (Alternative f, Carrier m, Threaders '[NonDetThreads] m p) => NonDetC m a -> m (f a) Source #

Runs a NonDet effect.

Unlike runLogic and runCullCut, this doesn't provide any means of interacting with created branches through Split, Cull or Cut.

However, it also doesn't impose any primitive effects, meaning runNonDet doesn't restrict what interpreters are run before it.

Derivs (NonDetC m) = NonDet ': Derivs m
Prims  (NonDetC m) = Prims m

runNonDet1 :: forall m a p. (Carrier m, Threaders '[NonDetThreads] m p) => NonDetC m a -> m (Maybe a) Source #

Runs a NonDet effect, but stop once the first valid result is found.

This is like runNonDet with the Alternative specialized to Maybe, but once a valid result is found, it won't run all other branches.

This is the equivalent of runCullCut @Maybe . cull or runLogic @Maybe . cull, but doesn't impose any primitive effects, meaning runNonDet1 doesn't restrict what interpreters are run before it.

Derivs (NonDetC m) = NonDet ': Derivs m
Prims  (NonDetC m) = Prims m

runCullCut :: forall f m a p. (Alternative f, Carrier m, Threaders '[NonDetThreads] m p) => CullCutC m a -> m (f a) Source #

Runs connected NonDet, Cull, and Cut effects.

Unlike runLogic, this doesn't provide the full power of Split. This allows for a larger variety of interpreters to be run before runCullCut compared to runLogic, since Split is significantly harder to thread compared to Cull and Cut.

Derivs (CullCutC m) = Cull ': Cut ': NonDet ': Derivs m
Prims  (CullCutC m) = Regional CullOrCall ': Prims m

runLogic :: forall f m a p. (Alternative f, Carrier m, Threaders '[NonDetThreads] m p) => LogicC m a -> m (f a) Source #

Runs connected NonDet, Cull, Cut, and Split effects -- i.e. Logic.

Derivs (LogicC m) = Split ': Cull ': Cut ': NonDet ': Derivs m
Prims  (LogicC m) = Split ': Regional CullOrCall ': Prims m

Split is a very restrictive primitive effect. Most notably, interpreters for effects with failure -- such as runError -- can't be used before runLogic. If you want to use such interpreters before runLogic, consider using runCullCut or runNonDet instead.