Copyright | (c) Eamon Olive 2020 (c) Louis Hyde 2020 |
---|---|
License | AGPL-3 |
Maintainer | ejolive97@gmail.com |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data ChoiceT f m a
- runChoiceT :: Monad m => (forall x. f x -> m x) -> ChoiceT f m a -> m a
- mapChoiceT :: (forall x. m x -> n x) -> ChoiceT f m a -> ChoiceT f n a
- runBacktrackableChoiceT :: forall f m a. Monad m => (forall x. f x -> m (Maybe x)) -> ChoiceT f m a -> m (Maybe a)
Documentation
Instances
MonadRWS r w s m => MonadRWS r w s (ChoiceT f m) Source # | |
Defined in Control.Monad.Trans.Choice.Covariant | |
MonadWriter w m => MonadWriter w (ChoiceT f m) Source # | |
MonadState s m => MonadState s (ChoiceT f m) Source # | |
MonadReader r m => MonadReader r (ChoiceT f m) Source # | |
MonadChoice f (ChoiceT f m) Source # | |
Defined in Control.Monad.Trans.Choice.Covariant | |
MonadTrans (ChoiceT f) Source # | |
Defined in Control.Monad.Trans.Choice.Covariant | |
Monad (ChoiceT f m) Source # | |
Functor (ChoiceT f m) Source # | |
Applicative (ChoiceT f m) Source # | |
Defined in Control.Monad.Trans.Choice.Covariant | |
MonadIO m => MonadIO (ChoiceT f m) Source # | |
Defined in Control.Monad.Trans.Choice.Covariant |
runChoiceT :: Monad m => (forall x. f x -> m x) -> ChoiceT f m a -> m a Source #
mapChoiceT :: (forall x. m x -> n x) -> ChoiceT f m a -> ChoiceT f n a Source #
runBacktrackableChoiceT Source #
:: Monad m | |
=> (forall x. f x -> m (Maybe x)) | The selection function.
If the result of the outputted computation is |
-> ChoiceT f m a | The choice structure to run |
-> m (Maybe a) | The resulting computation. If the selection function backtracks on the
first choice the result of the computation will be |
A variant of runChoiceT
that allows for the selection function to
output Nothing
to represent the desire to potentially select a different
option for the previous choice.