List-0.6.2: List monad transformer and class

Safe HaskellSafe
LanguageHaskell98

Data.List.Class

Description

The List class and actions for lists

Synopsis

Documentation

The List typeclass

class (MonadPlus l, Monad (ItemM l)) => List l where Source #

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

Minimal complete definition

runList, joinL

Associated Types

type ItemM l :: * -> * Source #

Methods

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

joinL :: ItemM l (l a) -> l a Source #

Transform an action returning a list to the returned list

> joinL $ Identity "hello"
"hello"

cons :: a -> l a -> l a infixr 5 Source #

cons. Can be derived from MonadPlus but is part of class for performance.

Instances

List [] Source # 

Associated Types

type ItemM ([] :: * -> *) :: * -> * Source #

Methods

runList :: [a] -> ItemM [] (ListItem [] a) Source #

joinL :: ItemM [] [a] -> [a] Source #

cons :: a -> [a] -> [a] Source #

Monad m => List (ListT m) Source # 

Associated Types

type ItemM (ListT m :: * -> *) :: * -> * Source #

Methods

runList :: ListT m a -> ItemM (ListT m) (ListItem (ListT m) a) Source #

joinL :: ItemM (ListT m) (ListT m a) -> ListT m a Source #

cons :: a -> ListT m a -> ListT m a Source #

data ListItem l a Source #

Constructors

Nil 
Cons 

Fields

Instances

Functor m => Functor (ListItem m) Source # 

Methods

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

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

(Eq (l a), Eq a) => Eq (ListItem l a) Source # 

Methods

(==) :: ListItem l a -> ListItem l a -> Bool #

(/=) :: ListItem l a -> ListItem l a -> Bool #

(Ord (l a), Ord a) => Ord (ListItem l a) Source # 

Methods

compare :: ListItem l a -> ListItem l a -> Ordering #

(<) :: ListItem l a -> ListItem l a -> Bool #

(<=) :: ListItem l a -> ListItem l a -> Bool #

(>) :: ListItem l a -> ListItem l a -> Bool #

(>=) :: ListItem l a -> ListItem l a -> Bool #

max :: ListItem l a -> ListItem l a -> ListItem l a #

min :: ListItem l a -> ListItem l a -> ListItem l a #

(Read (l a), Read a) => Read (ListItem l a) Source # 
(Show (l a), Show a) => Show (ListItem l a) Source # 

Methods

showsPrec :: Int -> ListItem l a -> ShowS #

show :: ListItem l a -> String #

showList :: [ListItem l a] -> ShowS #

fromList :: List l => [a] -> l a Source #

Convert a list to a MonadPlus

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

List operations for MonadPlus

filter :: MonadPlus m => (a -> Bool) -> m a -> m a Source #

filter for any MonadPlus

> filter (> 5) (Just 3)
Nothing

Standard list operations

repeat :: List l => a -> l a Source #

take :: List l => Int -> l a -> l a Source #

takeWhile :: List l => (a -> Bool) -> l a -> l a Source #

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

scanl :: List l => (a -> b -> a) -> a -> l b -> l a Source #

scanl1 :: List l => (a -> a -> a) -> l a -> l a Source #

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

concat :: List l => l [a] -> l a Source #

Generalized concat

For List l => l (l a) -> l a use join

concatMap :: List l => (a -> [b]) -> l a -> l b Source #

Genereralized concatMap

For List l => (a -> l b) -> l a -> l b use =<< (monadic bind)

tail :: List l => l a -> l a Source #

enumFrom :: (List l, Enum a) => a -> l a Source #

enumFromTo :: (List l, Enum a) => a -> a -> l a Source #

catMaybes :: List l => l (Maybe a) -> l a Source #

mapMaybe :: List l => (a -> Maybe b) -> l a -> l b Source #

Non standard List operations

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

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

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

An action to do foldl for Lists

foldl1L :: List l => (a -> a -> a) -> l a -> ItemM l a Source #

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

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

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

lastL :: List l => l a -> ItemM l a Source #

Consume all items and return the last one

> runIdentity $ lastL "hello"
'o'

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

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

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

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

filterL :: List l => (a -> ItemM l Bool) -> l a -> l a Source #

iterateM :: List l => (a -> ItemM l a) -> ItemM l a -> l a Source #

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

repeatM :: List l => ItemM l a -> l a Source #

splitAtM :: List l => Int -> l a -> ItemM l ([a], l a) Source #

Monadic variant of splitAt. Consumes x items from the list and return them with the remaining monadic list.

splitWhenM :: List l => (a -> ItemM l Bool) -> l a -> ItemM l ([a], l a) Source #

Monadic variant of break. Consumes items from the list until a condition holds.

Operations for non-monadic lists

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

Convert between List types

transformListMonad :: (List l, List k) => (ItemM l (k a) -> ItemM k (k a)) -> l a -> k a Source #

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.