lens-3.8.0.2: Lenses, Folds and Traversals

Portabilitynon-portable
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.Internal.Magma

Contents

Description

 

Synopsis

Magma

data Magma i t b a whereSource

This provides a way to peek at the internal structure of a Traversal or IndexedTraversal

Constructors

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 

Instances

(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

newtype Molten i a b t Source

This is a a non-reassociating initially encoded version of Bazaar.

Constructors

Molten 

Fields

runMolten :: Magma i t b a
 

Instances

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

data Mafic 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 in sums where possible.

Constructors

Mafic Int (Int -> Magma Int t b a) 

runMafic :: Mafic a b t -> Magma Int t b aSource

Generate a Magma using from a prefix sum.

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.

Constructors

TakingWhile Bool t (Bool -> Magma () t b (Corep p a)) 

Instances

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.