list-transformer-1.0.3: List monad transformer

Safe HaskellSafe
LanguageHaskell2010

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 | str <- 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 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.mapM, which buffers the entire output list before returning a single element).

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.

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

Instances

MonadTrans ListT Source # 

Methods

lift :: Monad m => m a -> ListT m a #

MonadError e m => MonadError e (ListT m) Source # 

Methods

throwError :: e -> ListT m a #

catchError :: ListT m a -> (e -> ListT m a) -> ListT m a #

MonadReader i m => MonadReader i (ListT m) Source # 

Methods

ask :: ListT m i #

local :: (i -> i) -> ListT m a -> ListT m a #

reader :: (i -> a) -> ListT m a #

MonadState s m => MonadState s (ListT m) Source # 

Methods

get :: ListT m s #

put :: s -> ListT m () #

state :: (s -> (a, s)) -> ListT m a #

Monad m => Monad (ListT m) Source # 

Methods

(>>=) :: ListT m a -> (a -> ListT m b) -> ListT m b #

(>>) :: ListT m a -> ListT m b -> ListT m b #

return :: a -> ListT m a #

fail :: String -> ListT m a #

Monad m => Functor (ListT m) Source # 

Methods

fmap :: (a -> b) -> ListT m a -> ListT m b #

(<$) :: a -> ListT m b -> ListT m a #

Monad m => MonadFail (ListT m) Source # 

Methods

fail :: String -> ListT m a #

Monad m => Applicative (ListT m) Source # 

Methods

pure :: a -> ListT m a #

(<*>) :: ListT m (a -> b) -> ListT m a -> ListT m b #

(*>) :: ListT m a -> ListT m b -> ListT m b #

(<*) :: ListT m a -> ListT m b -> ListT m a #

Foldable m => Foldable (ListT m) Source # 

Methods

fold :: Monoid m => ListT m m -> m #

foldMap :: Monoid m => (a -> m) -> ListT m a -> m #

foldr :: (a -> b -> b) -> b -> ListT m a -> b #

foldr' :: (a -> b -> b) -> b -> ListT m a -> b #

foldl :: (b -> a -> b) -> b -> ListT m a -> b #

foldl' :: (b -> a -> b) -> b -> ListT m a -> b #

foldr1 :: (a -> a -> a) -> ListT m a -> a #

foldl1 :: (a -> a -> a) -> ListT m a -> a #

toList :: ListT m a -> [a] #

null :: ListT m a -> Bool #

length :: ListT m a -> Int #

elem :: Eq a => a -> ListT m a -> Bool #

maximum :: Ord a => ListT m a -> a #

minimum :: Ord a => ListT m a -> a #

sum :: Num a => ListT m a -> a #

product :: Num a => ListT m a -> a #

(Traversable m, Monad m) => Traversable (ListT m) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ListT m a -> f (ListT m b) #

sequenceA :: Applicative f => ListT m (f a) -> f (ListT m a) #

mapM :: Monad m => (a -> m b) -> ListT m a -> m (ListT m b) #

sequence :: Monad m => ListT m (m a) -> m (ListT m a) #

MonadIO m => MonadIO (ListT m) Source # 

Methods

liftIO :: IO a -> ListT m a #

Monad m => Alternative (ListT m) Source # 

Methods

empty :: ListT m a #

(<|>) :: ListT m a -> ListT m a -> ListT m a #

some :: ListT m a -> ListT m [a] #

many :: ListT m a -> ListT m [a] #

Monad m => MonadPlus (ListT m) Source # 

Methods

mzero :: ListT m a #

mplus :: ListT m a -> ListT m a -> ListT m a #

(Monad m, Floating a) => Floating (ListT m a) Source # 

Methods

pi :: ListT m a #

exp :: ListT m a -> ListT m a #

log :: ListT m a -> ListT m a #

sqrt :: ListT m a -> ListT m a #

(**) :: ListT m a -> ListT m a -> ListT m a #

logBase :: ListT m a -> ListT m a -> ListT m a #

sin :: ListT m a -> ListT m a #

cos :: ListT m a -> ListT m a #

tan :: ListT m a -> ListT m a #

asin :: ListT m a -> ListT m a #

acos :: ListT m a -> ListT m a #

atan :: ListT m a -> ListT m a #

sinh :: ListT m a -> ListT m a #

cosh :: ListT m a -> ListT m a #

tanh :: ListT m a -> ListT m a #

asinh :: ListT m a -> ListT m a #

acosh :: ListT m a -> ListT m a #

atanh :: ListT m a -> ListT m a #

log1p :: ListT m a -> ListT m a #

expm1 :: ListT m a -> ListT m a #

log1pexp :: ListT m a -> ListT m a #

log1mexp :: ListT m a -> ListT m a #

