Safe Haskell | Safe-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.
- newtype List a = List (forall r. Monoid r => (a -> r) -> r)
- uncons :: List a -> Maybe (a, List a)
- caseList :: b -> (a -> List a -> b) -> List a -> b
- cons :: a -> List a -> List a
- snoc :: List a -> a -> List a
- fromList :: [a] -> List a
- head :: List a -> a
- headMay :: List a -> Maybe a
- init :: List a -> List a
- initMay :: List a -> Maybe (List a)
- tail :: List a -> List a
- tailMay :: List a -> Maybe (List a)
- last :: List a -> a
- lastMay :: List a -> Maybe a
- null :: List a -> Bool
- length :: List a -> Int
- map :: (a -> b) -> List a -> List b
- reverse :: List a -> List a
- intersperse :: a -> List a -> List a
- intercalate :: List a -> List (List a) -> List a
- transpose :: List (List a) -> List (List a)
- subsequences :: List a -> List (List a)
- permutations :: List a -> List (List a)
- concat :: List (List a) -> List a
- concatMap :: (a -> List b) -> List a -> List b
- scanl :: (a -> b -> a) -> a -> List b -> List a
- scanl1 :: (a -> a -> a) -> List a -> List a
- scanr :: (a -> b -> b) -> b -> List a -> List b
- scanr1 :: (a -> a -> a) -> List a -> List a
- mapAccumL :: (acc -> x -> (acc, y)) -> acc -> List x -> (acc, List y)
- mapAccumR :: (acc -> x -> (acc, y)) -> acc -> List x -> (acc, List y)
- iterate :: (a -> a) -> a -> List a
- repeat :: a -> List a
- replicate :: Int -> a -> List a
- cycle :: List a -> List a
- unfoldr :: (b -> Maybe (a, b)) -> b -> List a
- splitAt :: Int -> List a -> (List a, List a)
- takeWhile :: (a -> Bool) -> List a -> List a
- dropWhile :: (a -> Bool) -> List a -> List a
- dropWhileEnd :: (a -> Bool) -> List a -> List a
- span :: (a -> Bool) -> List a -> (List a, List a)
- break :: (a -> Bool) -> List a -> (List a, List a)
- stripPrefix :: Eq a => List a -> List a -> Maybe (List a)
- group :: Eq a => List a -> List (List a)
- inits :: List a -> List (List a)
- tails :: List a -> List (List a)
- isPrefixOf :: Eq a => List a -> List a -> Bool
- isSuffixOf :: Eq a => List a -> List a -> Bool
- isInfixOf :: Eq a => List a -> List a -> Bool
- lookup :: Eq a => a -> List (a, b) -> Maybe b
- filter :: (a -> Bool) -> List a -> List a
- partition :: (a -> Bool) -> List a -> (List a, List a)
- (!!) :: List a -> Int -> a
- elemIndex :: Eq a => a -> List a -> Maybe Int
- elemIndices :: Eq a => a -> List a -> List Int
- findIndex :: (a -> Bool) -> List a -> Maybe Int
- findIndices :: (a -> Bool) -> List a -> List Int
- zip :: List a -> List b -> List (a, b)
- zip3 :: List a -> List b -> List c -> List (a, b, c)
- zip4 :: List a -> List b -> List c -> List d -> List (a, b, c, d)
- zip5 :: List a -> List b -> List c -> List d -> List e -> List (a, b, c, d, e)
- zip6 :: List a -> List b -> List c -> List d -> List e -> List f -> List (a, b, c, d, e, f)
- zip7 :: List a -> List b -> List c -> List d -> List e -> List f -> List g -> List (a, b, c, d, e, f, g)
- zipWith :: (a -> b -> c) -> List a -> List b -> List c
- zipWith3 :: (a -> b -> c -> d) -> List a -> List b -> List c -> List d
- zipWith4 :: (a -> b -> c -> d -> e) -> List a -> List b -> List c -> List d -> List e
- zipWith5 :: (a -> b -> c -> d -> e -> f) -> List a -> List b -> List c -> List d -> List e -> List f
- zipWith6 :: (a -> b -> c -> d -> e -> f -> g) -> List a -> List b -> List c -> List d -> List e -> List f -> List g
- zipWith7 :: (a -> b -> c -> d -> e -> f -> g -> h) -> List a -> List b -> List c -> List d -> List e -> List f -> List g -> List h
- unzip :: List (a, b) -> (List a, List b)
- unzip3 :: List (a, b, c) -> (List a, List b, List c)
- unzip4 :: List (a, b, c, d) -> (List a, List b, List c, List d)
- unzip5 :: List (a, b, c, d, e) -> (List a, List b, List c, List d, List e)
- unzip6 :: List (a, b, c, d, e, f) -> (List a, List b, List c, List d, List e, List f)
- unzip7 :: List (a, b, c, d, e, f, g) -> (List a, List b, List c, List d, List e, List f, List g)
- lines :: String -> List String
- words :: String -> List String
- unlines :: List String -> String
- unwords :: List String -> String
- nub :: Eq a => List a -> List a
- delete :: Eq a => a -> List a -> List a
- (\\) :: Eq a => List a -> List a -> List a
- union :: Eq a => List a -> List a -> List a
- intersect :: Eq a => List a -> List a -> List a
- sort :: Ord a => List a -> List a
- insert :: Ord a => a -> List a -> List a
- nubBy :: (a -> a -> Bool) -> List a -> List a
- deleteBy :: (a -> a -> Bool) -> a -> List a -> List a
- deleteFirstsBy :: (a -> a -> Bool) -> List a -> List a -> List a
- unionBy :: (a -> a -> Bool) -> List a -> List a -> List a
- intersectBy :: (a -> a -> Bool) -> List a -> List a -> List a
- groupBy :: (a -> a -> Bool) -> List a -> List (List a)
- sortBy :: (a -> a -> Ordering) -> List a -> List a
- insertBy :: (a -> a -> Ordering) -> a -> List a -> List a
- genericLength :: Num i => List b -> i
- genericTake :: Integral i => i -> List a -> List a
- genericDrop :: Integral i => i -> List a -> List a
- genericSplitAt :: Integral i => i -> List b -> (List b, List b)
- genericIndex :: Integral a => List b -> a -> b
- genericReplicate :: Integral i => i -> a -> List a
Documentation
intersperse :: a -> List a -> List aSource
subsequences :: List a -> List (List a)Source
permutations :: List a -> List (List a)Source
dropWhileEnd :: (a -> Bool) -> List a -> List aSource
zip7 :: List a -> List b -> List c -> List d -> List e -> List f -> List g -> List (a, b, c, d, e, f, g)Source
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
unzip7 :: List (a, b, c, d, e, f, g) -> (List a, List b, List c, List d, List e, List f, List g)Source
genericLength :: Num i => List b -> iSource
genericTake :: Integral i => i -> List a -> List aSource
genericDrop :: Integral i => i -> List a -> List aSource
genericIndex :: Integral a => List b -> a -> bSource
genericReplicate :: Integral i => i -> a -> List aSource