lens-3.9.1: Lenses, Folds and Traversals

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

Control.Lens.Internal.Zipper

Contents

Description

This module provides internal types and functions used in the implementation of Control.Lens.Zipper. You shouldn't need to import it directly, and the exported types can be used to break Zipper invariants.

Synopsis

Documentation

>>> :set -XNoOverloadedStrings
>>> import Control.Lens
>>> import Data.Char

Jacket

data Jacket i a Source

A Jacket is used to store the contents of a Traversal in a way that we do not have to re-asocciate the elements. This enables us to more gracefully deal with infinite traversals.

Constructors

Ap Int Bool Bool (Last i) (Jacket i a) (Jacket i a) 
Leaf i a 
Pure 

Instances

size :: Jacket i a -> IntSource

Return the number of children in a jacket

nullLeft :: Jacket i a -> BoolSource

This is an internal function used to check from left-to-right if a Jacket has any Leaf nots or not.

nullRight :: Jacket i a -> BoolSource

This is an internal function used to check from right-to-left if a Jacket has any Leaf nots or not.

maximal :: Jacket i a -> Last iSource

This is used to extract the maximal key from a Jacket. This is used by moveTo and moveToward to seek specific keys, borrowing the asympotic guarantees of the original structure in many cases!

jacketIns :: Bazaar (Indexed i) a b t -> Jacket i aSource

Construct a Jacket from a Bazaar

Flow

newtype Flow i b a Source

Once we've updated a Zipper we need to put the values back into the original shape. Flow is an illegal Applicative that is used to put the values back.

Constructors

Flow 

Fields

runFlow :: Jacket i b -> a
 

Instances

Functor (Flow i b) 
Applicative (Flow i b)

This is an illegal Applicative.

Apply (Flow i b) 

jacketOuts :: Bazaar (Indexed i) a b t -> Jacket j b -> tSource

Given a Bazaar and a Jacket build from that Bazaar with jacketIns, refill the Bazaar with its new contents.

jacket :: AnIndexedTraversal i s t a b -> Lens s t (Jacket i a) (Jacket j b)Source

This is only a valid Lens if you don't change the shape of the Jacket!

Paths

data Path i a Source

A Path into a Jacket that ends at a Leaf.

Constructors

ApL Int Bool Bool (Last i) !(Path i a) !(Jacket i a) 
ApR Int Bool Bool (Last i) !(Jacket i a) !(Path i a) 
Start 

Instances

Functor (Path i) 
(Show i, Show a) => Show (Path i a) 

offset :: Path i a -> IntSource

Calculate the absolute position of the Leaf targeted by a Path.

This can be quite expensive for right-biased traversals such as you receive from a list.

pathsize :: Path i a -> IntSource

Return the total number of children in the Jacket by walking the Path to the root.

Recursion

recompress :: Path i a -> i -> a -> Jacket i aSource

Reconstruct a Jacket from a Path.

startl :: Path i a -> Jacket i a -> r -> (Path i a -> i -> a -> r) -> rSource

Walk down the tree to the leftmost child.

startr :: Path i a -> Jacket i a -> r -> (Path i a -> i -> a -> r) -> rSource

Walk down the tree to the rightmost child.

movel :: Path i a -> Jacket i a -> r -> (Path i a -> i -> a -> r) -> rSource

Move left one Leaf.

mover :: Path i a -> Jacket i a -> r -> (Path i a -> i -> a -> r) -> rSource

Move right one Leaf.

Zippers

data Top Source

This is used to represent the Top of the Zipper.

Every Zipper starts with Top.

e.g. Top :>> a is the type of the trivial Zipper.

Instances

data Zipper h i a Source

This is the type of a Zipper. It visually resembles a "breadcrumb trail" as used in website navigation. Each breadcrumb in the trail represents a level you can move up to.

This type operator associates to the left, so you can use a type like

Top :>> (String,Double) :>> String :>> Char

to represent a Zipper from (String,Double) down to Char that has an intermediate crumb for the String containing the Char.

You can construct a Zipper into *any* data structure with zipper.

You can repackage up the contents of a Zipper with rezip.

