lens-4.19.1: Lenses, Folds and Traversals

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

Control.Lens.Internal.Level

Contents

Description

This module provides implementation details of the combinators in Control.Lens.Level, which provides for the breadth-first Traversal of an arbitrary Traversal.

Synopsis

Levels

data Level i a Source #

This data type represents a path-compressed copy of one level of a source data structure. We can safely use path-compression because we know the depth of the tree.

Path compression is performed by viewing a Level as a PATRICIA trie of the paths into the structure to leaves at a given depth, similar in many ways to a IntMap, but unlike a regular PATRICIA trie we do not need to store the mask bits merely the depth of the fork.

One invariant of this structure is that underneath a Two node you will not find any Zero nodes, so Zero can only occur at the root.

Constructors

Two !Word !(Level i a) !(Level i a) 
One i a 
Zero 
Instances
TraversableWithIndex i (Level i) Source # 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (i -> a -> f b) -> Level i a -> f (Level i b) Source #

itraversed :: IndexedTraversal i (Level i a) (Level i b) a b Source #

FoldableWithIndex i (Level i) Source # 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Level i a -> m Source #

ifolded :: IndexedFold i (Level i a) a Source #

ifoldr :: (i -> a -> b -> b) -> b -> Level i a -> b Source #

ifoldl :: (i -> b -> a -> b) -> b -> Level i a -> b Source #

ifoldr' :: (i -> a -> b -> b) -> b -> Level i a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> Level i a -> b Source #

FunctorWithIndex i (Level i) Source # 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (i -> a -> b) -> Level i a -> Level i b Source #

imapped :: IndexedSetter i (Level i a) (Level i b) a b Source #

Functor (Level i) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

fmap :: (a -> b) -> Level i a -> Level i b #

(<$) :: a -> Level i b -> Level i a #

Foldable (Level i) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

fold :: Monoid m => Level i m -> m #

foldMap :: Monoid m => (a -> m) -> Level i a -> m #

foldr :: (a -> b -> b) -> b -> Level i a -> b #

foldr' :: (a -> b -> b) -> b -> Level i a -> b #

foldl :: (b -> a -> b) -> b -> Level i a -> b #

foldl' :: (b -> a -> b) -> b -> Level i a -> b #

foldr1 :: (a -> a -> a) -> Level i a -> a #

foldl1 :: (a -> a -> a) -> Level i a -> a #

toList :: Level i a -> [a] #

null :: Level i a -> Bool #

length :: Level i a -> Int #

elem :: Eq a => a -> Level i a -> Bool #

maximum :: Ord a => Level i a -> a #

minimum :: Ord a => Level i a -> a #

sum :: Num a => Level i a -> a #

product :: Num a => Level i a -> a #

Traversable (Level i) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

traverse :: Applicative f => (a -> f b) -> Level i a -> f (Level i b) #

sequenceA :: Applicative f => Level i (f a) -> f (Level i a) #

mapM :: Monad m => (a -> m b) -> Level i a -> m (Level i b) #

sequence :: Monad m => Level i (m a) -> m (Level i a) #

(Eq i, Eq a) => Eq (Level i a) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

(==) :: Level i a -> Level i a -> Bool #

(/=) :: Level i a -> Level i a -> Bool #

(Ord i, Ord a) => Ord (Level i a) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

compare :: Level i a -> Level i a -> Ordering #

(<) :: Level i a -> Level i a -> Bool #

(<=) :: Level i a -> Level i a -> Bool #

(>) :: Level i a -> Level i a -> Bool #

(>=) :: Level i a -> Level i a -> Bool #

max :: Level i a -> Level i a -> Level i a #

min :: Level i a -> Level i a -> Level i a #

(Read i, Read a) => Read (Level i a) Source # 
Instance details

Defined in Control.Lens.Internal.Level

(Show i, Show a) => Show (Level i a) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

showsPrec :: Int -> Level i a -> ShowS #

show :: Level i a -> String #

showList :: [Level i a] -> ShowS #

newtype Deepening i a Source #

This is an illegal Monoid used to construct a single Level.

Constructors

Deepening 

Fields

Instances
Semigroup (Deepening i a) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

(<>) :: Deepening i a -> Deepening i a -> Deepening i a #

sconcat :: NonEmpty (Deepening i a) -> Deepening i a #

stimes :: Integral b => b -> Deepening i a -> Deepening i a #

Monoid (Deepening i a) Source #

This is an illegal Monoid.

Instance details

Defined in Control.Lens.Internal.Level

Methods

mempty :: Deepening i a #

mappend :: Deepening i a -> Deepening i a -> Deepening i a #

mconcat :: [Deepening i a] -> Deepening i a #

deepening :: i -> a -> Deepening i a Source #

Generate the leaf of a given Deepening based on whether or not we're at the correct depth.

newtype Flows i b a Source #

This is an illegal Applicative used to replace the contents of a list of consecutive Level values representing each layer of a structure into the original shape that they were derived from.

Attempting to Flow something back into a shape other than the one it was taken from will fail.

Constructors

Flows 

Fields

Instances
Functor (Flows i b) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

fmap :: (a -> b0) -> Flows i b a -> Flows i b b0 #

(<$) :: a -> Flows i b b0 -> Flows i b a #

Applicative (Flows i b) Source #

This is an illegal Applicative.

Instance details

Defined in Control.Lens.Internal.Level

Methods

pure :: a -> Flows i b a #

(<*>) :: Flows i b (a -> b0) -> Flows i b a -> Flows i b b0 #

liftA2 :: (a -> b0 -> c) -> Flows i b a -> Flows i b b0 -> Flows i b c #

(*>) :: Flows i b a -> Flows i b b0 -> Flows i b b0 #

(<*) :: Flows i b a -> Flows i b b0 -> Flows i b a #

Apply (Flows i b) Source # 
Instance details

Defined in Control.Lens.Internal.Level

Methods

(<.>) :: Flows i b (a -> b0) -> Flows i b a -> Flows i b b0 #

(.>) :: Flows i b a -> Flows i b b0 -> Flows i b b0 #

(<.) :: Flows i b a -> Flows i b b0 -> Flows i b a #

liftF2 :: (a -> b0 -> c) -> Flows i b a -> Flows i b b0 -> Flows i b c #