list-transformer-1.0.0: List monad transformer

Safe HaskellSafe-Inferred

List.Transformer

Contents

Description

The ListT type is like a list that lets you interleave effects between each element of the list. The type's definition is very short:

 -- Every `ListT` begins with an outermost effect (the `m`)
 newtype ListT m a = ListT { next :: m (Step m a) }
 

 -- The return value of that effect is either
 -- * Cons: a new list element followed by the rest of the list
 -- * Nil : an empty list
 data Step m a = Cons a (ListT m a) | Nil

You most commonly use this type when you wish to generate each element of the list using IO. For example, you can read lines from standard input:

 import List.Transformer

 import qualified System.IO

 stdin :: ListT IO String
 stdin = ListT (do
     eof <- System.IO.isEOF
     if eof
         then return Nil
         else do
             string <- getLine
             return (Cons string stdin) )

You can also loop over a ListT to consume elements one-at-a-time. You "pay as you go" for effects, only running what you actually need:

 stdout :: ListT IO String -> IO ()
 stdout strings = do
     s <- next strings
     case s of
         Nil                  -> return ()
         Cons string strings' -> do
             putStrLn string
             stdout strings'

Combining stdin and stdout forwards lines one-by-one from standard input to standard output:

 main :: IO ()
 main = stdout stdin

These lines stream in constant space, never retaining more than one line in memory:

 $ runghc aboveExample.hs
 Test<Enter>
 Test
 123<Enter>
 123
 ABC<Enter>
 ABC
 <Ctrl-D>
 $

Sometimes we can simplify the code by taking advantage of the fact that the Monad instance for ListT behaves like a list comprehension:

 stdout :: ListT IO String -> IO ()
 stdout strings = runListT (do
     string <- strings
     liftIO (putStrLn string) )

You can read the above code as saying: "for each string in strings, call putStrLn on string.

You can even use list comprehension syntax if you enable the MonadComprehensions language extension:

 stdout strings = runListT [ r | string <- strings, r <- liftIO (putStrLn str) ]

The most important operations that you should familiarize yourself with are:

  • empty, which gives you an empty ListT with 0 elements
 empty :: ListT IO a
 pure, return :: a -> ListT IO a
 liftIO :: IO a -> ListT IO a
 (<|>) :: ListT IO a -> ListT IO a -> ListT IO a
  • (>>=), which powers do notation and MonadComprehensions:
 (>>=) :: ListT IO a -> (a -> ListT IO b) -> ListT IO b

For example, suppose you want to a build a ListT with three elements and no effects. You could just write:

 pure 1 <|> pure 2 <|> pure 3 :: ListT IO Int

... although you would probably prefer to use select instead:

 select :: [a] -> ListT IO a

 select [1, 2, 3] :: ListT IO Int

To test your understanding, guess what this code does and then test your guess by running the code:

 import List.Transformer

 strings :: ListT IO String
 strings = do
     _ <- select (repeat ())
     liftIO (putStrLn "Say something:")
     liftIO getLine

 main :: IO ()
 main = runListT (do
     string <- pure "Hello, there!" <|> strings
     liftIO (putStrLn string) )

This library does not provide utilities like mapM because there are many possible minor variations on mapM that we could write, such as:

 mapM :: Monad m => (a -> m b) -> [a] -> ListT m b
 mapM f xs = do
     x <- select xs
     lift (f x)

 -- Alternatively, using MonadComprehensions:
 mapM f x = [ r | x <- select xs, r <- lift (f x) ]

... or:

 mapM :: Monad m => (a -> m b) -> ListT m a -> ListT m b
 mapM f xs = do
     x <- xs
     lift (f x)

 -- Alternatively, using MonadComprehensions:
 mapM f x = [ r | x <- xs, r <- lift (f x) ]

... or:

 mapM :: Monad m => (a -> ListT m b) -> ListT m a -> ListT m b
 mapM f xs = do
     x <- xs
     f x

 -- Alternatively, using MonadComprehensions:
 mapM f x = [ r | x <- xs, r <- f x ]

 -- Alternatively, using a pre-existing operator from "Control.Monad"
 mapM = (=<<)