>>> rezip $ zipper 42
42

The combinators in this module provide lot of things you can do to the Zipper while you have it open.

Note that a value of type h :> s :> a doesn't actually contain a value of type h :> s -- as we descend into a level, the previous level is unpacked and stored in Coil form. Only one value of type _ :> _ exists at any particular time for any particular Zipper.

Constructors

Ord i => Zipper !(Coil h i a) Int !Int !(Path i a) i a 

Instances

Zipping h s => Zipping (Zipper h i s) a 

data a :@ i Source

An empty data type, used to represent the pairing of a position in a Zipper with an index. See :>.

type family h :> p Source

This type family represents a Zipper with the p variable abstracting over the position and the index, in terms of :@. You can visually see it in type signatures as:

 h :> (a :@ i) = Zipper h i a

type :>> h a = Zipper h Int aSource

Many zippers are indexed by Int keys. This type alias is convenient for reducing syntactic noise for talking about these boring indices.

type family Zipped h a Source

This represents the type a Zipper will have when it is fully Zipped back up.

data Coil t i a whereSource

A Coil is a linked list of the levels above the current one. The length of a Coil is known at compile time.

This is part of the internal structure of a Zipper. You shouldn't need to manipulate this directly.

Constructors

Coil :: Coil Top Int a 
Snoc :: Ord i => !(Coil h j s) -> AnIndexedTraversal' i s a -> Int -> !Int -> !(Path j s) -> j -> (Jacket i a -> s) -> Coil (Zipper h j s) i a 

focus :: IndexedLens' i (Zipper h i a) aSource

This Lens views the current target of the Zipper.

zipper :: a -> Top :>> aSource

Construct a Zipper that can explore anything, and start it at the Top.

focalPoint :: Zipper h i a -> iSource

Return the index of the focus.

tooth :: Zipper h i a -> IntSource

Return the index into the current Traversal within the current level of the Zipper.

jerkTo (tooth l) l = Just

Mnemonically, zippers have a number of teeth within each level. This is which tooth you are currently at.

This is based on ordinal position regardless of the underlying index type. It may be excessively expensive for a list.

focalPoint may be much cheaper if you have a Traversal indexed by ordinal position!

upward :: Ord j => ((h :> (s :@ j)) :> (a :@ i)) -> h :> (s :@ j)Source

Move the Zipper upward, closing the current level and focusing on the parent element.

NB: Attempts to move upward from the Top of the Zipper will fail to typecheck.

rightward :: MonadPlus m => (h :> (a :@ i)) -> m (h :> (a :@ i))Source

Jerk the Zipper one tooth to the rightward within the current Lens or Traversal.

Attempts to move past the start of the current Traversal (or trivially, the current Lens) will return Nothing.

>>> isNothing $ zipper "hello" & rightward
True
>>> zipper "hello" & fromWithin traverse & rightward <&> view focus
'e'
>>> zipper "hello" & fromWithin traverse & rightward <&> focus .~ 'u' <&> rezip
"hullo"
>>> rezip $ zipper (1,2) & fromWithin both & tug rightward & focus .~ 3
(1,3)

leftward :: MonadPlus m => (h :> (a :@ i)) -> m (h :> (a :@ i))Source

Jerk the Zipper leftward one tooth within the current Lens or Traversal.

Attempts to move past the end of the current Traversal (or trivially, the current Lens) will return Nothing.

>>> isNothing $ zipper "hello" & leftward
True

leftmost :: (a :> (b :@ i)) -> a :> (b :@ i)Source

Move to the leftmost position of the current Traversal.

This is just a convenient alias for farthest leftward.

>>> zipper "hello" & fromWithin traverse & leftmost & focus .~ 'a' & rezip
"aello"

rightmost :: (a :> (b :@ i)) -> a :> (b :@ i)Source

Move to the rightmost position of the current Traversal.

This is just a convenient alias for farthest rightward.

>>> zipper "hello" & fromWithin traverse & rightmost & focus .~ 'y' & leftmost & focus .~ 'j' & rezip
"jelly"

tug :: (a -> Maybe a) -> a -> aSource

