generator-0.5: A list monad transformer and related functions.

Data.List.Class

Description

The List class and actions for lists

Synopsis

Documentation

The List typeclass

class (MonadPlus l, Monad m) => List l m | l -> m whereSource

A class for list types. Every list has an underlying monad.

Methods

joinL :: m (l b) -> l bSource

Transform an action returning a list to the returned list

 > joinL $ Identity "hello"
 "hello"

foldrL :: (a -> m b -> m b) -> m b -> l a -> m bSource

foldr for Lists. the result and 'right side' values are monadic actions.

toListT :: l a -> ListT m aSource

Convert to a ListT.

Can be done with a foldrL but included in type-class for efficiency.

fromListT :: ListT m a -> l aSource

Convert from a ListT.

Can be done with a foldrL but included in type-class for efficiency.

Instances

List [] Identity 
Monad m => List (ListT m) m 
Monad m => List (DListT m) m 

List operations for MonadPlus

cons :: MonadPlus m => a -> m a -> m aSource

Prepend an item to a MonadPlus

fromList :: MonadPlus m => [a] -> m aSource

Convert a list to a MonadPlus

 > fromList [] :: Maybe Int
 Nothing
 > fromList [5] :: Maybe Int
 Just 5

filter :: MonadPlus m => (a -> Bool) -> m a -> m aSource

filter for any MonadPlus

 > filter (> 5) (Just 3)
 Nothing

repeat :: MonadPlus m => a -> m aSource

Standard list operations

takeWhile :: List l m => (a -> Bool) -> l a -> l aSource

genericTake :: (Integral i, List l m) => i -> l a -> l aSource

scanl :: List l m => (a -> b -> a) -> a -> l b -> l aSource

sequence :: List l m => l (m a) -> m (l a)Source

sequence_ :: List l m => l (m a) -> m ()Source

transpose :: List l m => l (l a) -> l (l a)Source

zip :: List l m => l a -> l b -> l (a, b)Source

zipWith :: List l m => (a -> b -> c) -> l a -> l b -> l cSource

Non standard List operations

foldlL :: List l m => (a -> b -> a) -> a -> l b -> m aSource

An action to do foldl for Lists

toList :: List l m => l a -> m [a]Source

An action to transform a List to a list

 > runIdentity $ toList "hello!"
 "hello!"

execute :: List l m => l a -> m ()Source

Execute the monadic actions in a List

lengthL :: (Integral i, List l m) => l a -> m iSource

Consume a list (execute its actions) and return its length

 > runIdentity $ lengthL [1,2,3]
 3

lastL :: List l m => l a -> m aSource

Consume all items and return the last one

 > runIdentity $ lastL "hello"
 'o'

Convert between List types

convList :: (List l m, List k m) => l a -> k aSource

Convert between lists with the same underlying monad

transformListMonad :: (List l m, List k s) => (forall x. m x -> s x) -> l a -> k aSource

Transform the underlying monad of a list given a way to transform the monad

 > import Data.List.Tree (bfs)
 > bfs (transformListMonad (\(Identity x) -> [x, x]) "hey" :: ListT [] Char)
 "hheeeeyyyyyyyy"

liftListMonad :: (MonadTrans t, Monad (t m), List l m) => l a -> ListT (t m) aSource

Lift the underlying monad of a list and transform it to a ListT.

Doing plain 'transformListMonad lift' instead doesn't give the compiler the same knowledge about the types.