Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The ListT
type is like a list that lets you interleave effects between
each element of the list.
Synopsis
- 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
- unfold :: Monad m => (b -> m (Maybe (a, b))) -> b -> ListT m a
- take :: Monad m => Int -> ListT m a -> ListT m a
- drop :: Monad m => Int -> ListT m a -> ListT m a
- dropWhile :: Monad m => (a -> Bool) -> ListT m a -> ListT m a
- takeWhile :: Monad m => (a -> Bool) -> ListT m a -> ListT m a
- zip :: Monad m => ListT m a -> ListT m b -> ListT m (a, b)
- data Step m a
- newtype ZipListT m a = ZipListT {
- getZipListT :: ListT m a
- class MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- class Monad m => MonadIO (m :: Type -> Type) where
- class Applicative f => Alternative (f :: Type -> Type) where
- class MFunctor (t :: (Type -> Type) -> k -> Type) where
Introduction
The type's definition is very short:
newtypeListT
m a = ListT { next :: m (Step
m a) }
Every ListT
begins with an outermost effect (the 'm'
, commonly IO
). The return value of that effect is either:
dataStep
m a = Cons a (ListT
m a) | Nil
- Cons: a new list element followed by the rest of the list
- Nil : an empty list
Example: stdin, stdout
You most commonly use the ListT 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> $
Core operations
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 powersdo
notation andMonadComprehensions
(>>=) :: ListT IO a -> (a -> ListT IO b) -> ListT IO b
select :: [a] -> ListT IO a
Monadic combination
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) ]
There are a few ways we could consider defining a ListT
analogue to the mapM
function from Prelude
, but none are given in this library because they need
require only (>>=
) and some trivial lifting.
mapM :: (a -> IO b) -> [a] -> IO [b] ( \f xs -> xs >>= f ) :: (a -> ListT IO b) -> ListT IO a -> ListT IO b ( \f xs -> select xs >>= lift . f ) :: (a -> IO b) -> [a] -> ListT IO b ( \f xs -> xs >>= lift . f ) :: (a -> IO b) -> ListT IO a -> ListT IO b
A critical difference between mapM
and ListT
's monad is that ListT
will
stream in constant space, whereas mapM
buffers the entire output list before
returning a single element.
Exercise: Interaction
To test your understanding, guess what this code does and then test your guess by running the code:
import List.Transformer (ListT
,runListT
,liftIO
, (<|>
),select
) import Data.Foldable (asum
) import Data.List (repeat
) strings ::ListT
IO String strings = doselect
(repeat
())asum
[ pure "" , pure "Say something:" , do x <-liftIO
getLine return ("You said: "<|>
x) ] main :: IO () main =runListT
(do string <- pure "Hello, there!"<|>
stringsliftIO
(putStrLn string) )
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
Consuming
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.
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
>>>
fold (<>) "" id (select ["a", "b", "c", "d", "e"])
"abcde"
Constructing
empty
is the empty list with no effects.
Use pure
/return
to construct a singleton list with no effects. Use liftIO
to turn an effect into a singleton list whose sole element is the effect's result.
Suppose you want to build a ListT
with three elements and no effects.
You could write:
pure 1 <|> pure 2 <|> pure 3 :: ListT IO Int
... although you would probably prefer to use select
instead:
select [1, 2, 3] :: ListT IO Int
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
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
.
Removing elements
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
dropWhile :: Monad m => (a -> Bool) -> ListT m a -> ListT m a Source #
dropWhile pred xs
drops elements from the head of xs
if they
satisfy the predicate, but still runs their effects.
>>>
let list xs = do x <- select xs; liftIO (print (show x)); return x
>>>
let sum = fold (+) 0 id
>>>
sum (dropWhile even (list [2,4,5,7,8]))
"2" "4" "5" "7" "8" 20
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
To filter elements from a list based on a predicate, use guard
.
For example, the following function is analogous to filter
:
filter :: Monad m => (a -> m Bool) -> ListT m a -> ListT m a filter pred as = do a <- as b <- lift (pred a) guard b return a
Concatenation
Use (<|>
) to concatenate two lists.
(<|>) :: ListT IO a -> ListT IO a -> ListT IO a
Use asum
to flatten a list of lists.
asum :: [ListT IO a] -> ListT IO a
Use join
to flatten a ListT
of ListT
s.
join :: ListT IO (ListT IO a) -> ListT IO a
Pairwise combination
The (<>
) operation joins every combination of an element from one list with
an element from the other.
>>>
runListT ( (select ["a", "b"] <> select ["1", "2", "3"]) >>= (liftIO . print) )
"a1" "a2" "a3" "b1" "b2" "b3"
This is the same combinatorial effect that (>>=
) produces.
>>>
runListT (do x <- select ["a", "b"]; y <- select ["1", "2", "3"]; liftIO (print (x <> y)))
"a1" "a2" "a3" "b1" "b2" "b3"
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"
Repetition
Unbounded repetition can be induced using
.
For example, here are several functions analogous to select
(repeat
())cycle
:
cycle1 :: Monad m => a -> ListT m a cycle1 a = do select (Data.List.repeat ()) return a
cycle2 :: Monad m => [a] -> ListT m a cycle2 as = do select (Data.List.repeat ()) select as
cycle3 :: Monad m => m a -> ListT m a cycle3 m = do select (Data.List.repeat ()) lift m
cycle4 :: Monad m => [m a] -> ListT m a cycle4 ms = do select (Data.List.repeat ()) m <- select ms lift m
cycle5 :: Monad m => ListT m a -> ListT m a cycle5 x = do select (Data.List.repeat ()) x
cycle6 :: Monad m => [ListT m a] -> ListT m a cycle6 lists = do select (Data.List.repeat ()) x <- select lists x
In a similar manner, we can use replicate
as the initial selection
to achieve bounded repetition:
replicate1 :: Monad m => Int -> a -> ListT m a replicate1 n a = do select (Data.List.replicate n ()) return a
replicate2 :: Monad m => Int -> [a] -> ListT m a replicate2 n as = do select (Data.List.replicate n ()) select as
replicate3 :: Monad m => Int -> m a -> ListT m a replicate3 n m = do select (Data.List.replicate n ()) lift m
replicate4 :: Monad m => Int -> [m a] -> ListT m a replicate4 n ms = do select (Data.List.replicate n ()) m <- select ms lift m
replicate5 :: Monad m => Int -> ListT m a -> ListT m a replicate5 n x = do select (Data.List.replicate n ()) x
replicate6 :: Monad m => Int -> [ListT m a] -> ListT m a replicate6 n lists = do select (Data.List.replicate n ()) x <- select lists x
Step
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'
Instances
MFunctor Step Source # | |
Foldable m => Foldable (Step m) Source # | |
Defined in List.Transformer fold :: Monoid m0 => Step m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Step m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Step m a -> m0 # foldr :: (a -> b -> b) -> b -> Step m a -> b # foldr' :: (a -> b -> b) -> b -> Step m a -> b # foldl :: (b -> a -> b) -> b -> Step m a -> b # foldl' :: (b -> a -> b) -> b -> Step m a -> b # foldr1 :: (a -> a -> a) -> Step m a -> a # foldl1 :: (a -> a -> a) -> Step m a -> a # elem :: Eq a => a -> Step m a -> Bool # maximum :: Ord a => Step m a -> a # minimum :: Ord a => Step m a -> a # | |
(Monad m, Traversable m) => Traversable (Step m) Source # | |
Monad m => Functor (Step m) Source # | |
Alternative instances
Similar to ZipList
in base: a newtype wrapper over ListT
that
overrides its normal Applicative
instance (combine every combination)
with one that "zips" outputs together one at a time.
>>>
let xs = do x <- select [1,2,3,4]; liftIO (print x)
>>>
let ys = do y <- select [5,6]; liftIO (print y)
>>>
runListT (xs *> ys)
1 5 6 2 5 6 3 5 6 4 5 6>>>
runListT (getZipListT (ZipListT xs *> ZipListT ys))
1 5 2 6 3
Note that the final "3" is printed even though it isn't paired with anything.
While this can be used to do zipping, it is usually more convenient to
just use zip
. This is more useful if you are working with a function
that expects "an Applicative instance", written to be polymorphic over
all Applicatives.
ZipListT | |
|
Instances
Re-exports
class MonadTrans (t :: (Type -> Type) -> Type -> Type) where #
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a monad transformation:
lift :: Monad m => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
Instances
MonadTrans ListT Source # | |
Defined in List.Transformer | |
MonadTrans ListT | |
Defined in Control.Monad.Trans.List | |
MonadTrans MaybeT | |
Defined in Control.Monad.Trans.Maybe | |
MonadTrans (ErrorT e) | |
Defined in Control.Monad.Trans.Error | |
MonadTrans (ExceptT e) | |
Defined in Control.Monad.Trans.Except | |
MonadTrans (IdentityT :: (Type -> Type) -> Type -> Type) | |
Defined in Control.Monad.Trans.Identity | |
MonadTrans (ReaderT r) | |
Defined in Control.Monad.Trans.Reader | |
MonadTrans (StateT s) | |
Defined in Control.Monad.Trans.State.Lazy | |
MonadTrans (StateT s) | |
Defined in Control.Monad.Trans.State.Strict | |
Monoid w => MonadTrans (WriterT w) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
Monoid w => MonadTrans (WriterT w) | |
Defined in Control.Monad.Trans.Writer.Strict | |
MonadTrans (ContT r) | |
Defined in Control.Monad.Trans.Cont | |
Monoid w => MonadTrans (RWST r w s) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
Monoid w => MonadTrans (RWST r w s) | |
Defined in Control.Monad.Trans.RWS.Strict |
class Monad m => MonadIO (m :: Type -> Type) 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:
Lift a computation from the IO
monad.
This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations
(i.e. IO
is the base monad for the stack).
Example
import Control.Monad.Trans.State -- from the "transformers" library printState :: Show s => StateT s IO () printState = do state <- get liftIO $ print state
Had we omitted
, we would have ended up with this error:liftIO
• Couldn't match type ‘IO’ with ‘StateT s IO’ Expected type: StateT s IO () Actual type: IO ()
The important part here is the mismatch between StateT s IO ()
and
.IO
()
Luckily, we know of a function that takes an
and returns an IO
a(m a)
:
,
enabling us to run the program and see the expected results:liftIO
> evalStateT printState "hello" "hello" > evalStateT printState 3 3
Instances
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
class MFunctor (t :: (Type -> Type) -> k -> Type) where #
A functor in the category of monads, using hoist
as the analog of fmap
:
hoist (f . g) = hoist f . hoist g hoist id = id
hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> t m b -> t n b #
Lift a monad morphism from m
to n
into a monad morphism from
(t m)
to (t n)
The first argument to hoist
must be a monad morphism, even though the
type system does not enforce this
Instances
MFunctor ListT Source # | |
MFunctor Step Source # | |
MFunctor Lift | |
MFunctor MaybeT | |
MFunctor (Backwards :: (Type -> Type) -> Type -> Type) | |
MFunctor (ExceptT e :: (Type -> Type) -> Type -> Type) | |
MFunctor (IdentityT :: (Type -> Type) -> Type -> Type) | |
MFunctor (ReaderT r :: (Type -> Type) -> Type -> TYPE LiftedRep) | |
MFunctor (StateT s :: (Type -> Type) -> Type -> TYPE LiftedRep) | |
MFunctor (StateT s :: (Type -> Type) -> Type -> TYPE LiftedRep) | |
MFunctor (WriterT w :: (Type -> Type) -> Type -> Type) | |
MFunctor (WriterT w :: (Type -> Type) -> Type -> Type) | |
MFunctor (Product f :: (Type -> Type) -> Type -> Type) | |
Functor f => MFunctor (Compose f :: (Type -> Type) -> Type -> Type) | |
MFunctor (RWST r w s :: (Type -> Type) -> Type -> TYPE LiftedRep) | |
MFunctor (RWST r w s :: (Type -> Type) -> Type -> TYPE LiftedRep) | |