planet-mitchell-0.0.0: Planet Mitchell

Safe HaskellSafe
LanguageHaskell2010

ListT

Synopsis

Documentation

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

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 
Instance details

Defined in List.Transformer

Methods

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

MonadReader i m => MonadReader i (ListT m) 
Instance details

Defined in List.Transformer

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) 
Instance details

Defined in List.Transformer

Methods

get :: ListT m s #

put :: s -> ListT m () #

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

MonadError e m => MonadError e (ListT m) 
Instance details

Defined in List.Transformer

Methods

throwError :: e -> ListT m a #

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

Monad m => Monad (ListT m) 
Instance details

Defined in List.Transformer

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) 
Instance details

Defined in List.Transformer

Methods

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

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

Monad m => MonadFail (ListT m) 
Instance details

Defined in List.Transformer

Methods

fail :: String -> ListT m a #

Monad m => Applicative (ListT m) 
Instance details

Defined in List.Transformer

Methods

pure :: a -> ListT m a #

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

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

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

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

Foldable m => Foldable (ListT m) 
Instance details

Defined in List.Transformer

Methods

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

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

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 #

(Monad m, Traversable m) => Traversable (ListT m) 
Instance details

Defined in List.Transformer

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 m0 => (a -> m0 b) -> ListT m a -> m0 (ListT m b) #

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

Monad m => Alternative (ListT m) 
Instance details

Defined in List.Transformer

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) 
Instance details

Defined in List.Transformer

Methods

mzero :: ListT m a #

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

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in List.Transformer

Methods

liftIO :: IO a -> ListT m a #

(Monad m, Floating a) => Floating (ListT m a) 
Instance details

Defined in List.Transformer

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) 
Instance details

Defined in List.Transformer

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) 
Instance details

Defined in List.Transformer

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, Semigroup a) => Semigroup (ListT m a) 
Instance details

Defined in List.Transformer

Methods

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

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

stimes :: Integral b => b -> ListT m a -> ListT m a #

(Monad m, Semigroup a, Monoid a) => Monoid (ListT m a) 
Instance details

Defined in List.Transformer

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

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 #

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 #

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 #

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 #

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 #

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 #

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 #

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

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"