| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | Safe-Inferred |
Data.Fold
Contents
Description
- class Choice p => Scan p where
- prefix1 :: a -> p a b -> p a b
- postfix1 :: p a b -> a -> p a b
- run1 :: a -> p a b -> b
- interspersing :: a -> p a b -> p a b
- class Scan p => Folding p where
- beneath :: Profunctor p => Optic p Identity s t a b -> p a b -> p s t
- data L1 a b = forall c . L1 (c -> b) (c -> a -> c) (a -> c)
- data L1' a b = forall c . L1' (c -> b) (c -> a -> c) (a -> c)
- data M1 a b = forall m . M1 (m -> b) (a -> m) (m -> m -> m)
- data R1 a b = forall c . R1 (c -> b) (a -> c -> c) (a -> c)
- data L a b = forall r . L (r -> b) (r -> a -> r) r
- data L' a b = forall r . L' (r -> b) (r -> a -> r) r
- data M a b = forall m . M (m -> b) (a -> m) (m -> m -> m) m
- data R a b = forall r . R (r -> b) (a -> r -> r) r
- class AsRM1 p where
- class AsRM1 p => AsL1' p where
- class AsRM1 p => AsRM p where
- class (AsRM p, AsL1' p) => AsL' p where
Scaners and Foldings
class Scan p => Folding p whereSource
Methods
prefix :: Foldable t => t a -> p a b -> p a bSource
Partially apply a Folding to some initial input on the left.
prefixOf :: Fold s a -> s -> p a b -> p a bSource
postfix :: Foldable t => p a b -> t a -> p a bSource
postfixOf :: Fold s a -> p a b -> s -> p a bSource
run :: Foldable t => t a -> p a b -> bSource
Apply a Folding to a container full of input:
>>>run ["hello","world"] $ L id (++) []"helloworld"
>>>run [1,2,3] $ L id (+) 06
Combinators
beneath :: Profunctor p => Optic p Identity s t a b -> p a b -> p s tSource
This acts like a generalized notion of "costrength",
when applied to a Folding, causing it to return the
left-most value that fails to match the Prism, or the
result of accumulating rewrapped in the Prism if
everything matches.
>>>run [Left 1, Left 2, Left 3] $ beneath _Left $ R id (+) 0Left 6
>>>run [Left 1, Right 2, Right 3] $ beneath _Left $ R id (+) 0Right 2
beneath :: Prism s t a b -> p a b -> p s t beneath :: Iso s t a b -> p a b -> p s t
Scans
Left Scans
A Mealy Machine
Constructors
| forall c . L1 (c -> b) (c -> a -> c) (a -> c) |
A strict Mealy Machine
Constructors
| forall c . L1' (c -> b) (c -> a -> c) (a -> c) |
Semigroup Scans
A semigroup reducer
Constructors
| forall m . M1 (m -> b) (a -> m) (m -> m -> m) |
Right Scans
A reversed Mealy machine
Constructors
| forall c . R1 (c -> b) (a -> c -> c) (a -> c) |
Foldings
Left Foldings
A Moore Machine
Constructors
| forall r . L (r -> b) (r -> a -> r) r |
Instances
| Profunctor L | |
| Choice L | |
| Folding L | |
| Scan L | |
| AsL' L | We can convert from a lazy left folding to a strict left folding. |
| AsL1' L | |
| AsRM L | We can convert from a lazy left folding to a right or monoidal fold |
| AsRM1 L | |
| Monad (L a) | |
| Functor (L a) | |
| Applicative (L a) | |
| MonadZip (L a) | |
| Comonad (L a) | |
| ComonadApply (L a) | |
| Apply (L a) | |
| Bind (L a) | |
| Extend (L a) |
A strict left fold / strict Moore machine
Constructors
| forall r . L' (r -> b) (r -> a -> r) r |
Instances
| Profunctor L' | |
| Choice L' | |
| Folding L' | |
| Scan L' | |
| AsL' L' | We can convert a lazy fold to itself |
| AsL1' L' | |
| AsRM L' | We can convert from a strict left folding to a right or monoidal fold |
| AsRM1 L' | |
| Monad (L' a) | |
| Functor (L' a) | |
| Applicative (L' a) | |
| MonadZip (L' a) | |
| Comonad (L' a) | |
| ComonadApply (L' a) | |
| Apply (L' a) | |
| Bind (L' a) | |
| Extend (L' a) |
Monoidal Foldings
A foldMap caught in amber. a.k.a. a monoidal reducer
Constructors
| forall m . M (m -> b) (a -> m) (m -> m -> m) m |
Right Foldings
right folds / a reversed Moore machine
Constructors
| forall r . R (r -> b) (a -> r -> r) r |
Homomorphisms
Scan Homomorphisms
We define f to be a scan homomorphism between p and q when:
f :: forall a b. p a b -> q a b
run1xs (f φ) ≡run1xs φprefix1xs (f φ) ≡ f (prefix1xs φ)postfix1(f φ) xs ≡ f (postfix1φ xs)dimapl r (f φ) ≡ f (dimapl r φ)purea ≡ f (purea) f φ<*>f ψ ≡ f (φ<*>ψ)returna ≡ f (returna) f φ>>=f . k ≡ f (φ>>=k)interspersinga (f φ) ≡ f (interspersinga φ)
Furthermore,
and left' (f φ)f ( should agree whenever either answer is left' φ)Right
and right' (f φ)f ( should agree whenever either answer is right' φ)Left
Folding Homomorphisms
We define f to be a folding homomorphism between p and q when
f is a scan homomorphism and additionally we can satisfy:
runxs (f φ) ≡runxs φrunOfl xs (f φ) ≡runOfl xs φprefixxs (f φ) ≡ f (prefixxs φ)prefixOfl xs (f φ) ≡ f (prefixOfl xs φ)postfix(f φ) xs ≡ f (postfixφ xs)postfixOfl (f φ) xs ≡ f (postfixOfl φ xs)extract(f φ) ≡extractφfilteringp (f φ) ≡ f (filteringp φ)
Note: A law including extend is explicitly excluded. To work consistenly
across foldings, use prefix and postfix instead.
class AsRM1 p => AsRM p whereSource
Methods
asM is a folding homomorphism to a monoidal folding
runxs (asMφ) ≡runxs φprefixxs (asMφ) ≡asM(prefixxs φ)prefixOfl xs (asMφ) ≡asM(prefixOfl xs φ)postfix(asMφ) xs ≡asM(postfixφ xs)postfixOfl (asMφ) xs ≡asM(postfixOfl φ xs)left'(asMφ) ≡asM(left'φ)right'(asMφ) ≡asM(right'φ)dimapl r (asMφ) ≡asM(dimapl r φ)extract(asMφ) ≡extractφpurea ≡asM(purea)asMφ<*>asMψ ≡asM(φ<*>ψ)returna ≡asM(returna)asMφ>>=asM. k ≡asM(φ>>=k)filteringp (asMφ) ≡asM(filteringp φ)interspersinga (asMφ) ≡asM(interspersinga φ)
asR is a folding homomorphism to a right folding
runxs (asRφ) ≡runxs φprefixxs (asRφ) ≡asR(prefixxs φ)prefixOfl xs (asRφ) ≡asR(prefixOfl xs φ)postfix(asRφ) xs ≡asR(postfixφ xs)postfixOfl (asRφ) xs ≡asR(postfixOfl φ xs)left'(asRφ) ≡asR(left'φ)right'(asRφ) ≡asR(right'φ)dimapl r (asRφ) ≡asR(dimapl r φ)extract(asRφ) ≡extractφpurea ≡asR(purea)asRφ<*>asRψ ≡asR(φ<*>ψ)returna ≡asR(returna)asRφ>>=asR. k ≡asR(φ>>=k)filteringp (asRφ) ≡asR(filteringp φ)interspersinga (asRφ) ≡asR(interspersinga φ)
class (AsRM p, AsL1' p) => AsL' p whereSource
Methods
asL' is a folding homomorphism to a strict left folding
runxs (asL'φ) ≡runxs φprefixxs (asL'φ) ≡asL'(prefixxs φ)prefixOfl xs (asL'φ) ≡asL'(prefixOfl xs φ)postfix(asL'φ) xs ≡asL'(postfixφ xs)postfixOfl (asL'φ) xs ≡asL'(postfixOfl φ xs)left'(asL'φ) ≡asL'(left'φ)right'(asL'φ) ≡asL'(right'φ)dimapl r (asL'φ) ≡asL'(dimapl r φ)extract(asL'φ) ≡extractφpurea ≡asL'(purea)asL'φ<*>asL'ψ ≡asL'(φ<*>ψ)returna ≡asL'(returna)asL'φ>>=asL'. k ≡asL'(φ>>=k)filteringp (asL'φ) ≡asL'(filteringp φ)interspersinga (asL'φ) ≡asL'(interspersinga φ)