Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Foldable types.
A minimal implementation of this interface is given by either FoldMap
or
Foldr
, but a default still needs to be given explicitly for the other.
data MyType a = ... {- Some custom Foldable type -} -- Method 1: Implement Foldr, default FoldMap. type instanceEval
(Foldr
f y xs) = ... {- Explicit implementation -} type instanceEval
(FoldMap
f xs) =FoldMapDefault_
f xs {- Default -} -- Method 2: Implement FoldMap, default Foldr. type instanceEval
(FoldMap
f xs) = ... {- Explicit implementation -} type instanceEval
(Foldr
f y xs) =FoldrDefault_
f y xs {- Default -}
Synopsis
- data Foldr :: (a -> b -> Exp b) -> b -> t a -> Exp b
- data FoldMap :: (a -> Exp m) -> t a -> Exp m
- type FoldMapDefault_ f xs = Eval (Foldr (Bicomap f Pure (.<>)) MEmpty xs)
- type FoldrDefault_ f y xs = Eval (UnEndo (Eval (FoldMap (Pure1 Endo <=< Pure1 f) xs)) y)
- data And :: t Bool -> Exp Bool
- data Or :: t Bool -> Exp Bool
- data All :: (a -> Exp Bool) -> t a -> Exp Bool
- data Any :: (a -> Exp Bool) -> t a -> Exp Bool
- data Sum :: t Nat -> Exp Nat
- data Concat :: t m -> Exp m
- data ConcatMap :: (a -> Exp [b]) -> t a -> Exp [b]
Core interface
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 FoldMap :: (a -> Exp m) -> t a -> Exp m Source #
Type-level foldMap
.
Instances
type Eval (FoldMap f (Right x :: Either a3 a1) :: a2 -> Type) Source # | |
type Eval (FoldMap f (Left _a :: Either a3 a1) :: a2 -> Type) Source # | |
type Eval (FoldMap f (Just x) :: a2 -> Type) Source # | |
type Eval (FoldMap f (Nothing :: Maybe a1) :: a2 -> Type) Source # | |
type Eval (FoldMap f (x ': xs) :: a2 -> Type) Source # | |
type Eval (FoldMap f ([] :: [a1]) :: a2 -> Type) Source # | |
Defined in Fcf.Class.Foldable |
Default implementations
type FoldMapDefault_ f xs = Eval (Foldr (Bicomap f Pure (.<>)) MEmpty xs) Source #
Default implementation of FoldMap
.
Usage
To define an instance of FoldMap
for a custom MyType
for which you already have
an instance of Foldr
:
type instanceEval
(FoldMap
f (xs :: MyType a)) =FoldMapDefault_
f xs
Example
>>>
:kind! FoldMapDefault_ Pure '[ 'EQ, 'LT, 'GT ]
FoldMapDefault_ Pure '[ 'EQ, 'LT, 'GT ] :: Ordering = 'LT
type FoldrDefault_ f y xs = Eval (UnEndo (Eval (FoldMap (Pure1 Endo <=< Pure1 f) xs)) y) Source #
Default implementation of Foldr
.
Usage
To define an instance of Foldr
for a custom MyType
for which you already
have an instance of FoldMap
:
type instanceEval
(Foldr
f y (xs :: MyType a)) =FoldrDefault_
f y xs
Example
>>>
:kind! FoldrDefault_ (.<>) 'EQ '[ 'EQ, 'LT, 'GT ]
FoldrDefault_ (.<>) 'EQ '[ 'EQ, 'LT, 'GT ] :: Ordering = 'LT
Derived operations
Predicates
data And :: t Bool -> Exp Bool Source #
Give True
if all of the booleans in the list are True
.
Example
>>>
:kind! Eval (And '[ 'True, 'True])
Eval (And '[ 'True, 'True]) :: Bool = 'True
>>>
:kind! Eval (And '[ 'True, 'True, 'False])
Eval (And '[ 'True, 'True, 'False]) :: Bool = 'False
data Or :: t Bool -> Exp Bool Source #
Give True
if any of the booleans in the list are True
.
Example
>>>
:kind! Eval (Or '[ 'True, 'True])
Eval (Or '[ 'True, 'True]) :: Bool = 'True
>>>
:kind! Eval (Or '[ 'False, 'False])
Eval (Or '[ 'False, 'False]) :: Bool = 'False
data All :: (a -> Exp Bool) -> t a -> Exp Bool Source #
Whether all elements of the list satisfy a predicate.
Note: this identifier conflicts with All
(from Data.Monoid).
Example
>>>
:kind! Eval (All (Flip (<) 6) '[0,1,2,3,4,5])
Eval (All (Flip (<) 6) '[0,1,2,3,4,5]) :: Bool = 'True
>>>
:kind! Eval (All (Flip (<) 5) '[0,1,2,3,4,5])
Eval (All (Flip (<) 5) '[0,1,2,3,4,5]) :: Bool = 'False
data Any :: (a -> Exp Bool) -> t a -> Exp Bool Source #
Whether any element of the list satisfies a predicate.
Note: this identifier conflicts with Any
(from Fcf.Utils),
Any
(from Data.Monoid), and Any
(from GHC.Exts).
Example
>>>
:kind! Eval (Any (Flip (<) 5) '[0,1,2,3,4,5])
Eval (Any (Flip (<) 5) '[0,1,2,3,4,5]) :: Bool = 'True
>>>
:kind! Eval (Any (Flip (<) 0) '[0,1,2,3,4,5])
Eval (Any (Flip (<) 0) '[0,1,2,3,4,5]) :: Bool = 'False
Numbers
data Sum :: t Nat -> Exp Nat Source #
Sum a Nat
-list.
Example
>>>
:kind! Eval (Sum '[1,2,3])
Eval (Sum '[1,2,3]) :: Nat = 6
Lists
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]