simple-effects-0.13.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.List

Description

Add non-determinism to your monad. Uses the ListT transformer under the hood.

Synopsis

Documentation

newtype NonDeterminism m Source #

Constructors

NonDeterminismMethods 

Fields

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.

repeat :: Monad m => a -> ListT m a #

Produce an infinite stream.

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.

cons :: Monad m => a -> ListT m a -> ListT m a #

Prepend an element.

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.

toList :: Monad m => ListT m a -> m [a] #

Execute, folding to a list.

foldMaybe :: Monad m => (r -> a -> m (Maybe r)) -> r -> ListT m a -> m r #

A version of fold, which allows early termination.

fold :: Monad m => (r -> a -> m r) -> r -> ListT m a -> m r #

Execute, applying a left fold.

null :: Monad m => ListT m a -> m Bool #

Execute, checking whether it's empty.

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.

Constructors

ListT (m (Maybe (a, ListT m a))) 
Instances
MonadTrans ListT 
Instance details

Defined in ListT

Methods

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

MMonad ListT 
Instance details

Defined in ListT

Methods

embed :: Monad n => (forall a. m a -> ListT n a) -> ListT m b -> ListT n b #

RunnableTrans ListT Source # 
Instance details

Defined in Control.Monad.Runnable

Associated Types

type TransformerState ListT m :: Type Source #

type TransformerResult ListT a :: Type Source #

MonadError e m => MonadError e (ListT m) 
Instance details

Defined in ListT

Methods

throwError :: e -> ListT m a #

catchError :: ListT m a -> (e -> ListT m a) -> ListT m a #

MonadBaseControl b m => MonadBaseControl b (ListT m) 
Instance details

Defined in ListT

Associated Types

type StM (ListT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ListT m) b -> b a) -> ListT m a #

restoreM :: StM (ListT m) a -> ListT m a #

MonadBase b m => MonadBase b (ListT m) 
Instance details

Defined in ListT

Methods

liftBase :: b α -> ListT m α #

Monad m => MonadEffect NonDeterminism (ListT m) Source # 
Instance details

Defined in Control.Effects.List

Monad m => Monad (ListT m) 
Instance details

Defined in ListT

Methods

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

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

return :: a -> ListT m a #

fail :: String -> ListT m a #

Functor m => Functor (ListT m) 
Instance details

Defined in ListT

Methods

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

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

(Monad m, Functor m) => Applicative (ListT m) 
Instance details

Defined in ListT

Methods

pure :: a -> ListT m a #

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

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

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

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

Monad m => MonadPlus (ListT m) 
Instance details

Defined in ListT

Methods

mzero :: ListT m a #

mplus :: ListT m a -> ListT m a -> ListT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in ListT

Methods

liftIO :: IO a -> ListT m a #

(Monad m, Functor m) => Alternative (ListT m) 
Instance details

Defined in ListT

Methods

empty :: ListT m a #

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

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

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

MFunctor ListT 
Instance details

Defined in ListT

Methods

hoist :: Monad m => (forall a. m a -> n a) -> ListT m b -> ListT n b #

Monad m => Semigroup (ListT m a) 
Instance details

Defined in ListT

Methods

(<>) :: ListT m a -> ListT m a -> ListT m a #

sconcat :: NonEmpty (ListT m a) -> ListT m a #

stimes :: Integral b => b -> ListT m a -> ListT m a #

Monad m => Monoid (ListT m a) 
Instance details

Defined in ListT

Methods

mempty :: ListT m a #

mappend :: ListT m a -> ListT m a -> ListT m a #

mconcat :: [ListT m a] -> ListT m a #

type TransformerState ListT m Source # 
Instance details

Defined in Control.Monad.Runnable

type TransformerResult ListT a Source # 
Instance details

Defined in Control.Monad.Runnable

type StM (ListT m) a 
Instance details

Defined in ListT

type StM (ListT m) a = StM m (Maybe (a, ListT m a))