list-t-1.0.3.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))) 
Instances
MMonad ListT Source # 
Instance details

Defined in ListT

Methods

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

MonadTrans ListT Source # 
Instance details

Defined in ListT

Methods

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

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

Defined in ListT

Methods

liftBase :: b α -> ListT m α #

MonadBaseControl b m => MonadBaseControl b (ListT m) Source # 
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 #

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

Defined in ListT

Methods

throwError :: e -> ListT m a #

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

Monad m => Monad (ListT m) Source # 
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) Source # 
Instance details

Defined in ListT

Methods

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

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

Monad m => MonadFail (ListT m) Source # 
Instance details

Defined in ListT

Methods

fail :: String -> ListT m a #

(Monad m, Functor m) => Applicative (ListT m) Source # 
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 #

MonadIO m => MonadIO (ListT m) Source # 
Instance details

Defined in ListT

Methods

liftIO :: IO a -> ListT m a #

(Monad m, Functor m) => Alternative (ListT m) Source # 
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] #

Monad m => MonadPlus (ListT m) Source # 
Instance details

Defined in ListT

Methods

mzero :: ListT m a #

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

MFunctor ListT Source # 
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) Source # 
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) Source # 
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 StM (ListT m) a Source # 
Instance details

Defined in ListT

type StM (ListT m) a = StM 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.