Whichever one you prefer, all three variations still stream in constant space (unlike Control.Monad.mapM, which buffers the entire output list before returning a single element).

Synopsis

ListT

newtype ListT m a Source

This is like a list except that you can interleave effects between each list element. For example:

 stdin :: ListT IO String
 stdin = ListT (do
     eof <- System.IO.isEOF
     if eof
         then return Nil
         else do
             line <- getLine
             return (Cons line stdin) )

The mnemonic is "List Transformer" because this type takes a base Monad, 'm', and returns a new transformed Monad that adds support for list comprehensions

Constructors

ListT 

Fields

next :: m (Step m a)
 

Instances

MonadTrans ListT 
MonadError e m => MonadError e (ListT m) 
MonadReader i m => MonadReader i (ListT m) 
MonadState s m => MonadState s (ListT m) 
Monad m => Monad (ListT m) 
Monad m => Functor (ListT m) 
Monad m => MonadPlus (ListT m) 
Monad m => Applicative (ListT m) 
Foldable m => Foldable (ListT m) 
(Monad m, Traversable m) => Traversable (ListT m) 
Monad m => Alternative (ListT m) 
MonadIO m => MonadIO (ListT m) 
(Monad m, Floating a) => Floating (ListT m a) 
(Monad m, Fractional a) => Fractional (ListT m a) 
(Monad m, Num a) => Num (ListT m a) 
(Monad m, Monoid a) => Monoid (ListT m a) 

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

Use this to drain a ListT, running it to completion and discarding all values. For example:

 stdout :: ListT IO String -> IO ()
 stdout l = runListT (do
     str <- l
     liftIO (putStrLn str) )

The most common specialized type for runListT will be:

 runListT :: ListT IO a -> IO ()

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

Use this to fold a ListT into a single value. This is designed to be used with the foldl library:

 import Control.Foldl (purely)
 import List.Transformer (fold)

 purely fold :: Monad m => Fold a b -> ListT m a -> m b

... but you can also use the fold function directly:

 fold (+) 0 id :: Num a => ListT m a -> m a

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

Use this to fold a ListT into a single value. This is designed to be used with the foldl library:

 import Control.Foldl (impurely)
 import List.Transformer (fold)

 impurely fold :: Monad m => FoldM m a b -> ListT m a -> m b

... but you can also use the foldM function directly.

select :: (Foldable f, Alternative m) => f a -> m aSource

Convert any collection that implements Foldable to another collection that implements Alternative

For this library, the most common specialized type for select will be:

 select :: [a] -> ListT IO a

Step

data Step m a Source

Pattern match on this type when you loop explicitly over a ListT using next. For example:

 stdout :: ListT IO String -> IO ()
 stdout l = do
     s <- next l
     case s of
         Nil       -> return ()
         Cons x l' -> do
             putStrLn x
             stdout l'

Constructors

Cons a (ListT m a) 
Nil 

Instances

Monad m => Functor (Step m) 
Foldable m => Foldable (Step m) 
(Monad m, Traversable m) => Traversable (Step m) 

Re-exports

class MonadTrans t where

The class of monad transformers. Instances should satisfy the following laws, which state that lift is a transformer of monads:

Methods

lift :: Monad m => m a -> t m a

Lift a computation from the argument monad to the constructed monad.

class Monad m => MonadIO m where

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a

Lift a computation from the IO monad.

Instances

MonadIO IO 
MonadIO m => MonadIO (ListT m) 
MonadIO m => MonadIO (MaybeT m) 
MonadIO m => MonadIO (IdentityT m) 
MonadIO m => MonadIO (ListT m) 
MonadIO m => MonadIO (ContT r m) 
(Error e, MonadIO m) => MonadIO (ErrorT e m) 
MonadIO m => MonadIO (ReaderT r m) 
MonadIO m => MonadIO (StateT s m) 
MonadIO m => MonadIO (StateT s m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

class Applicative f => Alternative f where

A monoid on applicative functors.

Minimal complete definition: empty and <|>.

If defined, some and many should be the least solutions of the equations:

Methods

empty :: f a

The identity of <|>

(<|>) :: f a -> f a -> f a

An associative binary operation

some :: f a -> f [a]

One or more.

many :: f a -> f [a]

Zero or more.