list-t-0.4.2: ListT done right

Safe HaskellNone
LanguageHaskell2010

ListT

Contents

Synopsis

Documentation

data 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.

Instances

Classes

class MonadTrans t => MonadTransUncons t where Source

A monad transformer capable of deconstructing like a list.

Methods

uncons :: Monad m => 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.

class MonadPlus m => MonadCons 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, MonadTransUncons t) => t m a -> m (Maybe a) Source

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

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

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

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

Execute, checking whether it's empty.

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

Execute, applying a left fold.

foldMaybe :: (Monad m, MonadTransUncons t) => (r -> a -> m (Maybe r)) -> r -> t m a -> m r Source

A version of fold, which allows early termination.

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

Execute, folding to a list.

toReverseList :: (Monad m, MonadTransUncons t) => t m a -> m [a] Source

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

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

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

splitAt :: (Monad m, MonadTransUncons t, MonadPlus (t m)) => Int -> t m a -> m ([a], t m a) Source

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

Construction utilities

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

Construct from any foldable.

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

Construct by unfolding a pure data structure.

repeat :: MonadCons 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.

type Transformation m a b = forall t. (Monad m, MonadCons (t m), MonadTransUncons t) => t m a -> t m b Source

A function, which updates the contents of a list transformer.

Since it's merely just a function, you can run it by passing a list transformer as an argument.

traverse :: (a -> m b) -> Transformation m a b Source

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

take :: Int -> Transformation m a a Source

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

drop :: Int -> Transformation m a a Source

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

slice :: Positive Int -> Transformation m a [a] Source

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

Positive numbers

data Positive n Source

A newtype wrapper around a number, which ensures that it is greater than zero.

Instances

Eq n => Eq (Positive n) 
Data n => Data (Positive n) 
Ord n => Ord (Positive n) 
Read n => Read (Positive n) 
Show n => Show (Positive n) 
Generic (Positive n) 
Typeable (* -> *) Positive 
type Rep (Positive n) 

positive :: (Ord n, Num n) => n -> Maybe (Positive n) Source

A smart constructor for positive numbers.