first-class-families-0.8.1.0: First-class type families
Safe HaskellSafe-Inferred
LanguageHaskell2010

Fcf.Data.List

Description

Lists.

See also Fcf.Class.Foldable for additional functions.

Synopsis

Basic functions

data (++) :: [a] -> [a] -> Exp [a] Source #

List catenation.

Example

Expand
>>> data Example where Ex :: a -> Example  -- Hide the type of examples to avoid brittleness in different GHC versions
>>> :kind! Ex (Eval ([1, 2] ++ [3, 4]) :: [Natural])
Ex (Eval ([1, 2] ++ [3, 4]) :: [Natural]) :: Example
= Ex [1, 2, 3, 4]

Instances

Instances details
type Eval (xs ++ ys :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (xs ++ ys :: [a] -> Type) = xs <> ys

data Head :: [a] -> Exp (Maybe a) Source #

Instances

Instances details
type Eval (Head ('[] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Head ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) = 'Just a2

data Last :: [a] -> Exp (Maybe a) Source #

Instances

Instances details
type Eval (Last ('[] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Last ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) = Eval (Last (b ': as))
type Eval (Last '[a2] :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Last '[a2] :: Maybe a1 -> Type) = 'Just a2

data Tail :: [a] -> Exp (Maybe [a]) Source #

Instances

Instances details
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tail (_a ': as) :: Maybe [a] -> Type) = 'Just as
type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]

data Cons :: a -> [a] -> Exp [a] Source #

Append an element to a list.

Example

Expand
>>> :kind! Eval (Cons 1 [2, 3])
Eval (Cons 1 [2, 3]) :: [Natural]
= [1, 2, 3]
>>> :kind! Eval (Cons Int [Char, Maybe Double])
Eval (Cons Int [Char, Maybe Double]) :: [*]
= [Int, Char, Maybe Double]

Instances

Instances details
type Eval (Cons a2 as :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Cons a2 as :: [a1] -> Type) = a2 ': as

data Snoc :: [a] -> a -> Exp [a] Source #

Append an element to the end of a list.

Example

Expand
>>> :kind! Eval (Snoc [1,2,3] 4)
Eval (Snoc [1,2,3] 4) :: [Natural]
= [1, 2, 3, 4]

Instances

Instances details
type Eval (Snoc lst a :: [k] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Snoc lst a :: [k] -> Type) = Eval (lst ++ '[a])

data Cons2 :: (a, b) -> ([a], [b]) -> Exp ([a], [b]) Source #

Append elements to two lists. Used in the definition of Unzip.

Instances

Instances details
type Eval (Cons2 '(a3, b) '(as, bs) :: ([a1], [a2]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Cons2 '(a3, b) '(as, bs) :: ([a1], [a2]) -> Type) = '(a3 ': as, b ': bs)

data Init :: [a] -> Exp (Maybe [a]) Source #

Instances

Instances details
type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) = Eval ((Map (Cons a2) :: Maybe [a1] -> Maybe [a1] -> Type) =<< Init (b ': as))
type Eval (Init '[a2] :: Maybe [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Init '[a2] :: Maybe [a1] -> Type) = 'Just ('[] :: [a1])

data Null :: [a] -> Exp Bool Source #

Instances

Instances details
type Eval (Null ('[] :: [a]) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Null ('[] :: [a]) :: Bool -> Type) = 'True
type Eval (Null (a2 ': as) :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Null (a2 ': as) :: Bool -> Type) = 'False

data Length :: [a] -> Exp Nat Source #

Instances

Instances details
type Eval (Length ('[] :: [a]) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Length ('[] :: [a]) :: Nat -> Type) = 0
type Eval (Length (a2 ': as) :: Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Length (a2 ': as) :: Nat -> Type) = 1 + Eval (Length as)

List transformations

data Reverse :: [a] -> Exp [a] Source #

Reverse a list.

Example

Expand
>>> :kind! Eval (Reverse [1,2,3,4,5])
Eval (Reverse [1,2,3,4,5]) :: [Natural]
= [5, 4, 3, 2, 1]

Instances

Instances details
type Eval (Reverse l :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Reverse l :: [a] -> Type)

data Intersperse :: a -> [a] -> Exp [a] Source #

Intersperse a separator between elements of a list.

Example

Expand
>>> :kind! Eval (Intersperse 0 [1,2,3,4])
Eval (Intersperse 0 [1,2,3,4]) :: [Natural]
= [1, 0, 2, 0, 3, 0, 4]

Instances

Instances details
type Eval (Intersperse _1 ('[] :: [a]) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Intersperse _1 ('[] :: [a]) :: [a] -> Type) = '[] :: [a]
type Eval (Intersperse sep (x ': xs) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Intersperse sep (x ': xs) :: [a] -> Type)

data Intercalate :: [a] -> [[a]] -> Exp [a] Source #

Join a list of words separated by some word.

Example

Expand
>>> :kind! Eval (Intercalate '[", "] [ '["Lorem"], '["ipsum"], '["dolor"] ])
Eval (Intercalate '[", "] [ '["Lorem"], '["ipsum"], '["dolor"] ]) :: [TL.Symbol]
= ["Lorem", ", ", "ipsum", ", ", "dolor"]

Instances

Instances details
type Eval (Intercalate xs xss :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Intercalate xs xss :: [a] -> Type) = Eval ((Concat :: [[a]] -> [a] -> Type) =<< Intersperse xs xss)

Reducing lists

data Foldr :: (a -> b -> Exp b) -> b -> t a -> Exp b Source #

Right fold.

Example

Expand
>>> :kind! Eval (Foldr (+) 0 [1, 2, 3, 4])
Eval (Foldr (+) 0 [1, 2, 3, 4]) :: Natural
= 10

Instances

Instances details
type Eval (Foldr f y ('Left _a :: Either a3 a1) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Left _a :: Either a3 a1) :: a2 -> Type) = y
type Eval (Foldr f y ('Right x :: Either a3 a1) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Right x :: Either a3 a1) :: a2 -> Type) = Eval (f x y)
type Eval (Foldr f y ('Just x) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Just x) :: a2 -> Type) = Eval (f x y)
type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) = y
type Eval (Foldr f y (x ': xs) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y (x ': xs) :: a2 -> Type) = Eval (f x (Eval (Foldr f y xs)))
type Eval (Foldr f y ('[] :: [a1]) :: a2 -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('[] :: [a1]) :: a2 -> Type) = y

data UnList :: b -> (a -> b -> Exp b) -> [a] -> Exp b Source #

This is Foldr with its argument flipped.

Instances

Instances details
type Eval (UnList y f xs :: a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (UnList y f xs :: a1 -> Type) = Eval (Foldr f y xs)

data Concat :: t m -> Exp m Source #

Concatenate a collection of elements from a monoid.

Example

Expand

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]])) :: [Natural]
= [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 [Char], Either Double Int]

Instances

Instances details
type Eval (Concat xs :: a -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Concat xs :: a -> Type) = Eval (FoldMap (Pure :: a -> a -> Type) xs)

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.

Instances

Instances details
type Eval (ConcatMap f xs :: [b] -> Type) Source # 
Instance details

Defined in Fcf.Class.Foldable

type Eval (ConcatMap f xs :: [b] -> Type) = Eval (FoldMap f xs)

Unfolding and building

data Unfoldr :: (b -> Exp (Maybe (a, b))) -> b -> Exp [a] Source #

Unfold a generator into a list.

Example

Expand
>>> data ToThree :: Nat -> Exp (Maybe (Nat, Nat))
>>> :{
type instance Eval (ToThree b) =
  If (4 TL.<=? b)
    Nothing
    (Just '(b, b TL.+ 1))
:}
>>> :kind! Eval (Unfoldr ToThree 0)
Eval (Unfoldr ToThree 0) :: [Natural]
= [0, 1, 2, 3]

See also the definition of Replicate.

Instances

Instances details
type Eval (Unfoldr f c :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Unfoldr f c :: [a] -> Type)

data Replicate :: Nat -> a -> Exp [a] Source #

Repeat the same element in a list.

Example

Expand
>>> :kind! Eval (Replicate 4 '("ok", 2))
Eval (Replicate 4 '("ok", 2)) :: [(TL.Symbol, Natural)]
= ['("ok", 2), '("ok", 2), '("ok", 2), '("ok", 2)]

Instances

Instances details
type Eval (Replicate n a2 :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Replicate n a2 :: [a1] -> Type)

Sublists

data Take :: Nat -> [a] -> Exp [a] Source #

Take a prefix of fixed length.

Example

Expand
>>> :kind! Eval (Take 2 [1,2,3,4,5])
Eval (Take 2 [1,2,3,4,5]) :: [Natural]
= [1, 2]

Instances

Instances details
type Eval (Take n as :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Take n as :: [a] -> Type)

data Drop :: Nat -> [a] -> Exp [a] Source #

Drop a prefix of fixed length, evaluate to the remaining suffix.

Example

Expand
>>> :kind! Eval (Drop 2 [1,2,3,4,5])
Eval (Drop 2 [1,2,3,4,5]) :: [Natural]
= [3, 4, 5]

Instances

Instances details
type Eval (Drop n as :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Drop n as :: [a] -> Type)

data TakeWhile :: (a -> Exp Bool) -> [a] -> Exp [a] Source #

Take the longest prefix of elements satisfying a predicate.

Example

Expand
>>> :kind! Eval (TakeWhile ((>=) 3) [1, 2, 3, 4, 5])
Eval (TakeWhile ((>=) 3) [1, 2, 3, 4, 5]) :: [Natural]
= [1, 2, 3]

Instances

Instances details
type Eval (TakeWhile p (x ': xs) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (TakeWhile p (x ': xs) :: [a] -> Type) = Eval (If (Eval (p x)) ('(:) x <$> TakeWhile p xs) (Pure ('[] :: [a])))
type Eval (TakeWhile p ('[] :: [a]) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (TakeWhile p ('[] :: [a]) :: [a] -> Type) = '[] :: [a]

data DropWhile :: (a -> Exp Bool) -> [a] -> Exp [a] Source #

Drop the longest prefix of elements satisfying a predicate, evaluate to the remaining suffix.

Example

Expand

:kind! Eval (DropWhile ((>=) 3) [1, 2, 3, 4, 5]) Eval (DropWhile ((>=) 3) [1, 2, 3, 4, 5]) :: [Natural] = [4, 5]

Instances

Instances details
type Eval (DropWhile p (x ': xs) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (DropWhile p (x ': xs) :: [a] -> Type) = Eval (If (Eval (p x)) (DropWhile p xs) (Pure (x ': xs)))
type Eval (DropWhile p ('[] :: [a]) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (DropWhile p ('[] :: [a]) :: [a] -> Type) = '[] :: [a]

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

Expand
>>> :kind! Eval (Span (Flip (<) 3) [1,2,3,4,1,2])
Eval (Span (Flip (<) 3) [1,2,3,4,1,2]) :: ([Natural], [Natural])
= '([1, 2], [3, 4, 1, 2])
>>> :kind! Eval (Span (Flip (<) 9) [1,2,3])
Eval (Span (Flip (<) 9) [1,2,3]) :: ([Natural], [Natural])
= '([1, 2, 3], '[])
>>> :kind! Eval (Span (Flip (<) 0) [1,2,3])
Eval (Span (Flip (<) 0) [1,2,3]) :: ([Natural], [Natural])
= '( '[], [1, 2, 3])

Instances

Instances details
type Eval (Span p lst :: ([a], [a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Span p lst :: ([a], [a]) -> Type) = '(Eval (TakeWhile p lst), Eval (DropWhile p lst))

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

Expand
>>> :kind! Eval (Break (Flip (>) 3) [1,2,3,4,1,2])
Eval (Break (Flip (>) 3) [1,2,3,4,1,2]) :: ([Natural], [Natural])
= '([1, 2, 3], [4, 1, 2])
>>> :kind! Eval (Break (Flip (<) 9) [1,2,3])
Eval (Break (Flip (<) 9) [1,2,3]) :: ([Natural], [Natural])
= '( '[], [1, 2, 3])
>>> :kind! Eval (Break (Flip (>) 9) [1,2,3])
Eval (Break (Flip (>) 9) [1,2,3]) :: ([Natural], [Natural])
= '([1, 2, 3], '[])

Instances

Instances details
type Eval (Break p lst :: ([a], [a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Break p lst :: ([a], [a]) -> Type) = Eval (Span (Not <=< p) lst)

data Tails :: [a] -> Exp [[a]] Source #

List of suffixes of a list.

Example

Expand
>>> :kind! Eval (Tails [0,1,2,3])
Eval (Tails [0,1,2,3]) :: [[Natural]]
= [[0, 1, 2, 3], [1, 2, 3], [2, 3], '[3]]

Instances

Instances details
type Eval (Tails ('[] :: [a]) :: [[a]] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tails ('[] :: [a]) :: [[a]] -> Type) = '[] :: [[a]]
type Eval (Tails (a2 ': as) :: [[a1]] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Tails (a2 ': as) :: [[a1]] -> Type) = (a2 ': as) ': Eval (Tails as)

Predicates

data IsPrefixOf :: [a] -> [a] -> Exp Bool Source #

Return True when the first list is a prefix of the second.

Example

Expand
>>> :kind! Eval ([0,1,2] `IsPrefixOf` [0,1,2,3,4,5])
Eval ([0,1,2] `IsPrefixOf` [0,1,2,3,4,5]) :: Bool
= True
>>> :kind! Eval ([0,1,2] `IsPrefixOf` [0,1,3,2,4,5])
Eval ([0,1,2] `IsPrefixOf` [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 ([0,1,3,2,4,5] `IsPrefixOf` '[])
Eval ([0,1,3,2,4,5] `IsPrefixOf` '[]) :: Bool
= False

Instances

Instances details
type Eval (IsPrefixOf xs ys :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (IsPrefixOf xs ys :: Bool -> Type)

data IsSuffixOf :: [a] -> [a] -> Exp Bool Source #

Return True when the first list is a suffix of the second.

Example

Expand
>>> :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

Instances details
type Eval (IsSuffixOf xs ys :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (IsSuffixOf xs ys :: Bool -> Type) = Eval (IsPrefixOf ((Reverse :: [a] -> [a] -> Type) @@ xs) ((Reverse :: [a] -> [a] -> Type) @@ ys))

data IsInfixOf :: [a] -> [a] -> Exp Bool Source #

Return True when the first list is contained within the second.

Example

Expand
>>> :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

Instances

Instances details
type Eval (IsInfixOf xs ys :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (IsInfixOf xs ys :: Bool -> Type) = Eval ((Any (IsPrefixOf xs) :: [[a]] -> Bool -> Type) =<< Tails ys)

Searching

data Elem :: a -> [a] -> Exp Bool Source #

Return True if an element is in a list.

See also FindIndex.

Example

Expand
>>> :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

Instances

Instances details
type Eval (Elem a2 as :: Bool -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Elem a2 as :: Bool -> Type) = Eval ((IsJust :: Maybe Nat -> Bool -> Type) =<< FindIndex (TyEq a2 :: a1 -> Bool -> Type) as)

data Lookup :: k -> [(k, b)] -> Exp (Maybe b) Source #

Find an element associated with a key in an association list.

Instances

Instances details
type Eval (Lookup a as :: Maybe b -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Lookup a as :: Maybe b -> Type) = Eval (Map (Snd :: (k, b) -> b -> Type) (Eval (Find ((TyEq a :: k -> Bool -> Type) <=< (Fst :: (k, b) -> k -> Type)) as)))

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

Expand
>>> :kind! Eval (Find (TyEq 0) [1,2,3])
Eval (Find (TyEq 0) [1,2,3]) :: Maybe Natural
= Nothing
>>> :kind! Eval (Find (TyEq 0) [1,2,3,0])
Eval (Find (TyEq 0) [1,2,3,0]) :: Maybe Natural
= Just 0

Instances

Instances details
type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) = Eval (If (Eval (p a2)) (Pure ('Just a2)) (Find p as))

data Filter :: (a -> Exp Bool) -> [a] -> Exp [a] Source #

Keep all elements that satisfy a predicate, remove all that don't.

Example

Expand
>>> :kind! Eval (Filter ((>) 3) [1,2,3,0])
Eval (Filter ((>) 3) [1,2,3,0]) :: [Natural]
= [1, 2, 0]

Instances

Instances details
type Eval (Filter _p ('[] :: [a]) :: [a] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Filter _p ('[] :: [a]) :: [a] -> Type) = '[] :: [a]
type Eval (Filter p (a2 ': as) :: [a1] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Filter p (a2 ': as) :: [a1] -> Type) = Eval (If (Eval (p a2)) ('(:) a2 <$> Filter p as) (Filter p as))

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

Expand
>>> :kind! Eval (Partition ((>=) 35) [20, 30, 40, 50])
Eval (Partition ((>=) 35) [20, 30, 40, 50]) :: ([Natural],
                                                [Natural])
= '([20, 30], [40, 50])

Instances

Instances details
type Eval (Partition p lst :: ([a], [a]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Partition p lst :: ([a], [a]) -> Type)

Indexing lists

data FindIndex :: (a -> Exp Bool) -> [a] -> Exp (Maybe Nat) Source #

Find the index of an element satisfying the predicate.

Example

Expand
>>> :kind! Eval (FindIndex ((<=) 3) [1,2,3,1,2,3])
Eval (FindIndex ((<=) 3) [1,2,3,1,2,3]) :: Maybe Natural
= Just 2
>>> :kind! Eval (FindIndex ((>) 0) [1,2,3,1,2,3])
Eval (FindIndex ((>) 0) [1,2,3,1,2,3]) :: Maybe Natural
= Nothing

Instances

Instances details
type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) = 'Nothing :: Maybe Nat
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) = Eval (If (Eval (p a2)) (Pure ('Just 0)) ((Map ((+) 1) :: Maybe Nat -> Maybe Nat -> Type) =<< FindIndex p as))

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

Expand
>>> :kind! Eval (SetIndex 2 7 [1,2,3])
Eval (SetIndex 2 7 [1,2,3]) :: [Natural]
= [1, 2, 7]

Instances

Instances details
type Eval (SetIndex n a' as :: [k] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (SetIndex n a' as :: [k] -> Type)

Zipping and unzipping

data ZipWith :: (a -> b -> Exp c) -> [a] -> [b] -> Exp [c] Source #

Combine elements of two lists pairwise.

Example

Expand
>>> :kind! Eval (ZipWith (+) [1,2,3] [1,1,1])
Eval (ZipWith (+) [1,2,3] [1,1,1]) :: [Natural]
= [2, 3, 4]

Instances

Instances details
type Eval (ZipWith _f ('[] :: [a]) _bs :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith _f ('[] :: [a]) _bs :: [c] -> Type) = '[] :: [c]
type Eval (ZipWith _f _as ('[] :: [b]) :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith _f _as ('[] :: [b]) :: [c] -> Type) = '[] :: [c]
type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (ZipWith f (a2 ': as) (b2 ': bs) :: [c] -> Type) = Eval (f a2 b2) ': Eval (ZipWith f as bs)

data Zip :: [a] -> [b] -> Exp [(a, b)] Source #

Instances

Instances details
type Eval (Zip as bs :: [(a, b)] -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Zip as bs :: [(a, b)] -> Type) = Eval (ZipWith (Pure2 ('(,) :: a -> b -> (a, b))) as bs)

data Unzip :: Exp [(a, b)] -> Exp ([a], [b]) Source #

Instances

Instances details
type Eval (Unzip as :: ([a], [b]) -> Type) Source # 
Instance details

Defined in Fcf.Data.List

type Eval (Unzip as :: ([a], [b]) -> Type) = Eval (Foldr (Cons2 :: (a, b) -> ([a], [b]) -> ([a], [b]) -> Type) '('[] :: [a], '[] :: [b]) (Eval as))