folds-0.7: Beautiful Folding

Copyright(C) 2009-2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

Data.Fold

Contents

Description

 

Synopsis

Scaners and Foldings

class Choice p => Scan p where Source

Minimal complete definition

interspersing

Methods

prefix1 :: a -> p a b -> p a b Source

postfix1 :: p a b -> a -> p a b Source

run1 :: a -> p a b -> b Source

Apply a Folding to a single element of input

interspersing :: a -> p a b -> p a b Source

class Scan p => Folding p where Source

Minimal complete definition

prefixOf, postfixOf, runOf, filtering

Methods

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

Partially apply a Folding to some initial input on the left.

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

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

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

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

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 -> b Source

filtering :: (a -> Bool) -> p a b -> p a b Source

Instances

Folding L Source

efficient prefix, leaky postfix

Folding L' Source

efficient prefix, leaky postfix

Folding M Source

efficient prefix, efficient postfix

Folding R Source

leaky prefix, efficient postfix

Combinators

beneath :: Profunctor p => Optic p Identity s t a b -> p a b -> p s t Source

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

Semigroup Scans

Right Scans

Foldings

Left Foldings

data L a b Source

A Moore Machine

Constructors

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

Instances

Corepresentable L Source 
Profunctor L Source 
Choice L Source 
Closed L Source 
Costrong L Source 
Folding L Source

efficient prefix, leaky postfix

Scan L Source 
AsL' L Source

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

AsL1' L Source 
AsRM L Source

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

AsRM1 L Source 
Cosieve L [] Source 
Monad (L a) Source 
Functor (L a) Source 
MonadFix (L a) Source 
Applicative (L a) Source 
Distributive (L a) Source 
Representable (L a) Source 
MonadZip (L a) Source 
Comonad (L a) Source 
ComonadApply (L a) Source 
Apply (L a) Source 
Bind (L a) Source 
Extend (L a) Source 
MonadReader [a] (L a) Source 
type Corep L = [] Source 
type Rep (L a) = [a] Source 

data L' a b Source

A strict left fold / strict Moore machine

Constructors

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

Instances

Corepresentable L' Source 
Profunctor L' Source 
Choice L' Source 
Closed L' Source 
Costrong L' Source 
Folding L' Source

efficient prefix, leaky postfix

Scan L' Source 
AsL' L' Source

We can convert a lazy fold to itself

AsL1' L' Source 
AsRM L' Source

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

AsRM1 L' Source 
Cosieve L' [] Source 
Monad (L' a) Source 
Functor (L' a) Source 
MonadFix (L' a) Source 
Applicative (L' a) Source 
Distributive (L' a) Source 
Representable (L' a) Source 
MonadZip (L' a) Source 
Comonad (L' a) Source 
ComonadApply (L' a) Source 
Apply (L' a) Source 
Bind (L' a) Source 
Extend (L' a) Source 
MonadReader [a] (L' a) Source 
type Corep L' = [] Source 
type Rep (L' a) = [a] Source 

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 

Right Foldings

data R a b Source

right folds / a reversed Moore machine

Constructors

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

Instances

Corepresentable R Source 
Profunctor R Source 
Choice R Source 
Closed R Source 
Costrong R Source 
Folding R Source

leaky prefix, efficient postfix

Scan R Source 
AsRM R Source

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

AsRM1 R Source 
Cosieve R [] Source 
Monad (R a) Source 
Functor (R a) Source 
MonadFix (R a) Source 
Applicative (R a) Source 
Distributive (R a) Source 
Representable (R a) Source 
MonadZip (R a) Source 
Comonad (R a) Source 
ComonadApply (R a) Source 
Apply (R a) Source 
Bind (R a) Source 
Extend (R a) Source 
MonadReader [a] (R a) Source 
type Corep R = [] Source 
type Rep (R a) = [a] Source 

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 whenever either answer is Left

class AsRM1 p where Source

Minimal complete definition

Nothing

Methods

asM1 :: p a b -> M1 a b Source

asM1 is a scan homomorphism to a semigroup reducer

asR1 :: p a b -> R1 a b Source

asM1 is a scan homomorphism to a right scan

class AsRM1 p => AsL1' p where Source

Minimal complete definition

Nothing

Methods

asL1' :: p a b -> L1' a b Source

Scan homomorphism to a strict Mealy machine

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 AsRM1 p => AsRM p where Source

Minimal complete definition

Nothing

Methods

asM :: p a b -> M a b Source

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 b Source

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 Source

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

AsRM L' Source

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

AsRM M Source

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

AsRM R Source

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

class (AsRM p, AsL1' p) => AsL' p where Source

Methods

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

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 Source

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

AsL' L' Source

We can convert a lazy fold to itself