This allows you to safely tug leftward or tug rightward on a Zipper. This will attempt the move, and stay where it was if it fails.

The more general signature allows its use in other circumstances, however.

tug f x ≡ fromMaybe a (f a)
>>> fmap rezip $ zipper "hello" & within traverse <&> tug leftward <&> focus .~ 'j'
"jello"
>>> fmap rezip $ zipper "hello" & within traverse <&> tug rightward <&> focus .~ 'u'
"hullo"

tugs :: (a -> Maybe a) -> Int -> a -> aSource

This allows you to safely tug leftward or tug rightward multiple times on a Zipper, moving multiple steps in a given direction and stopping at the last place you couldn't move from. This lets you safely move a Zipper, because it will stop at either end.

>>> fmap rezip $ zipper "stale" & within traverse <&> tugs rightward 2 <&> focus .~ 'y'
"style"
>>> rezip $ zipper "want" & fromWithin traverse & tugs rightward 2 & focus .~ 'r' & tugs leftward 100 & focus .~ 'c'
"cart"

farthest :: (a -> Maybe a) -> a -> aSource

Move in a direction as far as you can go, then stop there.

This repeatedly applies a function until it returns Nothing, and then returns the last answer.

>>> fmap rezip $ zipper ("hello","world") & downward _1 & within traverse <&> rightmost <&> focus .~ 'a'
("hella","world")
>>> rezip $ zipper ("hello","there") & fromWithin (both.traverse) & rightmost & focus .~ 'm'
("hello","therm")

jerks :: Monad m => (a -> m a) -> Int -> a -> m aSource

This allows for you to repeatedly pull a Zipper in a given direction, failing if it falls off the end.

>>> isNothing $ zipper "hello" & within traverse >>= jerks rightward 10
True
>>> fmap rezip $ zipper "silly" & within traverse >>= jerks rightward 3 <&> focus .~ 'k'
"silky"

teeth :: (h :> (a :@ i)) -> IntSource

Returns the number of siblings at the current level in the Zipper.

teeth z >= 1

NB: If the current Traversal targets an infinite number of elements then this may not terminate.

This is also a particularly expensive operation to perform on an unbalanced tree.

>>> zipper ("hello","world") & teeth
1
>>> zipper ("hello","world") & fromWithin both & teeth
2
>>> zipper ("hello","world") & downward _1 & teeth
1
>>> zipper ("hello","world") & downward _1 & fromWithin traverse & teeth
5
>>> zipper ("hello","world") & fromWithin (_1.traverse) & teeth
5
>>> zipper ("hello","world") & fromWithin (both.traverse) & teeth
10

jerkTo :: MonadPlus m => Int -> (h :> (a :@ i)) -> m (h :> (a :@ i))Source

Move the Zipper horizontally to the element in the nth position in the current level, absolutely indexed, starting with the farthest leftward as 0.

This returns Nothing if the target element doesn't exist.

jerkTo n ≡ jerks rightward n . farthest leftward
>>> isNothing $ zipper "not working." & jerkTo 20
True

tugTo :: Int -> (h :> (a :@ i)) -> h :> (a :@ i)Source

Move the Zipper horizontally to the element in the nth position of the current level, absolutely indexed, starting with the farthest leftward as 0.

If the element at that position doesn't exist, then this will clamp to the range 0 <= n < teeth.

tugTo n ≡ tugs rightward n . farthest leftward
>>> rezip $ zipper "not working." & fromWithin traverse & tugTo 100 & focus .~ '!' & tugTo 1 & focus .~ 'u'
"nut working!"

moveToward :: i -> (h :> (a :@ i)) -> h :> (a :@ i)Source

Move towards a particular index in the current Traversal.

moveTo :: MonadPlus m => i -> (h :> (a :@ i)) -> m (h :> (a :@ i))Source

Move horizontally to a particular index i in the current Traversal. In the case of simple zippers, the index is Int and we can move between traversals fairly easily:

>>> zipper (42, 32) & fromWithin both & moveTo 0 <&> view focus
42
>>> zipper (42, 32) & fromWithin both & moveTo 1 <&> view focus
32

