folds-0.7.1: 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

Instances

Scan L Source 

Methods

prefix1 :: a -> L a b -> L a b Source

postfix1 :: L a b -> a -> L a b Source

run1 :: a -> L a b -> b Source

interspersing :: a -> L a b -> L a b Source

Scan L' Source 

Methods

prefix1 :: a -> L' a b -> L' a b Source

postfix1 :: L' a b -> a -> L' a b Source

run1 :: a -> L' a b -> b Source

interspersing :: a -> L' a b -> L' a b Source

Scan L1 Source 

Methods

prefix1 :: a -> L1 a b -> L1 a b Source

postfix1 :: L1 a b -> a -> L1 a b Source

run1 :: a -> L1 a b -> b Source

interspersing :: a -> L1 a b -> L1 a b Source

Scan L1' Source 

Methods

prefix1 :: a -> L1' a b -> L1' a b Source

postfix1 :: L1' a b -> a -> L1' a b Source

run1 :: a -> L1' a b -> b Source

interspersing :: a -> L1' a b -> L1' a b Source

Scan M Source 

Methods

prefix1 :: a -> M a b -> M a b Source

postfix1 :: M a b -> a -> M a b Source

run1 :: a -> M a b -> b Source

interspersing :: a -> M a b -> M a b Source

Scan M1 Source 

Methods

prefix1 :: a -> M1 a b -> M1 a b Source

postfix1 :: M1 a b -> a -> M1 a b Source

run1 :: a -> M1 a b -> b Source

interspersing :: a -> M1 a b -> M1 a b Source

Scan R Source 

Methods

prefix1 :: a -> R a b -> R a b Source

postfix1 :: R a b -> a -> R a b Source

run1 :: a -> R a b -> b Source

interspersing :: a -> R a b -> R a b Source

Scan R1 Source 

Methods

prefix1 :: a -> R1 a b -> R1 a b Source

postfix1 :: R1 a b -> a -> R1 a b Source

run1 :: a -> R1 a b -> b Source

interspersing :: a -> R1 a b -> R1 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

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

runOf :: Fold s a -> s -> L a b -> b Source

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

Folding L' Source

efficient prefix, leaky postfix

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

runOf :: Fold s a -> s -> L' a b -> b Source

filtering :: (a -> Bool) -> L' a b -> L' a b Source

Folding M Source

efficient prefix, efficient postfix

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

runOf :: Fold s a -> s -> M a b -> b Source

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

Folding R Source

leaky prefix, efficient postfix

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

runOf :: Fold s a -> s -> R a b -> b Source

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

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

data L1 a b Source

A Mealy Machine

Constructors

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

Instances

Arrow L1 Source 

Methods

arr :: (b -> c) -> L1 b c

first :: L1 b c -> L1 (b, d) (c, d)

second :: L1 b c -> L1 (d, b) (d, c)

(***) :: L1 b c -> L1 b' c' -> L1 (b, b') (c, c')

(&&&) :: L1 b c -> L1 b c' -> L1 b (c, c')

ArrowChoice L1 Source 

Methods

left :: L1 b c -> L1 (Either b d) (Either c d)

right :: L1 b c -> L1 (Either d b) (Either d c)

(+++) :: L1 b c -> L1 b' c' -> L1 (Either b b') (Either c c')

(|||) :: L1 b d -> L1 c d -> L1 (Either b c) d

Corepresentable L1 Source 

Associated Types

type Corep (L1 :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep L1 d -> c) -> L1 d c

Profunctor L1 Source 

Methods

dimap :: (a -> b) -> (c -> d) -> L1 b c -> L1 a d

lmap :: (a -> b) -> L1 b c -> L1 a c

rmap :: (b -> c) -> L1 a b -> L1 a c

