Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype NonDet :: Effect where
- newtype Cull :: Effect where
- data Cut :: Effect where
- type Logic = Bundle '[NonDet, Cull, Cut, Split]
- type NonDetThreads = Threads ListT
- newtype LogicC m a = LogicC {}
- data CullOrCall
- newtype CullCutC m a = CullCutC {
- unCullCutC :: ListT m a
- newtype NonDetC m a = NonDetC {}
- runNonDet :: forall f m a p. (Alternative f, Carrier m, Threaders '[NonDetThreads] m p) => NonDetC m a -> m (f a)
- runNonDet1 :: forall m a p. (Carrier m, Threaders '[NonDetThreads] m p) => NonDetC m a -> m (Maybe a)
- runCullCut :: forall f m a p. (Alternative f, Carrier m, Threaders '[NonDetThreads] m p) => CullCutC m a -> m (f a)
- runLogic :: forall f m a p. (Alternative f, Carrier m, Threaders '[NonDetThreads] m p) => LogicC m a -> m (f a)
Documentation
data Cut :: Effect where Source #
An effect to delimit backtracking within nondeterministic contexts.
type NonDetThreads = Threads ListT Source #
NonDetThreads
accepts the following primitive effects:
Regional
s
Optional
s
(whens
is a functor)Unravel
p
ListenPrim
o
(wheno
is aMonoid
)WriterPrim
o
(wheno
is aMonoid
)ReaderPrim
i
Instances
MonadTrans LogicC Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadBase b m => MonadBase b (LogicC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
Monad (LogicC m) Source # | |
Functor (LogicC m) Source # | |
MonadFail m => MonadFail (LogicC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
Applicative (LogicC m) Source # | |
MonadIO m => MonadIO (LogicC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadThrow m => MonadThrow (LogicC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadCatch m => MonadCatch (LogicC m) Source # | |
(Carrier m, Threads ListT (Prims m)) => Carrier (LogicC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
type Derivs (LogicC m) Source # | |
type Prims (LogicC m) Source # | |
Defined in Control.Effect.Internal.NonDet |
data CullOrCall Source #
CullCutC | |
|
Instances
MonadTrans CullCutC Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadBase b m => MonadBase b (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
Monad (CullCutC m) Source # | |
Functor (CullCutC m) Source # | |
MonadFail m => MonadFail (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
Applicative (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadIO m => MonadIO (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadThrow m => MonadThrow (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadCatch m => MonadCatch (CullCutC m) Source # | |
(Carrier m, Threads ListT (Prims m)) => Carrier (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
type Derivs (CullCutC m) Source # | |
type Prims (CullCutC m) Source # | |
Defined in Control.Effect.Internal.NonDet |
Instances
MonadTrans NonDetC Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadBase b m => MonadBase b (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
Monad (NonDetC m) Source # | |
Functor (NonDetC m) Source # | |
MonadFail m => MonadFail (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
Applicative (NonDetC m) Source # | |
MonadIO m => MonadIO (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadThrow m => MonadThrow (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
MonadCatch m => MonadCatch (NonDetC m) Source # | |
(Carrier m, Threads ListT (Prims m)) => Carrier (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
type Derivs (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet | |
type Prims (NonDetC m) Source # | |
Defined in Control.Effect.Internal.NonDet |
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
or runCullCut
@Maybe . cull
, but doesn't impose
any primitive effects, meaning runLogic
@Maybe . cull
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.