(Monad m, Fractional a) => Fractional (ListT m a) Source # 

Methods

(/) :: ListT m a -> ListT m a -> ListT m a #

recip :: ListT m a -> ListT m a #

fromRational :: Rational -> ListT m a #

(Monad m, Num a) => Num (ListT m a) Source # 

Methods

(+) :: ListT m a -> ListT m a -> ListT m a #

(-) :: ListT m a -> ListT m a -> ListT m a #

(*) :: ListT m a -> ListT m a -> ListT m a #

negate :: ListT m a -> ListT m a #

abs :: ListT m a -> ListT m a #

signum :: ListT m a -> ListT m a #

fromInteger :: Integer -> ListT m a #

(Monad m, Monoid a) => Monoid (ListT m a) Source # 

Methods

mempty :: ListT m a #

mappend :: ListT m a -> ListT m a -> ListT m a #

mconcat :: [ListT m a] -> 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 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

foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m 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 (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 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

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) Source # 

Methods

fmap :: (a -> b) -> Step m a -> Step m b #

(<$) :: a -> Step m b -> Step m a #

Foldable m => Foldable (Step m) Source # 

Methods

fold :: Monoid m => Step m m -> m #

foldMap :: Monoid m => (a -> m) -> Step m a -> m #

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 #

toList :: Step m a -> [a] #

null :: Step m a -> Bool #

length :: Step m a -> Int #

elem :: Eq a => a -> Step m a -> Bool #

maximum :: Ord a => Step m a -> a #

minimum :: Ord a => Step m a -> a #

sum :: Num a => Step m a -> a #

product :: Num a => Step m a -> a #

(Traversable m, Monad m) => Traversable (Step m) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Step m a -> f (Step m b) #

sequenceA :: Applicative f => Step m (f a) -> f (Step m a) #

mapM :: Monad m => (a -> m b) -> Step m a -> m (Step m b) #

sequence :: Monad m => Step m (m a) -> m (Step m a) #

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

lift

Methods

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

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

Instances

MonadTrans ListT 

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans MaybeT 

Methods

lift :: Monad m => m a -> MaybeT m a #

MonadTrans ListT # 

Methods

lift :: Monad m => m a -> ListT m a #

MonadTrans (ErrorT e) 

Methods

lift :: Monad m => m a -> ErrorT e m a #

MonadTrans (ExceptT e) 

Methods

lift :: Monad m => m a -> ExceptT e m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

MonadTrans (StateT s) 

Methods

lift :: Monad m => m a -> StateT s m a #

Monoid w => MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

Monoid w => MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

MonadTrans (IdentityT *) 

Methods

lift :: Monad m => m a -> IdentityT * m a #

MonadTrans (ContT * r) 

Methods

lift :: Monad m => m a -> ContT * r m a #

MonadTrans (ReaderT * r) 

Methods

lift :: Monad m => m a -> ReaderT * r m a #

Monoid w => MonadTrans (RWST r w s) 

Methods

lift :: Monad m => m a -> RWST r w s m a #

Monoid w => MonadTrans (RWST r w s) 

Methods

lift :: Monad m => m a -> RWST r w s m a #

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

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) # 

Methods

liftIO :: IO a -> ListT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

MonadIO m => MonadIO (ContT * r m) 

Methods

liftIO :: IO a -> ContT * r m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

class Applicative f => Alternative f where #

A monoid on applicative functors.

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

  • some v = (:) <$> v <*> many v
  • many v = some v <|> pure []

Minimal complete definition

empty, (<|>)

Methods

empty :: f a #

The identity of <|>

(<|>) :: f a -> f a -> f a infixl 3 #

An associative binary operation

some :: f a -> f [a] #

One or more.

many :: f a -> f [a] #

Zero or more.

Instances

Alternative [] 

Methods

empty :: [a] #

(<|>) :: [a] -> [a] -> [a] #

some :: [a] -> [[a]] #

many :: [a] -> [[a]] #

Alternative Maybe 

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

Alternative IO 

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

Alternative U1 

Methods

empty :: U1 a #

(<|>) :: U1 a -> U1 a -> U1 a #

some :: U1 a -> U1 [a] #

many :: U1 a -> U1 [a] #

Alternative f => Alternative (Rec1 f) 

Methods

empty :: Rec1 f a #

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

some :: Rec1 f a -> Rec1 f [a] #

many :: Rec1 f a -> Rec1 f [a] #

MonadPlus m => Alternative (WrappedMonad m) 

Methods

empty :: WrappedMonad m a #

