list-t-0.2.2: ListT done right

Safe HaskellNone
LanguageHaskell2010

ListT

Contents

Synopsis

Documentation

data ListT m a Source

A proper implementation of a 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.

Instances

MFunctor ListT 
MonadTrans ListT 
ListTrans ListT 
MonadBase b m => MonadBase b (ListT m) 
MonadBaseControl b m => MonadBaseControl b (ListT m) 
(Monad m, Functor m) => Alternative (ListT m) 
Monad m => Monad (ListT m) 
Functor m => Functor (ListT m) 
Monad m => MonadPlus (ListT m) 
(Monad m, Functor m) => Applicative (ListT m) 
MonadIO m => MonadIO (ListT m) 
Monad m => ListMonad (ListT m) 
Monad m => Monoid (ListT m a) 
data StM (ListT m) = StM (StM m (Maybe (a, ListT m a))) 

Classes

class MonadTrans t => ListTrans t where Source

A monad transformer capable of executing like a list.

Methods

uncons :: t m a -> m (Maybe (a, t m a)) Source

Execute in the inner monad, getting the head and the tail. Returns nothing if it's empty.

Instances

class MonadPlus m => ListMonad m where Source

A monad capable of constructing like a list.

Methods

cons :: a -> m a -> m a Source

Prepend an element.

Instances

Execution utilities

head :: (Monad m, ListTrans t) => t m a -> m (Maybe a) Source

Execute, getting the head. Returns nothing if it's empty.

tail :: (Monad m, ListTrans t) => t m a -> m (Maybe (t m a)) Source

Execute, getting the tail. Returns nothing if it's empty.

null :: (Monad m, ListTrans t) => t m a -> m Bool Source

Execute, checking whether it's empty.

fold :: (Monad m, ListTrans t) => (r -> a -> m r) -> r -> t m a -> m r Source

Execute, applying a left fold.

toList :: (Monad m, ListTrans t) => t m a -> m [a] Source

Execute, folding to a list.

traverse_ :: (Monad m, ListTrans t) => (a -> m ()) -> t m a -> m () Source

Execute, traversing the stream with a side effect in the inner monad.

Construction utilities

fromFoldable :: (ListMonad m, Foldable f) => f a -> m a Source

Construct from any foldable.

unfold :: ListMonad m => (b -> Maybe (a, b)) -> b -> m a Source

Construct by unfolding a pure data structure.

repeat :: ListMonad m => a -> m a Source

Produce an infinite stream.

Transformation utilities

These utilities only accumulate the transformations without actually traversing the stream. They only get applied with a single traversal, which happens at the execution.

traverse :: (Monad m, ListMonad (t m), ListTrans t) => (a -> m b) -> t m a -> t m b Source

A transformation, which traverses the stream with an action in the inner monad.

take :: (Monad m, ListMonad (t m), ListTrans t) => Int -> t m a -> t m a Source

A trasformation, reproducing the behaviour of Data.List.take.

drop :: (Monad m, ListMonad (t m), ListTrans t) => Int -> t m a -> t m a Source

A trasformation, reproducing the behaviour of Data.List.drop.