folds-0.3: Beautiful Folding

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

Data.Fold

Contents

Description

 

Synopsis

Scaners and Foldings

class Choice p => Scan p whereSource

Methods

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

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

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

Apply a Folding to a single element of input

interspersing :: a -> p a b -> p a bSource

Instances

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 (+) 0
6

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

filtering :: (a -> Bool) -> p a b -> p a 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

Combinators

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

Scans

Left Scans

data L1 a b Source

A Mealy Machine

Constructors

forall c . L1 (c -> b) (c -> a -> c) (a -> c) 

data L1' a b Source

A strict Mealy Machine

Constructors

forall c . L1' (c -> b) (c -> a -> c) (a -> c) 

Semigroup Scans

data M1 a b Source

A semigroup reducer

Constructors

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

Right Scans

data R1 a b Source

A reversed Mealy machine

Constructors

forall c . R1 (c -> b) (a -> c -> c) (a -> c) 

Foldings

Left Foldings

data L a b Source

A Moore Machine

Constructors

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

Instances

Choice L 
Profunctor L 
Folding L

efficient prefix, leaky postfix

Scan L 
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

A strict left fold / strict Moore machine

Constructors

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

Instances

Choice L' 
Profunctor L' 
Folding L'

efficient prefix, leaky postfix

Scan L' 
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. a.k.a. a monoidal reducer

Constructors

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

Instances

Choice M 
Profunctor M 
Folding M

efficient prefix, efficient postfix

Scan M 
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

right folds / a reversed Moore machine

Constructors

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

Instances

Choice R 
Profunctor R 
Folding R

leaky prefix, efficient postfix

Scan R 
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) 

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
 run1 xs (f φ)        ≡ run1 xs φ
 prefix1 xs (f φ)     ≡ f (prefix1 xs φ)
 postfix1 (f φ) xs    ≡ f (postfix1 φ xs)
 dimap l r (f φ)      ≡ f (dimap l r φ)
 pure a               ≡ f (pure a)
 f φ <*> f ψ          ≡ f (φ <*> ψ)
 return a             ≡ f (return a)
 f φ >>= f . k        ≡ f (φ >>= k)
 interspersing a (f φ) ≡ f (interspersing a φ)

Furthermore,

left' (f φ) and f (left' φ) should agree whenever either answer is Right right' (f φ) and f (right' φ) should agree whenver either answer is 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:

 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)
 extract (f φ)        ≡ extract φ
 filtering p (f φ)     ≡ f (filtering p φ)

Note: A law including extend is explicitly excluded. To work consistenly across foldings, use prefix and postfix instead.

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 φ
 pure a                  ≡ asM (pure a)
 asM φ <*> asM ψ        ≡ asM<*> ψ)
 return a                ≡ asM (return a)
 asM φ >>= asM . k      ≡ asM>>= k)
 filtering p (asM φ)     ≡ asM (filtering p φ)
 interspersing a (asM φ) ≡ asM (interspersing a φ)

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 φ
 pure a                  ≡ asR (pure a)
 asR φ <*> asR ψ        ≡ asR<*> ψ)
 return a                ≡ asR (return a)
 asR φ >>= asR . k      ≡ asR>>= k)
 filtering p (asR φ)     ≡ asR (filtering p φ)
 interspersing a (asR φ) ≡ asR (interspersing a φ)

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 φ
 pure a                   ≡ asL' (pure a)
 asL' φ <*> asL' ψ       ≡ asL'<*> ψ)
 return a                 ≡ asL' (return a)
 asL' φ >>= asL' . k     ≡ asL'>>= k)
 filtering p (asL' φ)     ≡ asL' (filtering p φ)
 interspersing a (asL' φ) ≡ asL' (interspersing a φ)

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