Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- 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)
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
Instances
MonadTrans ListT | |
Defined in List.Transformer | |
MonadReader i m => MonadReader i (ListT m) | |
MonadState s m => MonadState s (ListT m) | |
MonadError e m => MonadError e (ListT m) | |
Defined in List.Transformer throwError :: e -> ListT m a # catchError :: ListT m a -> (e -> ListT m a) -> ListT m a # | |
Monad m => Monad (ListT m) | |
Monad m => Functor (ListT m) | |
Monad m => MonadFail (ListT m) | |
Defined in List.Transformer | |
Monad m => Applicative (ListT m) | |
Foldable m => Foldable (ListT m) | |
Defined in List.Transformer 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 # elem :: Eq a => a -> ListT m a -> Bool # maximum :: Ord a => ListT m a -> a # minimum :: Ord a => ListT m a -> a # | |
(Monad m, Traversable m) => Traversable (ListT m) | |
Monad m => Alternative (ListT m) | |
Monad m => MonadPlus (ListT m) | |
MonadIO m => MonadIO (ListT m) | |
Defined in List.Transformer | |
(Monad m, Floating a) => Floating (ListT m a) | |
Defined in List.Transformer 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 # | |
(Monad m, Fractional a) => Fractional (ListT m a) | |
(Monad m, Num a) => Num (ListT m a) | |
(Monad m, Semigroup a) => Semigroup (ListT m a) | |
(Monad m, Semigroup a, Monoid a) => Monoid (ListT m a) | |
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
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"