folds-0.1: Beautiful Folding

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Inferred

Data.Fold

Contents

Description

 

Synopsis

Foldings

Left Foldings

data L a b Source

Constructors

forall r . L (r -> b) (r -> a -> r) r 

Instances

Choice L 
Profunctor L 
Folding L

efficient prefix, leaky postfix

AsL' L

We can convert from a lazy left folding to a strict left folding.

AsRM L

We can convert from a lazy left folding to a right or monoidal fold

Monad (L a) 
Functor (L a) 
Applicative (L a) 
Comonad (L a) 
ComonadApply (L a) 
Apply (L a) 
Bind (L a) 
Extend (L a) 

data L' a b Source

strict left folds

Constructors

forall r . L' (r -> b) (r -> a -> r) r 

Instances

Choice L' 
Profunctor L' 
Folding L'

efficient prefix, leaky postfix

AsL' L'

We can convert a lazy fold to itself

AsRM L'

We can convert from a strict left folding to a right or monoidal fold

Monad (L' a) 
Functor (L' a) 
Applicative (L' a) 
Comonad (L' a) 
ComonadApply (L' a) 
Apply (L' a) 
Bind (L' a) 
Extend (L' a) 

Monoidal Foldings

data M a b Source

A foldMap caught in amber.

Constructors

forall m . M (m -> b) (a -> m) (m -> m -> m) m 

Instances

Choice M 
Profunctor M 
Folding M

efficient prefix, efficient postfix

AsRM M

We can convert from a monoidal fold to a lazy right fold

Monad (M a) 
Functor (M a) 
Applicative (M a) 
Comonad (M a) 
ComonadApply (M a) 
Apply (M a) 
Bind (M a) 
Extend (M a) 

Right Foldings

data R a b Source

Constructors

forall r . R (r -> b) (a -> r -> r) r 

Instances

Choice R 
Profunctor R 
Folding R

leaky prefix, efficient postfix

AsRM R

We can convert from a lazy right fold to a monoidal fold

Monad (R a) 
Functor (R a) 
Applicative (R a) 
Comonad (R a) 
ComonadApply (R a) 
Apply (R a) 
Bind (R a) 
Extend (R a) 

Folding Combinators

class Choice p => Folding p whereSource

Methods

prefix :: Foldable t => t a -> p a b -> p a bSource

prefix1 :: a -> p a b -> p a bSource

prefixOf :: Fold s a -> s -> p a b -> p a bSource

postfix :: Foldable t => p a b -> t a -> p a bSource

postfix1 :: p a b -> a -> p a bSource

postfixOf :: Fold s a -> p a b -> s -> p a bSource

run :: Foldable t => t a -> p a b -> bSource

run1 :: a -> p a b -> bSource

runOf :: Fold s a -> s -> p a b -> bSource

Instances

Folding L

efficient prefix, leaky postfix

Folding L'

efficient prefix, leaky postfix

Folding M

efficient prefix, efficient postfix

Folding R

leaky prefix, efficient postfix

beneath :: Profunctor p => Overloaded p Mutator s t a b -> p a b -> p s tSource

Lift a Folding into a Prism.

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 (+) 0
Left 6
>>> run [Left 1, Right 2, Right 3] $ beneath _Left $ R id (+) 0
Right 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

Folding Homomorphisms

We define f to be a folding homomorphism betwen p and q when:

 f :: forall a b. p a b -> q a b
 run xs (f φ)         ≡ run xs φ
 runOf l xs (f φ)     ≡ runOf l xs φ
 prefix xs (f φ)      ≡ f (prefix xs φ)
 prefixOf l xs (f φ)  ≡ f (prefixOf l xs φ)
 postfix (f φ) xs     ≡ f (postfix φ xs)
 postfixOf l (f φ) xs ≡ f (postfixOf l φ xs)
 left' (f φ)          ≡ f (left' φ)
 right' (f φ)         ≡ f (right' φ)
 dimap l r (f φ)      ≡ f (dimap l r φ)
 extract (f φ)        ≡ extract φ
 extend h (f φ)       ≡ f (extend (h . f) φ)
 pure a               ≡ f (pure a)
 f φ <*> f ψ          ≡ f (φ <*> ψ)
 return a             ≡ f (return a)
 f φ >>= f . k        ≡ f (φ >>= k)

class AsRM p whereSource

Methods

asM :: p a b -> M a bSource

asM is a folding homomorphism to a monoidal folding

 run xs (asM φ)         ≡ run xs φ
 prefix xs (asM φ)      ≡ asM (prefix xs φ)
 prefixOf l xs (asM φ)  ≡ asM (prefixOf l xs φ)
 postfix (asM φ) xs     ≡ asM (postfix φ xs)
 postfixOf l (asM φ) xs ≡ asM (postfixOf l φ xs)
 left' (asM φ)          ≡ asM (left' φ)
 right' (asM φ)         ≡ asM (right' φ)
 dimap l r (asM φ)      ≡ asM (dimap l r φ)
 extract (asM φ)        ≡ extract φ
 extend h (asM φ)       ≡ asM (extend (h . asM) φ)
 pure a                  ≡ asM (pure a)
 asM φ <*> asM ψ        ≡ asM<*> ψ)
 return a                ≡ asM (return a)
 asM φ >>= asM . k      ≡ asM>>= k)

asR :: p a b -> R a bSource

asR is a folding homomorphism to a right folding

 run xs (asR φ)         ≡ run xs φ
 prefix xs (asR φ)      ≡ asR (prefix xs φ)
 prefixOf l xs (asR φ)  ≡ asR (prefixOf l xs φ)
 postfix (asR φ) xs     ≡ asR (postfix φ xs)
 postfixOf l (asR φ) xs ≡ asR (postfixOf l φ xs)
 left' (asR φ)          ≡ asR (left' φ)
 right' (asR φ)         ≡ asR (right' φ)
 dimap l r (asR φ)      ≡ asR (dimap l r φ)
 extract (asR φ)        ≡ extract φ
 extend h (asR φ)       ≡ asR (extend (h . asR) φ)
 pure a                  ≡ asR (pure a)
 asR φ <*> asR ψ        ≡ asR<*> ψ)
 return a                ≡ asR (return a)
 asR φ >>= asR . k      ≡ asR>>= k)

