list-t-1: ListT done right

Safe HaskellNone
LanguageHaskell2010

ListT

Contents

Synopsis

Documentation

newtype ListT m a Source

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))) 

Execution utilities

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

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

head :: Monad m => ListT m a -> m (Maybe a) Source

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

tail :: Monad m => ListT m a -> m (Maybe (ListT m a)) Source

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

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

Execute, checking whether it's empty.

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

Execute, applying a left fold.

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

A version of fold, which allows early termination.

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

Execute, folding to a list.

toReverseList :: Monad m => ListT m a -> m [a] Source

Execute, folding to a list in the reverse order. Performs more efficiently than toList.

traverse_ :: Monad m => (a -> m ()) -> ListT m a -> m () Source

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

splitAt :: Monad m => Int -> ListT m a -> m ([a], ListT m a) Source

Execute, consuming a list of the specified length and returning the remainder stream.

Construction utilities

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

Prepend an element.

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

Construct from any foldable.

fromMVar :: MonadIO m => MVar (Maybe a) -> ListT m a Source

Construct from an MVar, interpreting the value of Nothing as the end.

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

Construct by unfolding a pure data structure.

unfoldM :: Monad m => (b -> m (Maybe (a, b))) -> b -> ListT m a Source

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.

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

Produce an infinite stream.

Transformation utilities

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

traverse :: Monad m => (a -> m b) -> ListT m a -> ListT m b Source

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

take :: Monad m => Int -> ListT m a -> ListT m a Source

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

drop :: Monad m => Int -> ListT m a -> ListT m a Source

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

slice :: Monad m => Int -> ListT m a -> ListT m [a] Source

A transformation, which slices a list into chunks of the specified length.