folds-0.7.4: Beautiful Folding

Safe HaskellTrustworthy
LanguageHaskell98

Data.Fold.L'

Synopsis

Documentation

data L' a b Source #

A strict left fold / strict Moore machine

Constructors

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 a -> (a -> L' a b) -> L' a b #

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

return :: a -> L' a a #

fail :: String -> L' a a #

Functor (L' a) Source # 

Methods

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

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

MonadFix (L' a) Source # 

Methods

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

Applicative (L' a) Source # 

Methods

pure :: a -> L' a a #

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

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

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

Distributive (L' a) Source # 

Methods

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

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

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

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

Representable (L' a) Source # 

Associated Types

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

Methods

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

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

MonadZip (L' a) Source # 

Methods

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

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

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

Comonad (L' a) Source # 

Methods

extract :: L' a a -> a #

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

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

ComonadApply (L' a) Source # 

Methods

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

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

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

Apply (L' a) Source # 

Methods

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

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

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

Bind (L' a) Source # 

Methods

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

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

Extend (L' a) Source # 

Methods

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

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

MonadReader [a] (L' a) Source # 

Methods

ask :: L' a [a] #

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

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

type Corep L' Source # 
type Corep L' = []
type Rep (L' a) Source # 
type Rep (L' a) = [a]

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

Construct a strict Moore machine from a state valuation and transition function