Instances

AsRM L

We can convert from a lazy left folding to a right or monoidal fold

AsRM L'

We can convert from a strict left folding to a right or monoidal fold

AsRM M

We can convert from a monoidal fold to a lazy right fold

AsRM R

We can convert from a lazy right fold to a monoidal fold

class AsL' p whereSource

Methods

asL' :: p a b -> L' a bSource

asL' is a folding homomorphism to a strict left folding

 run xs (asL' φ)         ≡ run xs φ
 prefix xs (asL' φ)      ≡ asL' (prefix xs φ)
 prefixOf l xs (asL' φ)  ≡ asL' (prefixOf l xs φ)
 postfix (asL' φ) xs     ≡ asL' (postfix φ xs)
 postfixOf l (asL' φ) xs ≡ asL' (postfixOf l φ xs)
 left' (asL' φ)          ≡ asL' (left' φ)
 right' (asL' φ)         ≡ asL' (right' φ)
 dimap l r (asL' φ)      ≡ asL' (dimap l r φ)
 extract (asL' φ)        ≡ extract φ
 extend h (asL' φ)       ≡ asL' (extend (h . asL') φ)
 pure a                   ≡ asL' (pure a)
 asL' φ <*> asL' ψ       ≡ asL'<*> ψ)
 return a                 ≡ asL' (return a)
 asL' φ >>= asL' . k     ≡ asL'>>= k)

Instances

AsL' L

We can convert from a lazy left folding to a strict left folding.

AsL' L'

We can convert a lazy fold to itself