| Copyright | (C) 2009-2013 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Fold
Description
Synopsis
- 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 Choice p => Scan p where Source #
Minimal complete definition
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 #
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 (+) 06
Instances
| Folding L Source # | |
Defined in Data.Fold.L Methods prefix :: Foldable t => t a -> L a b -> L a b Source # prefixOf :: Fold s a -> s -> L a b -> L a b Source # postfix :: Foldable t => L a b -> t a -> L a b Source # postfixOf :: Fold s a -> L a b -> s -> L a b Source # run :: Foldable t => t a -> L a b -> b Source # | |
| Folding L' Source # | |
Defined in Data.Fold.L' Methods prefix :: Foldable t => t a -> L' a b -> L' a b Source # prefixOf :: Fold s a -> s -> L' a b -> L' a b Source # postfix :: Foldable t => L' a b -> t a -> L' a b Source # postfixOf :: Fold s a -> L' a b -> s -> L' a b Source # run :: Foldable t => t a -> L' a b -> b Source # | |
| Folding M Source # | |
Defined in Data.Fold.M Methods prefix :: Foldable t => t a -> M a b -> M a b Source # prefixOf :: Fold s a -> s -> M a b -> M a b Source # postfix :: Foldable t => M a b -> t a -> M a b Source # postfixOf :: Fold s a -> M a b -> s -> M a b Source # run :: Foldable t => t a -> M a b -> b Source # | |
| Folding R Source # | |
Defined in Data.Fold.R Methods prefix :: Foldable t => t a -> R a b -> R a b Source # prefixOf :: Fold s a -> s -> R a b -> R a b Source # postfix :: Foldable t => R a b -> t a -> R a b Source # postfixOf :: Fold s a -> R a b -> s -> R a b Source # run :: Foldable t => t a -> R a b -> b Source # | |
Combinators
beneath :: Profunctor p => Optic p Identity s t a b -> p a b -> p s t Source #
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) |
Instances
| Arrow L1 Source # | |
| ArrowChoice L1 Source # | |
| Profunctor L1 Source # | |
| Costrong L1 Source # | |
| Strong L1 Source # | |
| Corepresentable L1 Source # | |
| Choice L1 Source # | |
| Closed L1 Source # | |
Defined in Data.Fold.L1 | |
| Scan L1 Source # | |
| AsL1' L1 Source # | |
| AsRM1 L1 Source # | |
| Cosieve L1 NonEmpty Source # | |
Defined in Data.Fold.L1 | |
| Monad (L1 a) Source # | |
| Functor (L1 a) Source # | |
| MonadFix (L1 a) Source # | |
Defined in Data.Fold.L1 | |
| Applicative (L1 a) Source # | |
| Distributive (L1 a) Source # | |
| Representable (L1 a) Source # | |
| MonadZip (L1 a) Source # | |
| Apply (L1 a) Source # | |
| Pointed (L1 a) Source # | |
Defined in Data.Fold.L1 | |
| Category L1 Source # | |
| Semigroupoid L1 Source # | |
| MonadReader (NonEmpty a) (L1 a) Source # | |
| type Corep L1 Source # | |
Defined in Data.Fold.L1 | |
| type Rep (L1 a) Source # | |
Defined in Data.Fold.L1 | |
A strict Mealy Machine
Constructors
| forall c. L1' (c -> b) (c -> a -> c) (a -> c) |
Instances
| Arrow L1' Source # | |
| ArrowChoice L1' Source # | |
| Profunctor L1' Source # | |
Defined in Data.Fold.L1' | |
| Costrong L1' Source # | |
| Strong L1' Source # | |
| Corepresentable L1' Source # | |
| Choice L1' Source # | |
| Closed L1' Source # | |
Defined in Data.Fold.L1' | |
| Scan L1' Source # | |
| AsL1' L1' Source # | |
| AsRM1 L1' Source # | |
| Cosieve L1' NonEmpty Source # | |
Defined in Data.Fold.L1' | |
| Monad (L1' a) Source # | |
| Functor (L1' a) Source # | |
| MonadFix (L1' a) Source # | |
Defined in Data.Fold.L1' | |
| Applicative (L1' a) Source # | |
| Distributive (L1' a) Source # | |
| Representable (L1' a) Source # | |
| Apply (L1' a) Source # | |
| Pointed (L1' a) Source # | |
Defined in Data.Fold.L1' | |
| Category L1' Source # | |
| Semigroupoid L1' Source # | |
| MonadReader (NonEmpty a) (L1' a) Source # | |
| type Corep L1' Source # | |
Defined in Data.Fold.L1' | |
| type Rep (L1' a) Source # | |
Defined in Data.Fold.L1' | |
Semigroup Scans
A semigroup reducer
Constructors
| forall m. M1 (m -> b) (a -> m) (m -> m -> m) |
Instances
| Arrow M1 Source # | |
| ArrowChoice M1 Source # | |
| Profunctor M1 Source # | |
| Costrong M1 Source # | |
| Strong M1 Source # | |
| Corepresentable M1 Source # | |
| Choice M1 Source # | |
| Closed M1 Source # | |
Defined in Data.Fold.M1 | |
| Scan M1 Source # | |
| AsRM1 M1 Source # | |
| Cosieve M1 FreeSemigroup Source # | |
Defined in Data.Fold.M1 Methods cosieve :: M1 a b -> FreeSemigroup a -> b # | |
| Monad (M1 a) Source # | |
| Functor (M1 a) Source # | |
| MonadFix (M1 a) Source # | |
Defined in Data.Fold.M1 | |
| Applicative (M1 a) Source # | |
| Distributive (M1 a) Source # | |
| Representable (M1 a) Source # | |
| MonadZip (M1 a) Source # | |
| Apply (M1 a) Source # | |
| Pointed (M1 a) Source # | |
Defined in Data.Fold.M1 | |
| Category M1 Source # | |
| Semigroupoid M1 Source # | |
| MonadReader (FreeSemigroup a) (M1 a) Source # | |
Defined in Data.Fold.M1 Methods ask :: M1 a (FreeSemigroup a) # local :: (FreeSemigroup a -> FreeSemigroup a) -> M1 a a0 -> M1 a a0 # reader :: (FreeSemigroup a -> a0) -> M1 a a0 # | |
| type Corep M1 Source # | |
Defined in Data.Fold.M1 | |
| type Rep (M1 a) Source # | |
Defined in Data.Fold.M1 | |
Right Scans
A reversed Mealy machine
Constructors
| forall c. R1 (c -> b) (a -> c -> c) (a -> c) |
Instances
| Arrow R1 Source # | |
| ArrowChoice R1 Source # | |
| Profunctor R1 Source # | |
| Costrong R1 Source # | |
| Strong R1 Source # | |
| Corepresentable R1 Source # | |
| Choice R1 Source # | |
| Closed R1 Source # | |
Defined in Data.Fold.R1 | |
| Scan R1 Source # | |
| AsRM1 R1 Source # | |
| Cosieve R1 NonEmpty Source # | |
Defined in Data.Fold.R1 | |
| Monad (R1 a) Source # | |
| Functor (R1 a) Source # | |
| MonadFix (R1 a) Source # | |
Defined in Data.Fold.R1 | |
| Applicative (R1 a) Source # | |
| Distributive (R1 a) Source # | |
| Representable (R1 a) Source # | |
| MonadZip (R1 a) Source # | |
| Apply (R1 a) Source # | |
| Pointed (R1 a) Source # | |
Defined in Data.Fold.R1 | |
| Category R1 Source # | |
| Semigroupoid R1 Source # | |
| MonadReader (NonEmpty a) (R1 a) Source # | |
| type Corep R1 Source # | |
Defined in Data.Fold.R1 | |
| type Rep (R1 a) Source # | |
Defined in Data.Fold.R1 | |
Foldings
Left Foldings
A Moore Machine
Constructors
| forall r. L (r -> b) (r -> a -> r) r |
Instances
A strict left fold / strict Moore machine
Constructors
| forall r. L' (r -> b) (r -> a -> r) r |
Instances
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 |
Instances
Right Foldings
right folds / a reversed Moore machine
Constructors
| forall r. R (r -> b) (a -> r -> r) r |
Instances
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
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
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 where Source #
Minimal complete definition
Nothing
Methods
asM :: p a b -> M a b Source #
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 :: p a b -> R a b Source #
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 φ)
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
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 φ)