lens-4.1.2.1: Lenses, Folds and Traversals

Copyright(C) 2012-2014 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellTrustworthy
LanguageHaskell98

Control.Lens.Internal.Magma

Contents

Description

 

Synopsis

Magma

data Magma i t b a where Source

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

TraversableWithIndex i (Magma i t b) 
FoldableWithIndex i (Magma i t b) 
FunctorWithIndex i (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 -> t Source

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

IndexedComonad (Molten i) 
IndexedFunctor (Molten i) 
Sellable (Indexed i) (Molten i) 
Bizarre (Indexed i) (Molten i) 
Functor (Molten i a b) 
Applicative (Molten i a b) 
Apply (Molten i a b) 
(~) * a b => Comonad (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 a Source

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.

In TakingWhile p g a b t, g has a nominal role to avoid exposing an illegal _|_ via Contravariant, while the remaining arguments are degraded to a nominal role by the invariants of Magma

Constructors

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

Instances

Corepresentable p => Bizarre p (TakingWhile p g) 
IndexedFunctor (TakingWhile p f) 
Functor (TakingWhile p f a b) 
Applicative (TakingWhile p f a b) 
Contravariant f => Contravariant (TakingWhile p f a b) 
Apply (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.