folds-0.7.1: Beautiful Folding

Safe HaskellTrustworthy
LanguageHaskell98

Data.Fold.L

Synopsis

Documentation

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 

unfoldL :: (s -> (b, a -> s)) -> s -> L a b Source

Construct a Moore machine from a state valuation and transition function