List-0.4.0: List monad transformer and class

Data.List.Class

Description

The List class and actions for lists

Synopsis

Documentation

The List typeclass

class (MonadPlus l, Monad (ItemM l)) => List l whereSource

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

Associated Types

type ItemM l :: * -> *Source

Methods

runList :: l a -> ItemM l (ListItem l a)Source

joinL :: ItemM l (l a) -> l aSource

Transform an action returning a list to the returned list

 > joinL $ Identity "hello"
 "hello"

Instances

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

data ListItem l a Source

Constructors

Nil 
Cons 

Fields

headL :: a
 
tailL :: l a
 

Instances

Functor m => Functor (ListItem m) 
(Eq a, Eq (l a)) => Eq (ListItem l a) 
(Ord a, Ord (l a)) => Ord (ListItem l a) 
(Read a, Read (l a)) => Read (ListItem l a) 
(Show a, Show (l a)) => Show (ListItem l a) 

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 => (a -> Bool) -> l a -> l aSource

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

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

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

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

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

Non standard List operations

foldrL :: List l => (a -> ItemM l b -> ItemM l b) -> ItemM l b -> l a -> ItemM l bSource

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

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

An action to do foldl for Lists

foldl1L :: List l => (a -> a -> a) -> l a -> ItemM l aSource

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

An action to transform a List to a list

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

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

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

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

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

Consume all items and return the last one

 > runIdentity $ lastL "hello"
 'o'

merge2On :: (Ord b, List l) => (a -> b) -> l a -> l a -> l aSource

Merge two lists sorted by a criteria given the criteria

 > merge2On id "01568" "239"
 "01235689"

mergeOn :: (Ord b, List l) => (a -> b) -> l (l a) -> l aSource

Merge many lists sorted by a criteria given the criteria

 > mergeOn length [["hi", "hey", "hello"], ["cat", "falcon"], ["banana", "cucumber"]]
 ["hi","cat","hey","hello","banana","falcon","cucumber"]

Operations useful for monadic lists

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

Execute the monadic actions in a List

joinM :: List l => l (ItemM l a) -> l aSource

Transform a list of actions to a list of their results

 > joinM [Identity 4, Identity 7]
 [4,7]

mapL :: List l => (a -> ItemM l b) -> l a -> l bSource

iterateM :: List l => (a -> ItemM l a) -> ItemM l a -> l aSource

Monadic version of iterate. Can be used to produce trees given a children of node function.

 import Data.List.Tree (bfsLayers)
 take 3 $ bfsLayers (iterateM (\i -> [i*2, i*2+1]) [1] :: ListT [] Int)
 [[1],[2,3],[4,5,6,7]]

takeWhileM :: List l => (a -> ItemM l Bool) -> l a -> l aSource

Operations for non-monadic lists

sortOn :: Ord b => (a -> b) -> [a] -> [a]Source

Convert between List types

transformListMonad :: (List l, List k) => (forall x. ItemM l x -> ItemM k 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"

listStateJoin :: (List l, List k, ItemM l ~ StateT s (ItemM k)) => l a -> ItemM l (k a)Source

listStateJoin can transform a ListT (StateT s m) a to a StateT s m (ListT m a).

When iterating a list, a state is already maintained and passed along in the form of the location along the list. This joins the inner StateT s into the list. The list will fork the state given to it and won't share its changes.