Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.Cassette.Lead
Synopsis
- type NullL s = forall r. K7 Tr r (s -> r)
- type UnL s a = forall r. K7 Tr (a -> r) (s -> r)
- type BinL s a b = forall r. K7 Tr (a -> b -> r) (s -> r)
- type TernL s a b c = forall r. K7 Tr (a -> b -> c -> r) (s -> r)
- type QuaternL s a b c d = forall r. K7 Tr (a -> b -> c -> d -> r) (s -> r)
- isoL :: Iso s s a a -> UnL s a
- prismL :: Prism s s a a -> UnL s a
- catanar :: BinL b a b -> BinL b b [a]
- catanal :: BinL a a b -> BinL a a [b]
- consL :: K7 Tr (a -> [a] -> r) ([a] -> r)
- nilL :: forall a r. K7 Tr r ([a] -> r)
- justL :: K7 Tr (a -> r) (Maybe a -> r)
- nothingL :: forall a r. K7 Tr r (Maybe a -> r)
- unitL :: NullL ()
- pairL :: K7 Tr (a -> b -> r) ((a, b) -> r)
- tripleL :: K7 Tr (a -> b -> c -> r) ((a, b, c) -> r)
- quadrupleL :: K7 Tr (a -> b -> c -> d -> r) ((a, b, c, d) -> r)
Documentation
type UnL s a = forall r. K7 Tr (a -> r) (s -> r) Source #
Unary leads. A lead of type
projects/injects a component UnL
s aa
from/into outer type s
.
type BinL s a b = forall r. K7 Tr (a -> b -> r) (s -> r) Source #
Binary leads. A lead of type
projects/injects components
BinL
s a ba
, b
from/into outer type s
.
type TernL s a b c = forall r. K7 Tr (a -> b -> c -> r) (s -> r) Source #
Ternary leads. A lead of type
projects/injects components
TernL
s a b ca
, b
, c
from/into outer type s
.
type QuaternL s a b c d = forall r. K7 Tr (a -> b -> c -> d -> r) (s -> r) Source #
Quaternary leads. A lead of type
projects/injects
components QuaternL
s a b c da
, b
, c
, d
from/into outer type s
.
catanar :: BinL b a b -> BinL b b [a] Source #
Iterates a one step construction function (resp. deconstruction) function,
i.e. a lead, thus obtaining a right fold (resp. unfold). The resulting lead
is a catamorphism on one side and an anamorpism on the other, hence the name.
The type of this function is the same as that of foldr
, lifted to
cassettes.
catanal :: BinL a a b -> BinL a a [b] Source #
Iterates a one step construction function (resp. deconstruction) function,
i.e. a lead, thus obtaining a left fold (resp. unfold). The resulting lead is
a catamorphism on one side and an anamorpism on the other, hence the name.
The type of this function is the same as that of foldl
, lifted to
cassettes.
quadrupleL :: K7 Tr (a -> b -> c -> d -> r) ((a, b, c, d) -> r) Source #
Construct/destruct a 4-tuple.