lensed :: ALens' s a -> IndexedLens' Int s aSource

Construct an IndexedLens from ALens where the index is fixed to 0.

downward :: forall j h s a. ALens' s a -> (h :> (s :@ j)) -> (h :> (s :@ j)) :>> aSource

Step down into a Lens. This is a constrained form of fromWithin for when you know there is precisely one target that can never fail.

 downward :: Lens' s a -> (h :> s) -> h :> s :> a
 downward :: Iso' s a  -> (h :> s) -> h :> s :> a

idownward :: forall i j h s a. Ord i => AnIndexedLens' i s a -> (h :> (s :@ j)) -> (h :> (s :@ j)) :> (a :@ i)Source

Step down into a IndexedLens. This is a constrained form of ifromWithin for when you know there is precisely one target that can never fail.

 idownward :: IndexedLens' i s a -> (h :> s:@j) -> h :> s:@j :> a:@i

within :: MonadPlus m => LensLike' (Indexing (Bazaar' (Indexed Int) a)) s a -> (h :> (s :@ j)) -> m ((h :> (s :@ j)) :>> a)Source

Step down into the leftmost entry of a Traversal.

 within :: Traversal' s a -> (h :> s:@j) -> Maybe (h :> s:@j :>> a)
 within :: Prism' s a     -> (h :> s:@j) -> Maybe (h :> s:@j :>> a)
 within :: Lens' s a      -> (h :> s:@j) -> Maybe (h :> s:@j :>> a)
 within :: Iso' s a       -> (h :> s:@j) -> Maybe (h :> s:@j :>> a)
 within :: MonadPlus m => ATraversal' s a -> (h :> s:@j) -> m (h :> s:@j :>> a)

iwithin :: (MonadPlus m, Ord i) => AnIndexedTraversal' i s a -> (h :> (s :@ j)) -> m ((h :> (s :@ j)) :> (a :@ i))Source

Step down into the leftmost entry of an IndexedTraversal.

Note: The index is assumed to be ordered and must increase monotonically or else you cannot (safely) moveTo or moveToward or use tapes.

 iwithin :: IndexedTraversal' i s a -> (h :> s:@j) -> Maybe (h :> s:@j :> a:@i)
 iwithin :: IndexedLens' i s a      -> (h :> s:@j) -> Maybe (h :> s:@j :> a:@i)
 iwithin :: MonadPlus m => ATraversal' s a -> (h :> s:@j) -> m (h :> s:@j :>> a)

withins :: MonadPlus m => LensLike' (Indexing (Bazaar' (Indexed Int) a)) s a -> (h :> (s :@ j)) -> m ((h :> (s :@ j)) :>> a)Source

Step down into every entry of a Traversal simultaneously.

>>> zipper ("hello","world") & withins both >>= leftward >>= withins traverse >>= rightward <&> focus %~ toUpper <&> rezip :: [(String,String)]
[("hEllo","world"),("heLlo","world"),("helLo","world"),("hellO","world")]
 withins :: Traversal' s a -> (h :> s:@j) -> [h :> s:@j :>> a]
 withins :: Lens' s a      -> (h :> s:@j) -> [h :> s:@j :>> a]
 withins :: Iso' s a       -> (h :> s:@j) -> [h :> s:@j :>> a]

iwithins :: (MonadPlus m, Ord i) => AnIndexedTraversal' i s a -> (h :> (s :@ j)) -> m ((h :> (s :@ j)) :> (a :@ i))Source

Step down into every entry of an IndexedTraversal simultaneously.

Note: The index is assumed to be ordered and must increase monotonically or else you cannot (safely) moveTo or moveToward or use tapes.

 iwithins :: IndexedTraversal' i s a -> (h :> s:@j) -> [h :> s:@j :> a:@i]
 iwithins :: IndexedLens' i s a      -> (h :> s:@j) -> [h :> s:@j :> a:@i]

fromWithin :: LensLike' (Indexing (Bazaar' (Indexed Int) a)) s a -> (h :> (s :@ j)) -> (h :> (s :@ j)) :>> aSource

Unsafely step down into a Traversal that is assumed to be non-empty.

