Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control.Effects.List
Description
Add non-determinism to your monad. Uses the ListT
transformer under the hood.
Synopsis
- newtype NonDeterminism m = NonDeterminismMethods {
- _choose :: forall a. [a] -> m a
- choose :: forall a m. MonadEffect NonDeterminism m => [a] -> m a
- deadEnd :: MonadEffect NonDeterminism m => m a
- evaluateToList :: Monad m => ListT m a -> m [a]
- traverseAllResults :: Monad m => (a -> m ()) -> ListT m a -> m ()
- foldAllResults :: Monad m => (r -> a -> m r) -> r -> ListT m a -> m r
- foldWithEarlyTermination :: Monad m => (r -> a -> m (Maybe r)) -> r -> ListT m a -> m r
- evaluateNResults :: Monad m => Int -> ListT m a -> m [a]
- evaluateOneResult :: Monad m => ListT m a -> m (Maybe a)
- evaluateAll :: Monad m => ListT m a -> m ()
- slice :: Monad m => Int -> ListT m a -> ListT m [a]
- drop :: Monad m => Int -> ListT m a -> ListT m a
- traverse :: Monad m => (a -> m b) -> ListT m a -> ListT m b
- repeat :: Monad m => a -> ListT m a
- unfoldM :: Monad m => (b -> m (Maybe (a, b))) -> b -> ListT m a
- unfold :: Monad m => (b -> Maybe (a, b)) -> b -> ListT m a
- fromMVar :: MonadIO m => MVar (Maybe a) -> ListT m a
- fromFoldable :: (Monad m, Foldable f) => f a -> ListT m a
- cons :: Monad m => a -> ListT m a -> ListT m a
- splitAt :: Monad m => Int -> ListT m a -> m ([a], ListT m a)
- traverse_ :: Monad m => (a -> m ()) -> ListT m a -> m ()
- toReverseList :: Monad m => ListT m a -> m [a]
- toList :: Monad m => ListT m a -> m [a]
- foldMaybe :: Monad m => (r -> a -> m (Maybe r)) -> r -> ListT m a -> m r
- fold :: Monad m => (r -> a -> m r) -> r -> ListT m a -> m r
- null :: Monad m => ListT m a -> m Bool
- tail :: Monad m => ListT m a -> m (Maybe (ListT m a))
- head :: Monad m => ListT m a -> m (Maybe a)
- uncons :: ListT m a -> m (Maybe (a, ListT m a))
- newtype ListT (m :: Type -> Type) a = ListT (m (Maybe (a, ListT m a)))
Documentation
newtype NonDeterminism m Source #
Constructors
NonDeterminismMethods | |
Fields
|
Instances
Effect NonDeterminism Source # | |
Defined in Control.Effects.List Associated Types type CanLift NonDeterminism t :: Constraint Source # type ExtraConstraint NonDeterminism m :: Constraint Source # Methods liftThrough :: (CanLift NonDeterminism t, Monad m, Monad (t m)) => NonDeterminism m -> NonDeterminism (t m) Source # mergeContext :: Monad m => m (NonDeterminism m) -> NonDeterminism m Source # | |
Monad m => MonadEffect NonDeterminism (ListT m) Source # | |
Defined in Control.Effects.List Methods effect :: NonDeterminism (ListT m) Source # | |
type CanLift NonDeterminism t Source # | |
Defined in Control.Effects.List | |
type ExtraConstraint NonDeterminism m Source # | |
Defined in Control.Effects.List |
choose :: forall a m. MonadEffect NonDeterminism m => [a] -> m a Source #
Get a value from the list. The choice of which value to take is non-deterministic in a sense that the rest of the computation will be ran once for each of them.
deadEnd :: MonadEffect NonDeterminism m => m a Source #
Signals that this branch of execution failed to produce a result.
evaluateToList :: Monad m => ListT m a -> m [a] Source #
Execute all the effects and collect the result in a list. Note that this forces all the results, no matter which elements of the result list you end up actually using. For lazyer behavior use the other handlers.
traverseAllResults :: Monad m => (a -> m ()) -> ListT m a -> m () Source #
Given a function, apply it to all the results.
foldAllResults :: Monad m => (r -> a -> m r) -> r -> ListT m a -> m r Source #
Given a folding function, fold over every result. If you want to terminate eary, use the
foldWithEarlyTermination
instead.
foldWithEarlyTermination :: Monad m => (r -> a -> m (Maybe r)) -> r -> ListT m a -> m r Source #
Same as foldAllResults
but the folding function has the ability to terminate early by
returning Nothing.
evaluateNResults :: Monad m => Int -> ListT m a -> m [a] Source #
Executes only the effects needed to produce the first n results.
evaluateOneResult :: Monad m => ListT m a -> m (Maybe a) Source #
Executes only the effects needed to produce a single result.
evaluateAll :: Monad m => ListT m a -> m () Source #
Execute all the effects but discard their results.
slice :: Monad m => Int -> ListT m a -> ListT m [a] #
A transformation, which slices a list into chunks of the specified length.
drop :: Monad m => Int -> ListT m a -> ListT m a #
A transformation,
reproducing the behaviour of Data.List.
.drop
traverse :: Monad m => (a -> m b) -> ListT m a -> ListT m b #
A transformation, which traverses the stream with an action in the inner monad.
unfoldM :: Monad m => (b -> m (Maybe (a, b))) -> b -> ListT m a #
Construct by unfolding a monadic data structure
This is the most memory-efficient way to construct ListT where the length depends on the inner monad.
unfold :: Monad m => (b -> Maybe (a, b)) -> b -> ListT m a #
Construct by unfolding a pure data structure.
fromMVar :: MonadIO m => MVar (Maybe a) -> ListT m a #
Construct from an MVar, interpreting the value of Nothing as the end.
fromFoldable :: (Monad m, Foldable f) => f a -> ListT m a #
Construct from any foldable.
splitAt :: Monad m => Int -> ListT m a -> m ([a], ListT m a) #
Execute, consuming a list of the specified length and returning the remainder stream.
traverse_ :: Monad m => (a -> m ()) -> ListT m a -> m () #
Execute, traversing the stream with a side effect in the inner monad.
toReverseList :: Monad m => ListT m a -> m [a] #
Execute, folding to a list in the reverse order.
Performs more efficiently than toList
.
foldMaybe :: Monad m => (r -> a -> m (Maybe r)) -> r -> ListT m a -> m r #
A version of fold
, which allows early termination.
tail :: Monad m => ListT m a -> m (Maybe (ListT m a)) #
Execute, getting the tail. Returns nothing if it's empty.
head :: Monad m => ListT m a -> m (Maybe a) #
Execute, getting the head. Returns nothing if it's empty.
uncons :: ListT m a -> m (Maybe (a, ListT m a)) #
Execute in the inner monad, getting the head and the tail. Returns nothing if it's empty.
newtype ListT (m :: Type -> Type) a #
A proper implementation of the list monad-transformer. Useful for streaming of monadic data structures.
Since it has instances of MonadPlus
and Alternative
,
you can use general utilities packages like
"monadplus"
with it.