(#.) :: Coercible * c b => (b -> c) -> L1 a b -> L1 a c

(.#) :: Coercible * b a => L1 b c -> (a -> b) -> L1 a c

Choice L1 Source 

Methods

left' :: L1 a b -> L1 (Either a c) (Either b c)

right' :: L1 a b -> L1 (Either c a) (Either c b)

Closed L1 Source 

Methods

closed :: L1 a b -> L1 (x -> a) (x -> b)

Strong L1 Source 

Methods

first' :: L1 a b -> L1 (a, c) (b, c)

second' :: L1 a b -> L1 (c, a) (c, b)

Costrong L1 Source 

Methods

unfirst :: L1 (a, d) (b, d) -> L1 a b

unsecond :: L1 (d, a) (d, b) -> L1 a b

Scan L1 Source 

Methods

prefix1 :: a -> L1 a b -> L1 a b Source

postfix1 :: L1 a b -> a -> L1 a b Source

run1 :: a -> L1 a b -> b Source

interspersing :: a -> L1 a b -> L1 a b Source

AsL1' L1 Source 

Methods

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

AsRM1 L1 Source 

Methods

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

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

Category * L1 Source 

Methods

id :: L1 a a

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

Cosieve L1 NonEmpty Source 

Methods

cosieve :: L1 a b -> NonEmpty a -> b

Semigroupoid * L1 Source 

Methods

o :: L1 j k1 -> L1 i j -> L1 i k1

Monad (L1 a) Source 

Methods

(>>=) :: L1 a b -> (b -> L1 a c) -> L1 a c

(>>) :: L1 a b -> L1 a c -> L1 a c

return :: b -> L1 a b

fail :: String -> L1 a b

Functor (L1 a) Source 

Methods

fmap :: (b -> c) -> L1 a b -> L1 a c

(<$) :: b -> L1 a c -> L1 a b

MonadFix (L1 a) Source 

Methods

mfix :: (b -> L1 a b) -> L1 a b

Applicative (L1 a) Source 

Methods

pure :: b -> L1 a b

(<*>) :: L1 a (b -> c) -> L1 a b -> L1 a c

(*>) :: L1 a b -> L1 a c -> L1 a c

(<*) :: L1 a b -> L1 a c -> L1 a b

Distributive (L1 a) Source 

Methods

distribute :: Functor f => f (L1 a b) -> L1 a (f b)

collect :: Functor f => (b -> L1 a c) -> f b -> L1 a (f c)

distributeM :: Monad m => m (L1 a b) -> L1 a (m b)

collectM :: Monad m => (b -> L1 a c) -> m b -> L1 a (m c)

Representable (L1 a) Source 

Associated Types

type Rep (L1 a :: * -> *) :: *

Methods

tabulate :: (Rep (L1 a) -> b) -> L1 a b

index :: L1 a b -> Rep (L1 a) -> b

MonadZip (L1 a) Source 

Methods

mzip :: L1 a b -> L1 a c -> L1 a (b, c)

mzipWith :: (b -> c -> d) -> L1 a b -> L1 a c -> L1 a d

munzip :: L1 a (b, c) -> (L1 a b, L1 a c)

Pointed (L1 a) Source 

Methods

point :: b -> L1 a b

Apply (L1 a) Source 

Methods

(<.>) :: L1 a (b -> c) -> L1 a b -> L1 a c

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

(<.) :: L1 a b -> L1 a c -> L1 a b

MonadReader (NonEmpty a) (L1 a) Source 

Methods

ask :: L1 a (NonEmpty a)

local :: (NonEmpty a -> NonEmpty a) -> L1 a b -> L1 a b

reader :: (NonEmpty a -> b) -> L1 a b

type Corep L1 = NonEmpty Source 
type Rep (L1 a) = NonEmpty a Source 

data L1' a b Source

A strict Mealy Machine

Constructors

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

Instances

Arrow L1' Source 

Methods

arr :: (b -> c) -> L1' b c

first :: L1' b c -> L1' (b, d) (c, d)

second :: L1' b c -> L1' (d, b) (d, c)

(***) :: L1' b c -> L1' b' c' -> L1' (b, b') (c, c')

(&&&) :: L1' b c -> L1' b c' -> L1' b (c, c')

ArrowChoice L1' Source 

Methods

left :: L1' b c -> L1' (Either b d) (Either c d)

right :: L1' b c -> L1' (Either d b) (Either d c)

(+++) :: L1' b c -> L1' b' c' -> L1' (Either b b') (Either c c')

(|||) :: L1' b d -> L1' c d -> L1' (Either b c) d

Corepresentable L1' Source 

Associated Types

type Corep (L1' :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep L1' d -> c) -> L1' d c

Profunctor L1' Source 

Methods

dimap :: (a -> b) -> (c -> d) -> L1' b c -> L1' a d

lmap :: (a -> b) -> L1' b c -> L1' a c

rmap :: (b -> c) -> L1' a b -> L1' a c

(#.) :: Coercible * c b => (b -> c) -> L1' a b -> L1' a c

(.#) :: Coercible * b a => L1' b c -> (a -> b) -> L1' a c

Choice L1' Source 

Methods

left' :: L1' a b -> L1' (Either a c) (Either b c)

right' :: L1' a b -> L1' (Either c a) (Either c b)

Closed L1' Source 

Methods

closed :: L1' a b -> L1' (x -> a) (x -> b)

Strong L1' Source 

Methods

first' :: L1' a b -> L1' (a, c) (b, c)

second' :: L1' a b -> L1' (c, a) (c, b)

Costrong L1' Source 

Methods

unfirst :: L1' (a, d) (b, d) -> L1' a b

unsecond :: L1' (d, a) (d, b) -> L1' a b

Scan L1' Source 

Methods

prefix1 :: a -> L1' a b -> L1' a b Source

postfix1 :: L1' a b -> a -> L1' a b Source

run1 :: a -> L1' a b -> b Source

interspersing :: a -> L1' a b -> L1' a b Source

AsL1' L1' Source 

Methods

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

AsRM1 L1' Source 

Methods

asM1 :: L1' a b -> M1 a b Source

asR1 :: L1' a b -> R1 a b Source

Category * L1' Source 

Methods

id :: L1' a a

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

Cosieve L1' NonEmpty Source 

Methods

cosieve :: L1' a b -> NonEmpty a -> b

Semigroupoid * L1' Source 

Methods

o :: L1' j k1 -> L1' i j -> L1' i k1

Monad (L1' a) Source 

Methods

(>>=) :: L1' a b -> (b -> L1' a c) -> L1' a c

(>>) :: L1' a b -> L1' a c -> L1' a c

return :: b -> L1' a b

fail :: String -> L1' a b

Functor (L1' a) Source 

Methods

fmap :: (b -> c) -> L1' a b -> L1' a c

(<$) :: b -> L1' a c -> L1' a b

MonadFix (L1' a) Source 

Methods

mfix :: (b -> L1' a b) -> L1' a b

Applicative (L1' a) Source 

Methods

pure :: b -> L1' a b

(<*>) :: L1' a (b -> c) -> L1' a b -> L1' a c

(*>) :: L1' a b -> L1' a c -> L1' a c

(<*) :: L1' a b -> L1' a c -> L1' a b

Distributive (L1' a) Source 

Methods

distribute :: Functor f => f (L1' a b) -> L1' a (f b)

collect :: Functor f => (b -> L1' a c) -> f b -> L1' a (f c)

distributeM :: Monad m => m (L1' a b) -> L1' a (m b)

collectM :: Monad m => (b -> L1' a c) -> m b -> L1' a (m c)

Representable (L1' a) Source 

Associated Types

type Rep (L1' a :: * -> *) :: *

Methods

tabulate :: (Rep (L1' a) -> b) -> L1' a b

index :: L1' a b -> Rep (L1' a) -> b

Pointed (L1' a) Source 

Methods

point :: b -> L1' a b

Apply (L1' a) Source 

Methods

(<.>) :: L1' a (b -> c) -> L1' a b -> L1' a c

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

(<.) :: L1' a b -> L1' a c -> L1' a b

MonadReader (NonEmpty a) (L1' a) Source 

Methods

ask :: L1' a (NonEmpty a)

local :: (NonEmpty a -> NonEmpty a) -> L1' a b -> L1' a b

reader :: (NonEmpty a -> b) -> L1' a b

type Corep L1' = NonEmpty Source 
type Rep (L1' a) = NonEmpty a Source 

Semigroup Scans

data M1 a b Source

A semigroup reducer

Constructors

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

Instances

Arrow M1 Source 

Methods

arr :: (b -> c) -> M1 b c

first :: M1 b c -> M1 (b, d) (c, d)

second :: M1 b c -> M1 (d, b) (d, c)

(***) :: M1 b c -> M1 b' c' -> M1 (b, b') (c, c')

(&&&) :: M1 b c -> M1 b c' -> M1 b (c, c')

ArrowChoice M1 Source 

Methods

left :: M1 b c -> M1 (Either b d) (Either c d)

right :: M1 b c -> M1 (Either d b) (Either d c)

(+++) :: M1 b c -> M1 b' c' -> M1 (Either b b') (Either c c')

(|||) :: M1 b d -> M1 c d -> M1 (Either b c) d

Corepresentable M1 Source 

Associated Types

type Corep (M1 :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep M1 d -> c) -> M1 d c

Profunctor M1 Source 

Methods

dimap :: (a -> b) -> (c -> d) -> M1 b c -> M1 a d

lmap :: (a -> b) -> M1 b c -> M1 a c

rmap :: (b -> c) -> M1 a b -> M1 a c

(#.) :: Coercible * c b => (b -> c) -> M1 a b -> M1 a c

(.#) :: Coercible * b a => M1 b c -> (a -> b) -> M1 a c

Choice M1 Source 

Methods

left' :: M1 a b -> M1 (Either a c) (Either b c)

right' :: M1 a b -> M1 (Either c a) (Either c b)

Closed M1 Source 

Methods

closed :: M1 a b -> M1 (x -> a) (x -> b)

Strong M1 Source 

Methods

first' :: M1 a b -> M1 (a, c) (b, c)

second' :: M1 a b -> M1 (c, a) (c, b)

Costrong M1 Source 

Methods

unfirst :: M1 (a, d) (b, d) -> M1 a b

unsecond :: M1 (d, a) (d, b) -> M1 a b

Scan M1 Source 

Methods

prefix1 :: a -> M1 a b -> M1 a b Source

postfix1 :: M1 a b -> a -> M1 a b Source

run1 :: a -> M1 a b -> b Source

interspersing :: a -> M1 a b -> M1 a b Source

AsRM1 M1 Source 

Methods

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

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

Category * M1 Source 

Methods

id :: M1 a a

(.) :: M1 b c -> M1 a b -> M1 a c

Cosieve M1 FreeSemigroup Source 

Methods

cosieve :: M1 a b -> FreeSemigroup a -> b

Semigroupoid * M1 Source 

Methods

o :: M1 j k1 -> M1 i j -> M1 i k1

Monad (M1 a) Source 

Methods

(>>=) :: M1 a b -> (b -> M1 a c) -> M1 a c

(>>) :: M1 a b -> M1 a c -> M1 a c

return :: b -> M1 a b

fail :: String -> M1 a b

Functor (M1 a) Source 

Methods

fmap :: (b -> c) -> M1 a b -> M1 a c

(<$) :: b -> M1 a c -> M1 a b

MonadFix (M1 a) Source 

Methods

mfix :: (b -> M1 a b) -> M1 a b

Applicative (M1 a) Source 

Methods

pure :: b -> M1 a b

(<*>) :: M1 a (b -> c) -> M1 a b -> M1 a c

(*>) :: M1 a b -> M1 a c -> M1 a c

(<*) :: M1 a b -> M1 a c -> M1 a b

Distributive (M1 a) Source 

Methods

distribute :: Functor f => f (M1 a b) -> M1 a (f b)

collect :: Functor f => (b -> M1 a c) -> f b -> M1 a (f c)

distributeM :: Monad m => m (M1 a b) -> M1 a (m b)

collectM :: Monad m => (b -> M1 a c) -> m b -> M1 a (m c)

Representable (M1 a) Source 

Associated Types

type Rep (M1 a :: * -> *) :: *

Methods

tabulate :: (Rep (M1 a) -> b) -> M1 a b

index :: M1 a b -> Rep (M1 a) -> b

MonadZip (M1 a) Source 

Methods

mzip :: M1 a b -> M1 a c -> M1 a (b, c)

mzipWith :: (b -> c -> d) -> M1 a b -> M1 a c -> M1 a d

munzip :: M1 a (b, c) -> (M1 a b, M1 a c)

Pointed (M1 a) Source 

Methods

point :: b -> M1 a b

Apply (M1 a) Source 

Methods

(<.>) :: M1 a (b -> c) -> M1 a b -> M1 a c

(.>) :: M1 a b -> M1 a c -> M1 a c

(<.) :: M1 a b -> M1 a c -> M1 a b

MonadReader (FreeSemigroup a) (M1 a) Source 

Methods

ask :: M1 a (FreeSemigroup a)

local :: (FreeSemigroup a -> FreeSemigroup a) -> M1 a b -> M1 a b

reader :: (FreeSemigroup a -> b) -> M1 a b

type Corep M1 = FreeSemigroup Source 
type Rep (M1 a) = FreeSemigroup a Source 

Right Scans

data R1 a b Source

A reversed Mealy machine

Constructors

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

Instances

Arrow R1 Source 

Methods

arr :: (b -> c) -> R1 b c

first :: R1 b c -> R1 (b, d) (c, d)

second :: R1 b c -> R1 (d, b) (d, c)

(***) :: R1 b c -> R1 b' c' -> R1 (b, b') (c, c')

(&&&) :: R1 b c -> R1 b c' -> R1 b (c, c')

ArrowChoice R1 Source 

Methods

left :: R1 b c -> R1 (Either b d) (Either c d)

right :: R1 b c -> R1 (Either d b) (Either d c)

(+++) :: R1 b c -> R1 b' c' -> R1 (Either b b') (Either c c')

(|||) :: R1 b d -> R1 c d -> R1 (Either b c) d

Corepresentable R1 Source 

Associated Types

type Corep (R1 :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep R1 d -> c) -> R1 d c

Profunctor R1 Source 

Methods

dimap :: (a -> b) -> (c -> d) -> R1 b c -> R1 a d

lmap :: (a -> b) -> R1 b c -> R1 a c

rmap :: (b -> c) -> R1 a b -> R1 a c

(#.) :: Coercible * c b => (b -> c) -> R1 a b -> R1 a c

(.#) :: Coercible * b a => R1 b c -> (a -> b) -> R1 a c

Choice R1 Source 

Methods

left' :: R1 a b -> R1 (Either a c) (Either b c)

right' :: R1 a b -> R1 (Either c a) (Either c b)

Closed R1 Source 

Methods

closed :: R1 a b -> R1 (x -> a) (x -> b)

Strong R1 Source 

Methods

first' :: R1 a b -> R1 (a, c) (b, c)

second' :: R1 a b -> R1 (c, a) (c, b)

Costrong R1 Source 

Methods

unfirst :: R1 (a, d) (b, d) -> R1 a b

unsecond :: R1 (d, a) (d, b) -> R1 a b

Scan R1 Source 

Methods

prefix1 :: a -> R1 a b -> R1 a b Source

postfix1 :: R1 a b -> a -> R1 a b Source

run1 :: a -> R1 a b -> b Source

interspersing :: a -> R1 a b -> R1 a b Source

AsRM1 R1 Source 

Methods

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

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

Category * R1 Source 

Methods

id :: R1 a a

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

Cosieve R1 NonEmpty Source 

Methods

cosieve :: R1 a b -> NonEmpty a -> b

Semigroupoid * R1 Source 

Methods

o :: R1 j k1 -> R1 i j -> R1 i k1

Monad (R1 a) Source 

Methods

(>>=) :: R1 a b -> (b -> R1 a c) -> R1 a c

(>>) :: R1 a b -> R1 a c -> R1 a c

return :: b -> R1 a b

fail :: String -> R1 a b

Functor (R1 a) Source 

Methods

fmap :: (b -> c) -> R1 a b -> R1 a c

(<$) :: b -> R1 a c -> R1 a b

MonadFix (R1 a) Source 

Methods

mfix :: (b -> R1 a b) -> R1 a b

Applicative (R1 a) Source 

Methods

pure :: b -> R1 a b

(<*>) :: R1 a (b -> c) -> R1 a b -> R1 a c

(*>) :: R1 a b -> R1 a c -> R1 a c

(<*) :: R1 a b -> R1 a c -> R1 a b

Distributive (R1 a) Source 

Methods

distribute :: Functor f => f (R1 a b) -> R1 a (f b)

collect :: Functor f => (b -> R1 a c) -> f b -> R1 a (f c)

distributeM :: Monad m => m (R1 a b) -> R1 a (m b)

collectM :: Monad m => (b -> R1 a c) -> m b -> R1 a (m c)

Representable (R1 a) Source 

Associated Types

type Rep (R1 a :: * -> *) :: *

Methods

tabulate :: (Rep (R1 a) -> b) -> R1 a b

index :: R1 a b -> Rep (R1 a) -> b

MonadZip (R1 a) Source 

Methods

mzip :: R1 a b -> R1 a c -> R1 a (b, c)

mzipWith :: (b -> c -> d) -> R1 a b -> R1 a c -> R1 a d

munzip :: R1 a (b, c) -> (R1 a b, R1 a c)

Pointed (R1 a) Source 

Methods

point :: b -> R1 a b

Apply (R1 a) Source 

Methods

(<.>) :: R1 a (b -> c) -> R1 a b -> R1 a c

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

(<.) :: R1 a b -> R1 a c -> R1 a b

MonadReader (NonEmpty a) (R1 a) Source 

Methods

ask :: R1 a (NonEmpty a)

local :: (NonEmpty a -> NonEmpty a) -> R1 a b -> R1 a b

reader :: (NonEmpty a -> b) -> R1 a b

type Corep R1 = NonEmpty Source 
type Rep (R1 a) = NonEmpty a Source 

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 

Associated Types

type Corep (L :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep L d -> c) -> L d c

Profunctor L Source 

Methods

dimap :: (a -> b) -> (c -> d) -> L b c -> L a d

lmap :: (a -> b) -> L b c -> L a c

rmap :: (b -> c) -> L a b -> L a c

(#.) :: Coercible * c b => (b -> c) -> L a b -> L a c

(.#) :: Coercible * b a => L b c -> (a -> b) -> L a c

Choice L Source 

Methods

left' :: L a b -> L (Either a c) (Either b c)

right' :: L a b -> L (Either c a) (Either c b)

Closed L Source 

Methods

closed :: L a b -> L (x -> a) (x -> b)

Costrong L Source 

Methods

unfirst :: L (a, d) (b, d) -> L a b

unsecond :: L (d, a) (d, b) -> L a b

Folding L Source

efficient prefix, leaky postfix

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

runOf :: Fold s a -> s -> L a b -> b Source

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

Scan L Source 

Methods

prefix1 :: a -> L a b -> L a b Source

postfix1 :: L a b -> a -> L a b Source

run1 :: a -> L a b -> b Source

interspersing :: a -> L a b -> L a b Source

AsL' L Source

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

Methods

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

AsL1' L Source 

Methods

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

AsRM L Source

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

Methods

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

asR :: L a b -> R a b Source

AsRM1 L Source 

Methods

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

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

Cosieve L [] Source
>>> cosieve (L id (+) 0) [1,2,3]
6

Methods

cosieve :: L a b -> [a] -> b

Monad (L a) Source 

Methods

(>>=) :: L a b -> (b -> L a c) -> L a c

(>>) :: L a b -> L a c -> L a c

return :: b -> L a b

fail :: String -> L a b

Functor (L a) Source 

Methods

fmap :: (b -> c) -> L a b -> L a c

(<$) :: b -> L a c -> L a b

MonadFix (L a) Source 

Methods

mfix :: (b -> L a b) -> L a b

Applicative (L a) Source 

Methods

pure :: b -> L a b

(<*>) :: L a (b -> c) -> L a b -> L a c

(*>) :: L a b -> L a c -> L a c

(<*) :: L a b -> L a c -> L a b

Distributive (L a) Source 

Methods

distribute :: Functor f => f (L a b) -> L a (f b)

collect :: Functor f => (b -> L a c) -> f b -> L a (f c)

distributeM :: Monad m => m (L a b) -> L a (m b)

collectM :: Monad m => (b -> L a c) -> m b -> L a (m c)

Representable (L a) Source 

Associated Types

type Rep (L a :: * -> *) :: *

Methods

tabulate :: (Rep (L a) -> b) -> L a b

index :: L a b -> Rep (L a) -> b

MonadZip (L a) Source 

Methods

mzip :: L a b -> L a c -> L a (b, c)

mzipWith :: (b -> c -> d) -> L a b -> L a c -> L a d

munzip :: L a (b, c) -> (L a b, L a c)

Comonad (L a) Source 

Methods

extract :: L a b -> b

duplicate :: L a b -> L a (L a b)

extend :: (L a b -> c) -> L a b -> L a c

ComonadApply (L a) Source 

Methods

(<@>) :: L a (b -> c) -> L a b -> L a c

(@>) :: L a b -> L a c -> L a c

(<@) :: L a b -> L a c -> L a b

Apply (L a) Source 

Methods

(<.>) :: L a (b -> c) -> L a b -> L a c

(.>) :: L a b -> L a c -> L a c

(<.) :: L a b -> L a c -> L a b

Bind (L a) Source 

Methods

(>>-) :: L a b -> (b -> L a c) -> L a c

join :: L a (L a b) -> L a b

Extend (L a) Source 

Methods

duplicated :: L a b -> L a (L a b)

extended :: (L a b -> c) -> L a b -> L a c

MonadReader [a] (L a) Source 

Methods

ask :: L a [a]

local :: ([a] -> [a]) -> L a b -> L a b

reader :: ([a] -> b) -> L a b

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 

Associated Types

type Corep (L' :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep L' d -> c) -> L' d c

Profunctor L' Source 

Methods

dimap :: (a -> b) -> (c -> d) -> L' b c -> L' a d

lmap :: (a -> b) -> L' b c -> L' a c

rmap :: (b -> c) -> L' a b -> L' a c

(#.) :: Coercible * c b => (b -> c) -> L' a b -> L' a c

(.#) :: Coercible * b a => L' b c -> (a -> b) -> L' a c

Choice L' Source 

Methods

left' :: L' a b -> L' (Either a c) (Either b c)

right' :: L' a b -> L' (Either c a) (Either c b)

Closed L' Source 

Methods

closed :: L' a b -> L' (x -> a) (x -> b)

Costrong L' Source 

Methods

unfirst :: L' (a, d) (b, d) -> L' a b

unsecond :: L' (d, a) (d, b) -> L' a b

Folding L' Source

efficient prefix, leaky postfix

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

runOf :: Fold s a -> s -> L' a b -> b Source

filtering :: (a -> Bool) -> L' a b -> L' a b Source

Scan L' Source 

Methods

prefix1 :: a -> L' a b -> L' a b Source

postfix1 :: L' a b -> a -> L' a b Source

run1 :: a -> L' a b -> b Source

interspersing :: a -> L' a b -> L' a b Source

AsL' L' Source

We can convert a lazy fold to itself

Methods

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

AsL1' L' Source 

Methods

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

AsRM L' Source

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

Methods

asM :: L' a b -> M a b Source

asR :: L' a b -> R a b Source

AsRM1 L' Source 

Methods

asM1 :: L' a b -> M1 a b Source

asR1 :: L' a b -> R1 a b Source

Cosieve L' [] Source 

Methods

cosieve :: L' a b -> [a] -> b

Monad (L' a) Source 

Methods

(>>=) :: L' a b -> (b -> L' a c) -> L' a c

(>>) :: L' a b -> L' a c -> L' a c

return :: b -> L' a b

fail :: String -> L' a b

Functor (L' a) Source 

Methods

fmap :: (b -> c) -> L' a b -> L' a c

(<$) :: b -> L' a c -> L' a b

MonadFix (L' a) Source 

Methods

mfix :: (b -> L' a b) -> L' a b

Applicative (L' a) Source 

Methods

pure :: b -> L' a b

(<*>) :: L' a (b -> c) -> L' a b -> L' a c

(*>) :: L' a b -> L' a c -> L' a c

(<*) :: L' a b -> L' a c -> L' a b

Distributive (L' a) Source 

Methods

distribute :: Functor f => f (L' a b) -> L' a (f b)

collect :: Functor f => (b -> L' a c) -> f b -> L' a (f c)

distributeM :: Monad m => m (L' a b) -> L' a (m b)

collectM :: Monad m => (b -> L' a c) -> m b -> L' a (m c)

Representable (L' a) Source 

Associated Types

type Rep (L' a :: * -> *) :: *

Methods

tabulate :: (Rep (L' a) -> b) -> L' a b

index :: L' a b -> Rep (L' a) -> b

MonadZip (L' a) Source 

Methods

mzip :: L' a b -> L' a c -> L' a (b, c)

mzipWith :: (b -> c -> d) -> L' a b -> L' a c -> L' a d

munzip :: L' a (b, c) -> (L' a b, L' a c)

Comonad (L' a) Source 

Methods

extract :: L' a b -> b

duplicate :: L' a b -> L' a (L' a b)

extend :: (L' a b -> c) -> L' a b -> L' a c

ComonadApply (L' a) Source 

Methods

(<@>) :: L' a (b -> c) -> L' a b -> L' a c

(@>) :: L' a b -> L' a c -> L' a c

(<@) :: L' a b -> L' a c -> L' a b

Apply (L' a) Source 

Methods

(<.>) :: L' a (b -> c) -> L' a b -> L' a c

(.>) :: L' a b -> L' a c -> L' a c

(<.) :: L' a b -> L' a c -> L' a b

Bind (L' a) Source 

Methods

(>>-) :: L' a b -> (b -> L' a c) -> L' a c

join :: L' a (L' a b) -> L' a b

Extend (L' a) Source 

Methods

duplicated :: L' a b -> L' a (L' a b)

extended :: (L' a b -> c) -> L' a b -> L' a c

MonadReader [a] (L' a) Source 

Methods

ask :: L' a [a]

local :: ([a] -> [a]) -> L' a b -> L' a b

reader :: ([a] -> b) -> L' a b

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 

Instances

Corepresentable M Source 

Associated Types

type Corep (M :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep M d -> c) -> M d c

Profunctor M Source 

Methods

dimap :: (a -> b) -> (c -> d) -> M b c -> M a d

lmap :: (a -> b) -> M b c -> M a c

rmap :: (b -> c) -> M a b -> M a c

(#.) :: Coercible * c b => (b -> c) -> M a b -> M a c

(.#) :: Coercible * b a => M b c -> (a -> b) -> M a c

Choice M Source 

Methods

left' :: M a b -> M (Either a c) (Either b c)

right' :: M a b -> M (Either c a) (Either c b)

Closed M Source 

Methods

closed :: M a b -> M (x -> a) (x -> b)

Costrong M Source 

Methods

unfirst :: M (a, d) (b, d) -> M a b

unsecond :: M (d, a) (d, b) -> M a b

Folding M Source

efficient prefix, efficient postfix

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

runOf :: Fold s a -> s -> M a b -> b Source

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

Scan M Source 

Methods

prefix1 :: a -> M a b -> M a b Source

postfix1 :: M a b -> a -> M a b Source

run1 :: a -> M a b -> b Source

interspersing :: a -> M a b -> M a b Source

AsRM M Source

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

Methods

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

asR :: M a b -> R a b Source

AsRM1 M Source 

Methods

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

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

Cosieve M FreeMonoid Source 

Methods

cosieve :: M a b -> FreeMonoid a -> b

Monad (M a) Source 

Methods

(>>=) :: M a b -> (b -> M a c) -> M a c

(>>) :: M a b -> M a c -> M a c

return :: b -> M a b

fail :: String -> M a b

Functor (M a) Source 

Methods

fmap :: (b -> c) -> M a b -> M a c

(<$) :: b -> M a c -> M a b

MonadFix (M a) Source 

Methods

mfix :: (b -> M a b) -> M a b

Applicative (M a) Source 

Methods

pure :: b -> M a b

(<*>) :: M a (b -> c) -> M a b -> M a c

(*>) :: M a b -> M a c -> M a c

(<*) :: M a b -> M a c -> M a b

Distributive (M a) Source 

Methods

distribute :: Functor f => f (M a b) -> M a (f b)

collect :: Functor f => (b -> M a c) -> f b -> M a (f c)

distributeM :: Monad m => m (M a b) -> M a (m b)

collectM :: Monad m => (b -> M a c) -> m b -> M a (m c)

Representable (M a) Source 

Associated Types

type Rep (M a :: * -> *) :: *

Methods

tabulate :: (Rep (M a) -> b) -> M a b

index :: M a b -> Rep (M a) -> b

MonadZip (M a) Source 

Methods

mzip :: M a b -> M a c -> M a (b, c)

mzipWith :: (b -> c -> d) -> M a b -> M a c -> M a d

munzip :: M a (b, c) -> (M a b, M a c)

Comonad (M a) Source 

Methods

extract :: M a b -> b

duplicate :: M a b -> M a (M a b)

extend :: (M a b -> c) -> M a b -> M a c

ComonadApply (M a) Source 

Methods

(<@>) :: M a (b -> c) -> M a b -> M a c

(@>) :: M a b -> M a c -> M a c

(<@) :: M a b -> M a c -> M a b

Apply (M a) Source 

Methods

(<.>) :: M a (b -> c) -> M a b -> M a c

(.>) :: M a b -> M a c -> M a c

(<.) :: M a b -> M a c -> M a b

Bind (M a) Source 

Methods

(>>-) :: M a b -> (b -> M a c) -> M a c

join :: M a (M a b) -> M a b

Extend (M a) Source 

Methods

duplicated :: M a b -> M a (M a b)

extended :: (M a b -> c) -> M a b -> M a c

MonadReader (FreeMonoid a) (M a) Source 

Methods

ask :: M a (FreeMonoid a)

local :: (FreeMonoid a -> FreeMonoid a) -> M a b -> M a b

reader :: (FreeMonoid a -> b) -> M a b

type Corep M = FreeMonoid Source 
type Rep (M a) = FreeMonoid a Source 

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 

Associated Types

type Corep (R :: * -> * -> *) :: * -> *

Methods

cotabulate :: (Corep R d -> c) -> R d c

Profunctor R Source 

Methods

dimap :: (a -> b) -> (c -> d) -> R b c -> R a d

lmap :: (a -> b) -> R b c -> R a c

rmap :: (b -> c) -> R a b -> R a c

(#.) :: Coercible * c b => (b -> c) -> R a b -> R a c

(.#) :: Coercible * b a => R b c -> (a -> b) -> R a c

Choice R Source 

Methods

left' :: R a b -> R (Either a c) (Either b c)

right' :: R a b -> R (Either c a) (Either c b)

Closed R Source 

Methods

closed :: R a b -> R (x -> a) (x -> b)

Costrong R Source 

Methods

unfirst :: R (a, d) (b, d) -> R a b

unsecond :: R (d, a) (d, b) -> R a b

Folding R Source

leaky prefix, efficient postfix

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

runOf :: Fold s a -> s -> R a b -> b Source

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

Scan R Source 

Methods

prefix1 :: a -> R a b -> R a b Source

postfix1 :: R a b -> a -> R a b Source

run1 :: a -> R a b -> b Source

interspersing :: a -> R a b -> R a b Source

AsRM R Source

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

Methods

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

asR :: R a b -> R a b Source

AsRM1 R Source 

Methods

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

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

Cosieve R [] Source 

Methods

cosieve :: R a b -> [a] -> b

Monad (R a) Source 

Methods

(>>=) :: R a b -> (b -> R a c) -> R a c

(>>) :: R a b -> R a c -> R a c

return :: b -> R a b

fail :: String -> R a b

Functor (R a) Source 

Methods

fmap :: (b -> c) -> R a b -> R a c

(<$) :: b -> R a c -> R a b

MonadFix (R a) Source 

Methods

mfix :: (b -> R a b) -> R a b

Applicative (R a) Source 

Methods

pure :: b -> R a b

(<*>) :: R a (b -> c) -> R a b -> R a c

(*>) :: R a b -> R a c -> R a c

(<*) :: R a b -> R a c -> R a b

Distributive (R a) Source 

Methods

distribute :: Functor f => f (R a b) -> R a (f b)

collect :: Functor f => (b -> R a c) -> f b -> R a (f c)

distributeM :: Monad m => m (R a b) -> R a (m b)

collectM :: Monad m => (b -> R a c) -> m b -> R a (m c)

Representable (R a) Source 

Associated Types

type Rep (R a :: * -> *) :: *

Methods

tabulate :: (Rep (R a) -> b) -> R a b

index :: R a b -> Rep (R a) -> b

MonadZip (R a) Source 

Methods

mzip :: R a b -> R a c -> R a (b, c)

mzipWith :: (b -> c -> d) -> R a b -> R a c -> R a d

munzip :: R a (b, c) -> (R a b, R a c)

Comonad (R a) Source 

Methods

extract :: R a b -> b

duplicate :: R a b -> R a (R a b)

extend :: (R a b -> c) -> R a b -> R a c

ComonadApply (R a) Source 

Methods

(<@>) :: R a (b -> c) -> R a b -> R a c

(@>) :: R a b -> R a c -> R a c

(<@) :: R a b -> R a c -> R a b

Apply (R a) Source 

Methods

(<.>) :: R a (b -> c) -> R a b -> R a c

(.>) :: R a b -> R a c -> R a c

(<.) :: R a b -> R a c -> R a b

Bind (R a) Source 

Methods

(>>-) :: R a b -> (b -> R a c) -> R a c

join :: R a (R a b) -> R a b

Extend (R a) Source 

Methods

duplicated :: R a b -> R a (R a b)

extended :: (R a b -> c) -> R a b -> R a c

MonadReader [a] (R a) Source 

Methods

ask :: R a [a]

local :: ([a] -> [a]) -> R a b -> R a b

reader :: ([a] -> b) -> R a b

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

Instances

AsRM1 L Source 

Methods

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

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

AsRM1 L' Source 

Methods

asM1 :: L' a b -> M1 a b Source

asR1 :: L' a b -> R1 a b Source

AsRM1 L1 Source 

Methods

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

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

AsRM1 L1' Source 

Methods

asM1 :: L1' a b -> M1 a b Source

asR1 :: L1' a b -> R1 a b Source

AsRM1 M Source 

Methods

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

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

AsRM1 M1 Source 

Methods

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

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

AsRM1 R Source 

Methods

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

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

AsRM1 R1 Source 

Methods

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

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

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

Instances

AsL1' L Source 

Methods

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

AsL1' L' Source 

Methods

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

AsL1' L1 Source 

Methods

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

AsL1' L1' Source 

Methods

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

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

Methods

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

asR :: L a b -> R a b Source

AsRM L' Source

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

Methods

asM :: L' a b -> M a b Source

asR :: L' a b -> R a b Source

AsRM M Source

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

Methods

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

asR :: M a b -> R a b Source

AsRM R Source

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

Methods

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

asR :: R a b -> R a b Source

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.

Methods

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

AsL' L' Source

We can convert a lazy fold to itself

Methods

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