If this invariant is not met then this will usually result in an error!

 fromWithin :: Traversal' s a -> (h :> s:@j) -> h :> s:@j :>> a
 fromWithin :: Lens' s a      -> (h :> s:@j) -> h :> s:@j :>> a
 fromWithin :: Iso' s a       -> (h :> s:@j) -> h :> s:@j :>> a

You can reason about this function as if the definition was:

 fromWithin l ≡ fromJust . within l

ifromWithin :: Ord i => AnIndexedTraversal' i s a -> (h :> (s :@ j)) -> (h :> (s :@ j)) :> (a :@ i)Source

Unsafey step down into an IndexedTraversal that is assumed to be non-empty

If this invariant is not met then this will usually result in an error!

 ifromWithin :: IndexedTraversal' i s a -> (h :> s:@j) -> h :> s:@j :> a:@i
 ifromWithin :: IndexedLens' i s a      -> (h :> s:@j) -> h :> s:@j :> a:@i

You can reason about this function as if the definition was:

 fromWithin l ≡ fromJust . within l

class Zipping h a whereSource

This enables us to pull the Zipper back up to the Top.

Methods

recoil :: Coil h i a -> Jacket i a -> Zipped h aSource

Instances

Zipping Top a 
Zipping h s => Zipping (Zipper h i s) a 

rezip :: Zipping h a => (h :> (a :@ i)) -> Zipped h aSource

Close something back up that you opened as a Zipper.

focusedContext :: (Indexable i p, Zipping h a) => (h :> (a :@ i)) -> Pretext p a a (Zipped h a)Source

Extract the current focus from a Zipper as a Pretext, with access to the current index.

Tapes

data Tape h i a whereSource

A Tape is a recorded path through the (indexed) Traversal chain of a Zipper.

Constructors

Tape :: Track h i a -> i -> Tape h i a 

saveTape :: Zipper h i a -> Tape h i aSource

Save the current path as as a Tape we can play back later.

restoreTape :: MonadPlus m => Tape h i a -> Zipped h a -> m (Zipper h i a)Source

Restore ourselves to a previously recorded position precisely.

If the position does not exist, then fail.

restoreNearTape :: MonadPlus m => Tape h i a -> Zipped h a -> m (Zipper h i a)Source

Restore ourselves to a location near our previously recorded position.

When moving left to right through a Traversal, if this will clamp at each level to the range 0 <= k < teeth, so the only failures will occur when one of the sequence of downward traversals find no targets.

unsafelyRestoreTape :: Tape h i a -> Zipped h a -> Zipper h i aSource

Restore ourselves to a previously recorded position.

This *assumes* that nothing has been done in the meantime to affect the existence of anything on the entire path.

Motions leftward or rightward are clamped, but all traversals included on the Tape are assumed to be non-empty.

Violate these assumptions at your own risk!

Tracks

peel :: Coil h i a -> Track h i aSource

This is used to peel off the path information from a Coil for use when saving the current path for later replay.

data Track t i a whereSource

The Track forms the bulk of a Tape.

Constructors

Track :: Track Top Int a 
Fork :: Ord i => Track h j s -> j -> AnIndexedTraversal' i s a -> Track (Zipper h j s) i a 

restoreTrack :: MonadPlus m => Track h i a -> Zipped h a -> m (Zipper h i a)Source

Restore ourselves to a previously recorded position precisely.

If the position does not exist, then fail.

restoreNearTrack :: MonadPlus m => Track h i a -> Zipped h a -> m (Zipper h i a)Source

Restore ourselves to a location near our previously recorded position.

When moving leftward to rightward through a Traversal, if this will clamp at each level to the range 0 <= k < teeth, so the only failures will occur when one of the sequence of downward traversals find no targets.

unsafelyRestoreTrack :: Track h i a -> Zipped h a -> Zipper h i aSource

Restore ourselves to a previously recorded position.

This *assumes* that nothing has been done in the meantime to affect the existence of anything on the entire Path.

Motions leftward or rightward are clamped, but all traversals included on the Tape are assumed to be non-empty.

Violate these assumptions at your own risk!