(<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a #

some :: WrappedMonad m a -> WrappedMonad m [a] #

many :: WrappedMonad m a -> WrappedMonad m [a] #

ArrowPlus a => Alternative (ArrowMonad a) 

Methods

empty :: ArrowMonad a a #

(<|>) :: ArrowMonad a a -> ArrowMonad a a -> ArrowMonad a a #

some :: ArrowMonad a a -> ArrowMonad a [a] #

many :: ArrowMonad a a -> ArrowMonad a [a] #

Alternative (Proxy *) 

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

Applicative m => Alternative (ListT m) 

Methods

empty :: ListT m a #

(<|>) :: ListT m a -> ListT m a -> ListT m a #

some :: ListT m a -> ListT m [a] #

many :: ListT m a -> ListT m [a] #

(Functor m, Monad m) => Alternative (MaybeT m) 

Methods

empty :: MaybeT m a #

(<|>) :: MaybeT m a -> MaybeT m a -> MaybeT m a #

some :: MaybeT m a -> MaybeT m [a] #

many :: MaybeT m a -> MaybeT m [a] #

Monad m => Alternative (ListT m) # 

Methods

empty :: ListT m a #

(<|>) :: ListT m a -> ListT m a -> ListT m a #

some :: ListT m a -> ListT m [a] #

many :: ListT m a -> ListT m [a] #

(Alternative f, Alternative g) => Alternative ((:*:) f g) 

Methods

empty :: (f :*: g) a #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: (f :*: g) a -> (f :*: g) [a] #

many :: (f :*: g) a -> (f :*: g) [a] #

(Alternative f, Applicative g) => Alternative ((:.:) f g) 

Methods

empty :: (f :.: g) a #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

some :: (f :.: g) a -> (f :.: g) [a] #

many :: (f :.: g) a -> (f :.: g) [a] #

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) 

Methods

empty :: WrappedArrow a b a #

(<|>) :: WrappedArrow a b a -> WrappedArrow a b a -> WrappedArrow a b a #

some :: WrappedArrow a b a -> WrappedArrow a b [a] #

many :: WrappedArrow a b a -> WrappedArrow a b [a] #

Alternative f => Alternative (Alt * f) 

Methods

empty :: Alt * f a #

(<|>) :: Alt * f a -> Alt * f a -> Alt * f a #

some :: Alt * f a -> Alt * f [a] #

many :: Alt * f a -> Alt * f [a] #

(Functor m, Monad m, Error e) => Alternative (ErrorT e m) 

Methods

empty :: ErrorT e m a #

(<|>) :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

some :: ErrorT e m a -> ErrorT e m [a] #

many :: ErrorT e m a -> ErrorT e m [a] #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 

Methods

empty :: ExceptT e m a #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

some :: ExceptT e m a -> ExceptT e m [a] #

many :: ExceptT e m a -> ExceptT e m [a] #

(Functor m, MonadPlus m) => Alternative (StateT s m) 

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

(Functor m, MonadPlus m) => Alternative (StateT s m) 

Methods

empty :: StateT s m a #

(<|>) :: StateT s m a -> StateT s m a -> StateT s m a #

some :: StateT s m a -> StateT s m [a] #

many :: StateT s m a -> StateT s m [a] #

(Monoid w, Alternative m) => Alternative (WriterT w m) 

Methods

empty :: WriterT w m a #

(<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a #

some :: WriterT w m a -> WriterT w m [a] #

many :: WriterT w m a -> WriterT w m [a] #

(Monoid w, Alternative m) => Alternative (WriterT w m) 

Methods

empty :: WriterT w m a #

(<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a #

some :: WriterT w m a -> WriterT w m [a] #

many :: WriterT w m a -> WriterT w m [a] #

Alternative m => Alternative (IdentityT * m) 

Methods

empty :: IdentityT * m a #

(<|>) :: IdentityT * m a -> IdentityT * m a -> IdentityT * m a #

some :: IdentityT * m a -> IdentityT * m [a] #

many :: IdentityT * m a -> IdentityT * m [a] #

Alternative f => Alternative (M1 i c f) 

Methods

empty :: M1 i c f a #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a #

some :: M1 i c f a -> M1 i c f [a] #

many :: M1 i c f a -> M1 i c f [a] #

Alternative m => Alternative (ReaderT * r m) 

Methods

empty :: ReaderT * r m a #

(<|>) :: ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a #

some :: ReaderT * r m a -> ReaderT * r m [a] #

many :: ReaderT * r m a -> ReaderT * r m [a] #

(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) 

Methods

empty :: RWST r w s m a #

(<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

some :: RWST r w s m a -> RWST r w s m [a] #

many :: RWST r w s m a -> RWST r w s m [a] #

(Monoid w, Functor m, MonadPlus m) => Alternative (RWST r w s m) 

Methods

empty :: RWST r w s m a #

(<|>) :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a #

some :: RWST r w s m a -> RWST r w s m [a] #

many :: RWST r w s m a -> RWST r w s m [a] #