List-0.1: List monad transformer and class

Control.Monad.ListT

Description

A list monad transformer / a monadic list.

Monadic list example: A program which reads numbers from the user and accumulates them.

 import Control.Monad.ListT (ListT)
 import Data.List.Class (execute, joinM, repeat, scanl, takeWhile)
 import Prelude hiding (repeat, scanl, takeWhile)

 main =
   execute . joinM . fmap print .
   scanl (+) 0 .
   fmap (fst . head) .
   takeWhile (not . null) .
   fmap reads .
   joinM $ (repeat getLine :: ListT IO (IO String))

Synopsis

Documentation

data ListItem l a Source

Constructors

Nil 
Cons 

Fields

headL :: a
 
tailL :: l a
 

newtype ListT m a Source

Constructors

ListT 

Fields

runListT :: m (ListItem (ListT m) a)
 

Instances

MonadTrans ListT 
MonadReader s m => MonadReader s (ListT m) 
MonadState s m => MonadState s (ListT m) 
MonadError e m => MonadError e (ListT m) 
Monad m => Monad (ListT m) 
Monad m => Functor (ListT m) 
Monad m => MonadPlus (ListT m) 
Monad m => Applicative (ListT m) 
MonadIO m => MonadIO (ListT m) 
Monad m => List (ListT m) 
Monad m => Monoid (ListT m a) 

foldrListT :: Monad m => (a -> m b -> m b) -> m b -> ListT m a -> m bSource

foldr for ListT