Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- data Magma i t b a where
- runMagma :: Magma i t a a -> t
- newtype Molten i a b t = Molten {}
- data Mafic a b t = Mafic Int (Int -> Magma Int t b a)
- runMafic :: Mafic a b t -> Magma Int t b a
- data TakingWhile p g a b t = TakingWhile Bool t (Bool -> Magma () t b (Corep p a))
- runTakingWhile :: Corepresentable p => TakingWhile p f a b t -> Magma () t b (Corep p a)
Magma
data Magma i t b a whereSource
This provides a way to peek at the internal structure of a
Traversal
or IndexedTraversal
MagmaAp :: Magma i (x -> y) b a -> Magma i x b a -> Magma i y b a | |
MagmaPure :: x -> Magma i x b a | |
MagmaFmap :: (x -> y) -> Magma i x b a -> Magma i y b a | |
Magma :: i -> a -> Magma i b b a |
(FunctorWithIndex i (Magma i t b), FoldableWithIndex i (Magma i t b), Traversable (Magma i t b)) => TraversableWithIndex i (Magma i t b) | |
Foldable (Magma i t b) => FoldableWithIndex i (Magma i t b) | |
Functor (Magma i t b) => FunctorWithIndex i (Magma i t b) | |
Functor (Magma i t b) | |
Foldable (Magma i t b) | |
(Functor (Magma i t b), Foldable (Magma i t b)) => Traversable (Magma i t b) | |
(Show i, Show a) => Show (Magma i t b a) |
runMagma :: Magma i t a a -> tSource
Run a Magma
where all the individual leaves have been converted to the
expected type
Molten
This is a a non-reassociating initially encoded version of Bazaar
.
IndexedFunctor (Molten i) => IndexedComonad (Molten i) | |
IndexedFunctor (Molten i) | |
Corepresentable (Indexed i) => Sellable (Indexed i) (Molten i) | |
Profunctor (Indexed i) => Bizarre (Indexed i) (Molten i) | |
Functor (Molten i a b) | |
Functor (Molten i a b) => Applicative (Molten i a b) | |
(Functor (Molten i a b), ~ * a b) => Comonad (Molten i a b) | |
Functor (Molten i a b) => Apply (Molten i a b) |
Mafic
This is used to generate an indexed magma from an unindexed source
By constructing it this way we avoid infinite reassociations in sums where possible.
TakingWhile
data TakingWhile p g a b t Source
This is used to generate an indexed magma from an unindexed source
By constructing it this way we avoid infinite reassociations where possible.
TakingWhile Bool t (Bool -> Magma () t b (Corep p a)) |
(Profunctor p, Corepresentable p) => Bizarre p (TakingWhile p g) | |
IndexedFunctor (TakingWhile p f) | |
Functor (TakingWhile p f a b) | |
Functor (TakingWhile p f a b) => Applicative (TakingWhile p f a b) | |
Functor (TakingWhile p f a b) => Apply (TakingWhile p f a b) | |
(Functor (TakingWhile p f a b), Gettable f) => Gettable (TakingWhile p f a b) |
runTakingWhile :: Corepresentable p => TakingWhile p f a b t -> Magma () t b (Corep p a)Source
Generate a Magma
with leaves only while the predicate holds from left to right.