Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lists.
See also Fcf.Class.Foldable for additional functions.
Synopsis
- data (++) :: [a] -> [a] -> Exp [a]
- data Head :: [a] -> Exp (Maybe a)
- data Last :: [a] -> Exp (Maybe a)
- data Tail :: [a] -> Exp (Maybe [a])
- data Cons :: a -> [a] -> Exp [a]
- data Snoc :: [a] -> a -> Exp [a]
- data Cons2 :: (a, b) -> ([a], [b]) -> Exp ([a], [b])
- data Init :: [a] -> Exp (Maybe [a])
- data Null :: [a] -> Exp Bool
- data Length :: [a] -> Exp Nat
- data Reverse :: [a] -> Exp [a]
- data Intersperse :: a -> [a] -> Exp [a]
- data Intercalate :: [a] -> [[a]] -> Exp [a]
- data Foldr :: (a -> b -> Exp b) -> b -> t a -> Exp b
- data UnList :: b -> (a -> b -> Exp b) -> [a] -> Exp b
- data Concat :: t m -> Exp m
- data ConcatMap :: (a -> Exp [b]) -> t a -> Exp [b]
- data Unfoldr :: (b -> Exp (Maybe (a, b))) -> b -> Exp [a]
- data Replicate :: Nat -> a -> Exp [a]
- data Take :: Nat -> [a] -> Exp [a]
- data Drop :: Nat -> [a] -> Exp [a]
- data TakeWhile :: (a -> Exp Bool) -> [a] -> Exp [a]
- data DropWhile :: (a -> Exp Bool) -> [a] -> Exp [a]
- data Span :: (a -> Exp Bool) -> [a] -> Exp ([a], [a])
- data Break :: (a -> Exp Bool) -> [a] -> Exp ([a], [a])
- data Tails :: [a] -> Exp [[a]]
- data IsPrefixOf :: [a] -> [a] -> Exp Bool
- data IsSuffixOf :: [a] -> [a] -> Exp Bool
- data IsInfixOf :: [a] -> [a] -> Exp Bool
- data Elem :: a -> [a] -> Exp Bool
- data Lookup :: k -> [(k, b)] -> Exp (Maybe b)
- data Find :: (a -> Exp Bool) -> [a] -> Exp (Maybe a)
- data Filter :: (a -> Exp Bool) -> [a] -> Exp [a]
- data Partition :: (a -> Exp Bool) -> [a] -> Exp ([a], [a])
- data FindIndex :: (a -> Exp Bool) -> [a] -> Exp (Maybe Nat)
- data SetIndex :: Nat -> a -> [a] -> Exp [a]
- data ZipWith :: (a -> b -> Exp c) -> [a] -> [b] -> Exp [c]
- data Zip :: [a] -> [b] -> Exp [(a, b)]
- data Unzip :: Exp [(a, b)] -> Exp ([a], [b])
Basic functions
data (++) :: [a] -> [a] -> Exp [a] Source #
List catenation.
Example
>>>
:kind! Eval ('[1, 2] ++ '[3, 4])
Eval ('[1, 2] ++ '[3, 4]) :: [Nat] = '[1, 2, 3, 4]
data Cons :: a -> [a] -> Exp [a] Source #
Append an element to a list.
Example
>>>
:kind! Eval (Cons 1 '[2, 3])
Eval (Cons 1 '[2, 3]) :: [Nat] = '[1, 2, 3]>>>
:kind! Eval (Cons Int '[Char, Maybe Double])
Eval (Cons Int '[Char, Maybe Double]) :: [*] = '[Int, Char, Maybe Double]
data Snoc :: [a] -> a -> Exp [a] Source #
Append an element to the end of a list.
Example
>>>
:kind! Eval (Snoc '[1,2,3] 4)
Eval (Snoc '[1,2,3] 4) :: [Nat] = '[1, 2, 3, 4]
data Cons2 :: (a, b) -> ([a], [b]) -> Exp ([a], [b]) Source #
Append elements to two lists. Used in the definition of Unzip
.
List transformations
data Reverse :: [a] -> Exp [a] Source #
Reverse a list.
Example
>>>
:kind! Eval (Reverse '[1,2,3,4,5])
Eval (Reverse '[1,2,3,4,5]) :: [Nat] = '[5, 4, 3, 2, 1]
data Intersperse :: a -> [a] -> Exp [a] Source #
Intersperse a separator between elements of a list.
Example
>>>
:kind! Eval (Intersperse 0 '[1,2,3,4])
Eval (Intersperse 0 '[1,2,3,4]) :: [Nat] = '[1, 0, 2, 0, 3, 0, 4]
Instances
type Eval (Intersperse _1 ('[] :: [a]) :: [a] -> Type) Source # | |
Defined in Fcf.Data.List | |
type Eval (Intersperse sep (x ': xs) :: [a] -> Type) Source # | |
Defined in Fcf.Data.List |
data Intercalate :: [a] -> [[a]] -> Exp [a] Source #
Join a list of words separated by some word.
Example
>>>
:kind! Eval (Intercalate '[", "] '[ '["Lorem"], '["ipsum"], '["dolor"] ])
Eval (Intercalate '[", "] '[ '["Lorem"], '["ipsum"], '["dolor"] ]) :: [TL.Symbol] = '["Lorem", ", ", "ipsum", ", ", "dolor"]
Instances
type Eval (Intercalate xs xss :: [a] -> Type) Source # | |
Defined in Fcf.Data.List type Eval (Intercalate xs xss :: [a] -> Type) = Eval ((Concat :: [[a]] -> [a] -> Type) =<< Intersperse xs xss) |
Reducing lists
See also Fcf.Class.Foldable.
data Foldr :: (a -> b -> Exp b) -> b -> t a -> Exp b Source #
Right fold.
Example
>>>
:kind! Eval (Foldr (+) 0 '[1, 2, 3, 4])
Eval (Foldr (+) 0 '[1, 2, 3, 4]) :: Nat = 10
Instances
type Eval (Foldr f y ('Right x :: Either a3 a1) :: a2 -> Type) Source # | |
type Eval (Foldr f y ('Left _a :: Either a3 a1) :: a2 -> Type) Source # | |
type Eval (Foldr f y ('Just x) :: a2 -> Type) Source # | |
type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) Source # | |
type Eval (Foldr f y (x ': xs) :: a2 -> Type) Source # | |
type Eval (Foldr f y ('[] :: [a1]) :: a2 -> Type) Source # | |
Defined in Fcf.Class.Foldable |
data UnList :: b -> (a -> b -> Exp b) -> [a] -> Exp b Source #
This is Foldr
with its argument flipped.
data Concat :: t m -> Exp m Source #
Concatenate a collection of elements from a monoid.
Example
For example, fold a list of lists.
Concat :: [[a]] -> Exp [a]
>>>
:kind! Eval (Concat ( '[ '[1,2], '[3,4], '[5,6]]))
Eval (Concat ( '[ '[1,2], '[3,4], '[5,6]])) :: [Nat] = '[1, 2, 3, 4, 5, 6]>>>
:kind! Eval (Concat ( '[ '[Int, Maybe Int], '[Maybe String, Either Double Int]]))
Eval (Concat ( '[ '[Int, Maybe Int], '[Maybe String, Either Double Int]])) :: [*] = '[Int, Maybe Int, Maybe String, Either Double Int]
data ConcatMap :: (a -> Exp [b]) -> t a -> Exp [b] Source #
Map a function and concatenate the results.
This is FoldMap
specialized to the list monoid.
Unfolding and building
data Unfoldr :: (b -> Exp (Maybe (a, b))) -> b -> Exp [a] Source #
Unfold a generator into a list.
Example
>>>
data ToThree :: Nat -> Exp (Maybe (Nat, Nat))
>>>
:{
type instance Eval (ToThree b) = If (Eval (b Fcf.>= 4)) 'Nothing ('Just '(b, b TL.+ 1)) :}
>>>
:kind! Eval (Unfoldr ToThree 0)
Eval (Unfoldr ToThree 0) :: [Nat] = '[0, 1, 2, 3]
See also the definition of Replicate
.
data Replicate :: Nat -> a -> Exp [a] Source #
Repeat the same element in a list.
Example
>>>
:kind! Eval (Replicate 4 '("ok", 2))
Eval (Replicate 4 '("ok", 2)) :: [(TL.Symbol, Nat)] = '[ '("ok", 2), '("ok", 2), '("ok", 2), '("ok", 2)]
Sublists
data Take :: Nat -> [a] -> Exp [a] Source #
Take a prefix of fixed length.
Example
>>>
:kind! Eval (Take 2 '[1,2,3,4,5])
Eval (Take 2 '[1,2,3,4,5]) :: [Nat] = '[1, 2]
data Drop :: Nat -> [a] -> Exp [a] Source #
Drop a prefix of fixed length, evaluate to the remaining suffix.
Example
>>>
:kind! Eval (Drop 2 '[1,2,3,4,5])
Eval (Drop 2 '[1,2,3,4,5]) :: [Nat] = '[3, 4, 5]
data TakeWhile :: (a -> Exp Bool) -> [a] -> Exp [a] Source #
Take the longest prefix of elements satisfying a predicate.
Example
>>>
:kind! Eval (TakeWhile ((>=) 3) '[1, 2, 3, 4, 5])
Eval (TakeWhile ((>=) 3) '[1, 2, 3, 4, 5]) :: [Nat] = '[1, 2, 3]
data DropWhile :: (a -> Exp Bool) -> [a] -> Exp [a] Source #
Drop the longest prefix of elements satisfying a predicate, evaluate to the remaining suffix.
Example
:kind! Eval (DropWhile ((>=) 3) '[1, 2, 3, 4, 5]) Eval (DropWhile ((>=) 3) '[1, 2, 3, 4, 5]) :: [Nat] = '[4, 5]
data Span :: (a -> Exp Bool) -> [a] -> Exp ([a], [a]) Source #
Span
, applied to a predicate p
and a list xs
, returns a tuple:
the first component is the longest prefix (possibly empty) of xs
whose elements
satisfy p
;
the second component is the remainder of the list.
See also TakeWhile
, DropWhile
, and Break
.
Example
>>>
:kind! Eval (Span (Flip (<) 3) '[1,2,3,4,1,2,3,4])
Eval (Span (Flip (<) 3) '[1,2,3,4,1,2,3,4]) :: ([Nat], [Nat]) = '( '[1, 2], '[3, 4, 1, 2, 3, 4])
>>>
:kind! Eval (Span (Flip (<) 9) '[1,2,3])
Eval (Span (Flip (<) 9) '[1,2,3]) :: ([Nat], [Nat]) = '( '[1, 2, 3], '[])
>>>
:kind! Eval (Span (Flip (<) 0) '[1,2,3])
Eval (Span (Flip (<) 0) '[1,2,3]) :: ([Nat], [Nat]) = '( '[], '[1, 2, 3])
data Break :: (a -> Exp Bool) -> [a] -> Exp ([a], [a]) Source #
Break
, applied to a predicate p
and a list xs
, returns a tuple:
the first component is the longest prefix (possibly empty) of xs
whose elements
do not satisfy p
; the second component is the remainder of the list.
Example
>>>
:kind! Eval (Break (Flip (>) 3) '[1,2,3,4,1,2,3,4])
Eval (Break (Flip (>) 3) '[1,2,3,4,1,2,3,4]) :: ([Nat], [Nat]) = '( '[1, 2, 3], '[4, 1, 2, 3, 4])
>>>
:kind! Eval (Break (Flip (<) 9) '[1,2,3])
Eval (Break (Flip (<) 9) '[1,2,3]) :: ([Nat], [Nat]) = '( '[], '[1, 2, 3])
>>>
:kind! Eval (Break (Flip (>) 9) '[1,2,3])
Eval (Break (Flip (>) 9) '[1,2,3]) :: ([Nat], [Nat]) = '( '[1, 2, 3], '[])
data Tails :: [a] -> Exp [[a]] Source #
List of suffixes of a list.
Example
>>>
:kind! Eval (Tails '[0,1,2,3])
Eval (Tails '[0,1,2,3]) :: [[Nat]] = '[ '[0, 1, 2, 3], '[1, 2, 3], '[2, 3], '[3]]
Predicates
data IsPrefixOf :: [a] -> [a] -> Exp Bool Source #
Return True
when the first list is a prefix of the second.
Example
>>>
:kind! Eval (IsPrefixOf '[0,1,2] '[0,1,2,3,4,5])
Eval (IsPrefixOf '[0,1,2] '[0,1,2,3,4,5]) :: Bool = 'True
>>>
:kind! Eval (IsPrefixOf '[0,1,2] '[0,1,3,2,4,5])
Eval (IsPrefixOf '[0,1,2] '[0,1,3,2,4,5]) :: Bool = 'False
>>>
:kind! Eval (IsPrefixOf '[] '[0,1,3,2,4,5])
Eval (IsPrefixOf '[] '[0,1,3,2,4,5]) :: Bool = 'True
>>>
:kind! Eval (IsPrefixOf '[0,1,3,2,4,5] '[])
Eval (IsPrefixOf '[0,1,3,2,4,5] '[]) :: Bool = 'False
Instances
type Eval (IsPrefixOf xs ys :: Bool -> Type) Source # | |
Defined in Fcf.Data.List |
data IsSuffixOf :: [a] -> [a] -> Exp Bool Source #
Return True
when the first list is a suffix of the second.
Example
>>>
:kind! Eval (IsSuffixOf '[3,4,5] '[0,1,2,3,4,5])
Eval (IsSuffixOf '[3,4,5] '[0,1,2,3,4,5]) :: Bool = 'True
>>>
:kind! Eval (IsSuffixOf '[3,4,5] '[0,1,3,2,4,5])
Eval (IsSuffixOf '[3,4,5] '[0,1,3,2,4,5]) :: Bool = 'False
>>>
:kind! Eval (IsSuffixOf '[] '[0,1,3,2,4,5])
Eval (IsSuffixOf '[] '[0,1,3,2,4,5]) :: Bool = 'True
>>>
:kind! Eval (IsSuffixOf '[0,1,3,2,4,5] '[])
Eval (IsSuffixOf '[0,1,3,2,4,5] '[]) :: Bool = 'False
Instances
type Eval (IsSuffixOf xs ys :: Bool -> Type) Source # | |
Defined in Fcf.Data.List |
data IsInfixOf :: [a] -> [a] -> Exp Bool Source #
Return True
when the first list is contained within the second.
Example
>>>
:kind! Eval (IsInfixOf '[2,3,4] '[0,1,2,3,4,5,6])
Eval (IsInfixOf '[2,3,4] '[0,1,2,3,4,5,6]) :: Bool = 'True
>>>
:kind! Eval (IsInfixOf '[2,4,4] '[0,1,2,3,4,5,6])
Eval (IsInfixOf '[2,4,4] '[0,1,2,3,4,5,6]) :: Bool = 'False
Searching
data Elem :: a -> [a] -> Exp Bool Source #
Return True
if an element is in a list.
See also FindIndex
.
Example
>>>
:kind! Eval (Elem 1 '[1,2,3])
Eval (Elem 1 '[1,2,3]) :: Bool = 'True>>>
:kind! Eval (Elem 1 '[2,3])
Eval (Elem 1 '[2,3]) :: Bool = 'False
data Lookup :: k -> [(k, b)] -> Exp (Maybe b) Source #
Find an element associated with a key in an association list.
data Find :: (a -> Exp Bool) -> [a] -> Exp (Maybe a) Source #
Find Just
the first element satisfying a predicate, or evaluate to
Nothing
if no element satisfies the predicate.
Example
>>>
:kind! Eval (Find (TyEq 0) '[1,2,3])
Eval (Find (TyEq 0) '[1,2,3]) :: Maybe Nat = 'Nothing
>>>
:kind! Eval (Find (TyEq 0) '[1,2,3,0])
Eval (Find (TyEq 0) '[1,2,3,0]) :: Maybe Nat = 'Just 0
data Filter :: (a -> Exp Bool) -> [a] -> Exp [a] Source #
Keep all elements that satisfy a predicate, remove all that don't.
Example
>>>
:kind! Eval (Filter ((>) 3) '[1,2,3,0])
Eval (Filter ((>) 3) '[1,2,3,0]) :: [Nat] = '[1, 2, 0]
data Partition :: (a -> Exp Bool) -> [a] -> Exp ([a], [a]) Source #
Split a list into one where all elements satisfy a predicate, and a second where no elements satisfy it.
Example
>>>
:kind! Eval (Partition ((>=) 35) '[ 20, 30, 40, 50])
Eval (Partition ((>=) 35) '[ 20, 30, 40, 50]) :: ([Nat], [Nat]) = '( '[20, 30], '[40, 50])
Indexing lists
data FindIndex :: (a -> Exp Bool) -> [a] -> Exp (Maybe Nat) Source #
Find the index of an element satisfying the predicate.
Example
>>>
:kind! Eval (FindIndex ((<=) 3) '[1,2,3,1,2,3])
Eval (FindIndex ((<=) 3) '[1,2,3,1,2,3]) :: Maybe Nat = 'Just 2
>>>
:kind! Eval (FindIndex ((>) 0) '[1,2,3,1,2,3])
Eval (FindIndex ((>) 0) '[1,2,3,1,2,3]) :: Maybe Nat = 'Nothing
data SetIndex :: Nat -> a -> [a] -> Exp [a] Source #
Modify an element at a given index.
The list is unchanged if the index is out of bounds.
Example
>>>
:kind! Eval (SetIndex 2 7 '[1,2,3])
Eval (SetIndex 2 7 '[1,2,3]) :: [Nat] = '[1, 2, 7]
Zipping and unzipping
data ZipWith :: (a -> b -> Exp c) -> [a] -> [b] -> Exp [c] Source #
Combine elements of two lists pairwise.
Example
>>>
:kind! Eval (ZipWith (+) '[1,2,3] '[1,1,1])
Eval (ZipWith (+) '[1,2,3] '[1,1,1]) :: [Nat] = '[2, 3, 4]