church-list-0.0.1: Lazy lists with O(1) concatenation that, unlike dlists, allow inspection

Safe HaskellSafe-Inferred

Data.Church.List

Description

This module provides a Tree-based lazy list representation which offers O(1) concatenation and snoc, similarly to difference lists, but also examine examination of the results. Since many operations require walking the tree, they are computationally more expensive than regular lists, but are ideal for the situation where you must constantly append to, and examine, a list that you are building up.

Synopsis

Documentation

newtype List a Source

Constructors

List (forall r. Monoid r => (a -> r) -> r) 

uncons :: List a -> Maybe (a, List a)Source

caseList :: b -> (a -> List a -> b) -> List a -> bSource

Case analyze a concat type's head and tail.

cons :: a -> List a -> List aSource

snoc :: List a -> a -> List aSource

fromList :: [a] -> List aSource

head :: List a -> aSource

init :: List a -> List aSource

tail :: List a -> List aSource

last :: List a -> aSource

map :: (a -> b) -> List a -> List bSource

intersperse :: a -> List a -> List aSource

concatMap :: (a -> List b) -> List a -> List bSource

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

scanl1 :: (a -> a -> a) -> List a -> List aSource

scanr :: (a -> b -> b) -> b -> List a -> List bSource

scanr1 :: (a -> a -> a) -> List a -> List aSource

mapAccumL :: (acc -> x -> (acc, y)) -> acc -> List x -> (acc, List y)Source

mapAccumR :: (acc -> x -> (acc, y)) -> acc -> List x -> (acc, List y)Source

iterate :: (a -> a) -> a -> List aSource

repeat :: a -> List aSource

replicate :: Int -> a -> List aSource

unfoldr :: (b -> Maybe (a, b)) -> b -> List aSource

splitAt :: Int -> List a -> (List a, List a)Source

takeWhile :: (a -> Bool) -> List a -> List aSource

dropWhile :: (a -> Bool) -> List a -> List aSource

dropWhileEnd :: (a -> Bool) -> List a -> List aSource

span :: (a -> Bool) -> List a -> (List a, List a)Source

break :: (a -> Bool) -> List a -> (List a, List a)Source

stripPrefix :: Eq a => List a -> List a -> Maybe (List a)Source

group :: Eq a => List a -> List (List a)Source

isPrefixOf :: Eq a => List a -> List a -> BoolSource

isSuffixOf :: Eq a => List a -> List a -> BoolSource

isInfixOf :: Eq a => List a -> List a -> BoolSource

lookup :: Eq a => a -> List (a, b) -> Maybe bSource

filter :: (a -> Bool) -> List a -> List aSource

partition :: (a -> Bool) -> List a -> (List a, List a)Source

(!!) :: List a -> Int -> aSource

elemIndex :: Eq a => a -> List a -> Maybe IntSource

elemIndices :: Eq a => a -> List a -> List IntSource

findIndex :: (a -> Bool) -> List a -> Maybe IntSource

findIndices :: (a -> Bool) -> List a -> List IntSource

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

zip3 :: List a -> List b -> List c -> List (a, b, c)Source

zip4 :: List a -> List b -> List c -> List d -> List (a, b, c, d)Source

zip5 :: List a -> List b -> List c -> List d -> List e -> List (a, b, c, d, e)Source

zip6 :: List a -> List b -> List c -> List d -> List e -> List f -> List (a, b, c, d, e, f)Source

zip7 :: List a -> List b -> List c -> List d -> List e -> List f -> List g -> List (a, b, c, d, e, f, g)Source

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

zipWith3 :: (a -> b -> c -> d) -> List a -> List b -> List c -> List dSource

zipWith4 :: (a -> b -> c -> d -> e) -> List a -> List b -> List c -> List d -> List eSource

zipWith5 :: (a -> b -> c -> d -> e -> f) -> List a -> List b -> List c -> List d -> List e -> List fSource

zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> List a -> List b -> List c -> List d -> List e -> List f -> List gSource

zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> List a -> List b -> List c -> List d -> List e -> List f -> List g -> List hSource

unzip :: List (a, b) -> (List a, List b)Source

unzip3 :: List (a, b, c) -> (List a, List b, List c)Source

unzip4 :: List (a, b, c, d) -> (List a, List b, List c, List d)Source

unzip5 :: List (a, b, c, d, e) -> (List a, List b, List c, List d, List e)Source

unzip6 :: List (a, b, c, d, e, f) -> (List a, List b, List c, List d, List e, List f)Source

unzip7 :: List (a, b, c, d, e, f, g) -> (List a, List b, List c, List d, List e, List f, List g)Source

nub :: Eq a => List a -> List aSource

delete :: Eq a => a -> List a -> List aSource

(\\) :: Eq a => List a -> List a -> List aSource

union :: Eq a => List a -> List a -> List aSource

intersect :: Eq a => List a -> List a -> List aSource

sort :: Ord a => List a -> List aSource

insert :: Ord a => a -> List a -> List aSource

nubBy :: (a -> a -> Bool) -> List a -> List aSource

deleteBy :: (a -> a -> Bool) -> a -> List a -> List aSource

deleteFirstsBy :: (a -> a -> Bool) -> List a -> List a -> List aSource

unionBy :: (a -> a -> Bool) -> List a -> List a -> List aSource

intersectBy :: (a -> a -> Bool) -> List a -> List a -> List aSource

groupBy :: (a -> a -> Bool) -> List a -> List (List a)Source

sortBy :: (a -> a -> Ordering) -> List a -> List aSource

insertBy :: (a -> a -> Ordering) -> a -> List a -> List aSource

genericTake :: Integral i => i -> List a -> List aSource

genericDrop :: Integral i => i -> List a -> List aSource

genericSplitAt :: Integral i => i -> List b -> (List b, List b)Source

genericIndex :: Integral a => List b -> a -> bSource