List-0.4.0: 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 (join)
 import Control.Monad.ListT (ListT)
 import Control.Monad.Trans (lift)
 import Data.List.Class (execute, repeat, scanl, takeWhile, mapL)
 import Prelude hiding (repeat, scanl, takeWhile)
 
 main =
     execute . mapL print .
     scanl (+) 0 .
     fmap (fst . head) .
     takeWhile (not . null) .
     fmap reads $ do
       repeat ()
       lift getLine :: ListT IO String

Documentation

newtype ListT m a Source

Constructors

ListT 

Fields

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

Instances

MonadTrans ListT 
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) 
Eq (m (ListItem (ListT m) a)) => Eq (ListT m a) 
Ord (m (ListItem (ListT m) a)) => Ord (ListT m a) 
Read (m (ListItem (ListT m) a)) => Read (ListT m a) 
Show (m (ListItem (ListT m) a)) => Show (ListT m a) 
Monad m => Monoid (ListT m a)