lens-3.9.0.3: Lenses, Folds and Traversals

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

Control.Lens.Zipper

Contents

Description

This module provides a Zipper with fairly strong type checking guarantees.

The code here is inspired by Brandon Simmons' zippo package, but uses a different approach to represent the Zipper that makes the whole thing look like his breadcrumb trail, and can move side-to-side through traversals.

Some examples types:

Top :>> a
represents a trivial Zipper with its focus at the root.
Top :>> Tree a :>> a
represents a Zipper that starts with a Tree and descends in a single step to values of type a.
Top :>> Tree a :>> Tree a :>> Tree a
represents a Zipper into a Tree with an intermediate bookmarked Tree, focusing in yet another Tree.

Since individual levels of a Zipper are managed by an arbitrary IndexedTraversal, you can move left and right through the IndexedTraversal selecting neighboring elements.

>>> zipper ("hello","world") & downward _1 & fromWithin traverse & focus .~ 'J' & rightmost & focus .~ 'y' & rezip
("Jelly","world")

This is particularly powerful when compiled with plate, uniplate or biplate for walking down into self-similar children in syntax trees and other structures.

Given keys in ascending order you can jump directly to a given key with moveTo. When used with traversals for balanced tree-like structures such as an IntMap or Map, searching for a key with moveTo can be done in logarithmic time.

Synopsis

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

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.

data a :@ i Source

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

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.

Instances

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

zipper :: a -> Top :>> aSource

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

Focusing

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

This Lens views the current target of the 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.

Vertical Movement

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.

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]

Lateral Movement

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

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)

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"

Movement Combinators

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"

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"

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")

Absolute Positioning

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!

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!"

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

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

Move towards a particular index in the current Traversal.

Closing the zipper

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

Close something back up that you opened as a Zipper.

type family Zipped h a Source

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

class Zipping h a Source

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

Instances

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

Recording

data Tape h i a Source

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

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.

Unsafe Movement

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

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!