| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
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) | NilYou 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 | str <- strings, r <- liftIO (putStrLn str) ]
The most important operations that you should familiarize yourself with are:
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 powersdonotation andMonadComprehensions:
(>>=) :: ListT IO a -> (a -> ListT IO b) -> ListT IO b
For example, suppose you want to 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 xs = [ 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 xs = [ 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 xs = [ 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., which buffers the entire output
list before returning a single element).mapM
This library is designed to stream results in constant space and does not expose an obvious way to collect all the results into memory. As a rule of thumb if you think you need to collect all the results in memory try to instead see if you can consume the results as they are being generated (such as in all the above examples). If you can stream the data from start to finish then your code will use significantly less memory and your program will become more responsive.
- newtype ListT m a = ListT {}
- runListT :: Monad m => ListT m a -> m ()
- fold :: Monad m => (x -> a -> x) -> x -> (x -> b) -> ListT m a -> m b
- foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> ListT m a -> m b
- select :: (Foldable f, Alternative m) => f a -> m a
- take :: Monad m => Int -> ListT m a -> ListT m a
- drop :: Monad m => Int -> ListT m a -> ListT m a
- takeWhile :: Monad m => (a -> Bool) -> ListT m a -> ListT m a
- unfold :: Monad m => (b -> m (Maybe (a, b))) -> b -> ListT m a
- zip :: Monad m => ListT m a -> ListT m b -> ListT m (a, b)
- data Step m a
- class MonadTrans (t :: (* -> *) -> * -> *) where
- class Monad m => MonadIO (m :: * -> *) where
- class Applicative f => Alternative (f :: * -> *) where
ListT
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
Instances
| MonadTrans ListT Source # | |
| MonadState s m => MonadState s (ListT m) Source # | |
| MonadReader i m => MonadReader i (ListT m) Source # | |
| MonadError e m => MonadError e (ListT m) Source # | |
| Monad m => Monad (ListT m) Source # | |
| Monad m => Functor (ListT m) Source # | |
| Monad m => MonadFail (ListT m) Source # | |
| Monad m => Applicative (ListT m) Source # | |
| Foldable m => Foldable (ListT m) Source # | |
| (Traversable m, Monad m) => Traversable (ListT m) Source # | |
| MonadIO m => MonadIO (ListT m) Source # | |
| Monad m => Alternative (ListT m) Source # | |
| Monad m => MonadPlus (ListT m) Source # | |
| (Monad m, Floating a) => Floating (ListT m a) Source # | |
| (Monad m, Fractional a) => Fractional (ListT m a) Source # | |
| (Monad m, Num a) => Num (ListT m a) Source # | |
| (Monad m, Semigroup a) => Semigroup (ListT m a) Source # | |
| (Monad m, Semigroup a, Monoid a) => Monoid (ListT m a) Source # | |
fold :: Monad m => (x -> a -> x) -> x -> (x -> b) -> ListT m a -> m b Source #
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
select :: (Foldable f, Alternative m) => f a -> m a Source #
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
take :: Monad m => Int -> ListT m a -> ListT m a Source #
take n xs takes n elements from the head of xs.
>>>let list xs = do x <- select xs; liftIO (print (show x)); return x>>>let sum = fold (+) 0 id>>>sum (take 2 (list [5,4,3,2,1]))"5" "4" 9
drop :: Monad m => Int -> ListT m a -> ListT m a Source #
drop n xs drops n elements from the head of xs, but still runs their
effects.
>>>let list xs = do x <- select xs; liftIO (print (show x)); return x>>>let sum = fold (+) 0 id>>>sum (drop 2 (list [5,4,3,2,1]))"5" "4" "3" "2" "1" 6
takeWhile :: Monad m => (a -> Bool) -> ListT m a -> ListT m a Source #
takeWhile pred xs takes elements from xs until the predicate pred fails
>>>let list xs = do x <- select xs; liftIO (print (show x)); return x>>>let sum = fold (+) 0 id>>>sum (takeWhile even (list [2,4,5,7,8]))"2" "4" "5" 6
unfold :: Monad m => (b -> m (Maybe (a, b))) -> b -> ListT m a Source #
unfold step seed generates a ListT from a step function and an
initial seed.
zip :: Monad m => ListT m a -> ListT m b -> ListT m (a, b) Source #
zip xs ys zips two ListT together, running the effects of each before
possibly recursing. Notice in the example below, 4 is output even though
it has no corresponding element in the second list.
>>>let list xs = do x <- select xs; liftIO (print (show x)); return x>>>runListT (zip (list [1,2,3,4,5]) (list [6,7,8]))"1" "6" "2" "7" "3" "8" "4"
Step
Re-exports
class MonadTrans (t :: (* -> *) -> * -> *) where #
The class of monad transformers. Instances should satisfy the
following laws, which state that lift is a monad transformation:
Minimal complete definition
Methods
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
| MonadTrans ListT | |
| MonadTrans MaybeT | |
| MonadTrans ListT # | |
| MonadTrans (ErrorT e) | |
| MonadTrans (ExceptT e) | |
| MonadTrans (StateT s) | |
| MonadTrans (StateT s) | |
| Monoid w => MonadTrans (WriterT w) | |
| Monoid w => MonadTrans (WriterT w) | |
| MonadTrans (IdentityT *) | |
| MonadTrans (ContT * r) | |
| MonadTrans (ReaderT * r) | |
| Monoid w => MonadTrans (RWST r w s) | |
| Monoid w => MonadTrans (RWST r w s) | |
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:
Minimal complete definition
Instances
| MonadIO IO | Since: 4.9.0.0 |
| MonadIO m => MonadIO (ListT m) | |
| MonadIO m => MonadIO (MaybeT m) | |
| MonadIO m => MonadIO (ListT m) # | |
| (Error e, MonadIO m) => MonadIO (ErrorT e m) | |
| MonadIO m => MonadIO (ExceptT e 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) | |
| MonadIO m => MonadIO (IdentityT * m) | |
| MonadIO m => MonadIO (ContT * r m) | |
| MonadIO m => MonadIO (ReaderT * r 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.
If defined, some and many should be the least solutions
of the equations:
Methods
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances