| Portability | non-portable | 
|---|---|
| Stability | experimental | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | None | 
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 slightly 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 Zipperwith its focus at the root.
- Top- :>- Treea- :>a
-  represents a Zipperthat starts with aTreeand descends in a single step to values of typea.
- Top- :>- Treea- :>- Treea- :>- Treea
-  represents a Zipperinto aTreewith an intermediate bookmarkedTree, focusing in yet anotherTree.
Since individual levels of a Zipper are managed by an arbitrary Traversal,
 you can move left and right through the Traversal 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.
- data Top
- data h :> a
- type Zipper = :>
- zipper :: a -> Top :> a
- focus :: SimpleIndexedLens (Tape (h :> a)) (h :> a) a
- focusedContext :: Zipping h a => (h :> a) -> Context a a (Zipped h a)
- upward :: ((h :> s) :> a) -> h :> s
- downward :: SimpleLensLike (Context a a) s a -> (h :> s) -> (h :> s) :> a
- within :: MonadPlus m => SimpleLensLike (Bazaar a a) s a -> (h :> s) -> m ((h :> s) :> a)
- withins :: SimpleLensLike (Bazaar a a) s a -> (h :> s) -> [(h :> s) :> a]
- leftward :: MonadPlus m => (h :> a) -> m (h :> a)
- rightward :: MonadPlus m => (h :> a) -> m (h :> a)
- leftmost :: (a :> b) -> a :> b
- rightmost :: (a :> b) -> a :> b
- tug :: (a -> Maybe a) -> a -> a
- tugs :: (a -> Maybe a) -> Int -> a -> a
- jerks :: Monad m => (a -> m a) -> Int -> a -> m a
- farthest :: (a -> Maybe a) -> a -> a
- tooth :: (h :> a) -> Int
- teeth :: (h :> a) -> Int
- jerkTo :: MonadPlus m => Int -> (h :> a) -> m (h :> a)
- tugTo :: Int -> (h :> a) -> h :> a
- rezip :: Zipping h a => (h :> a) -> Zipped h a
- type family Zipped h a
- class Zipping h a
- data Tape k
- saveTape :: (h :> a) -> Tape (h :> a)
- restoreTape :: MonadPlus m => Tape (h :> a) -> Zipped h a -> m (h :> a)
- restoreNearTape :: MonadPlus m => Tape (h :> a) -> Zipped h a -> m (h :> a)
- fromWithin :: SimpleLensLike (Bazaar a a) s a -> (h :> s) -> (h :> s) :> a
- unsafelyRestoreTape :: Tape (h :> a) -> Zipped h a -> h :> a
Zippers
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 ( down to String,Double)Char that has an intermediate
 crumb for the String containing the Char.
You can construct a zipper into *any* data structure with zipper.
>>>:t zipper (Just "hello")zipper (Just "hello") :: Top :> Maybe [Char]
You can repackage up the contents of a zipper with rezip.
>>>rezip $ zipper 4242
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  doesn't actually contain a value
 of type :> s :> ah  -- as we descend into a level, the previous level is
 unpacked and stored in :> sCoil form. Only one value of type _  exists
 at any particular time for any particular :> _Zipper.
Focusing
Vertical Movement
upward :: ((h :> s) :> a) -> h :> sSource
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.
>>>:t zipper ("hello","world") & downward _1 & fromWithin traverse & upwardzipper ("hello","world") & downward _1 & fromWithin traverse & upward :: (Top :> ([Char], [Char])) :> [Char]
withins :: SimpleLensLike (Bazaar a a) s a -> (h :> s) -> [(h :> s) :> a]Source
Step down into every entry of a Traversal simultaneously.
>>>zipper ("hello","world") & withins both >>= leftward >>= withins traverse >>= rightward <&> focus %~ toUpper <&> rezip[("hEllo","world"),("heLlo","world"),("helLo","world"),("hellO","world")]
withins::SimpleTraversals a -> (h :> s) -> [h :> s :> a]withins::SimpleLenss a -> (h :> s) -> [h :> s :> a]withins::SimpleIsos a -> (h :> s) -> [h :> s :> a]
Lateral Movement
rightward :: MonadPlus m => (h :> a) -> m (h :> a)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" & rightwardTrue
>>>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)
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.
tugf x ≡fromMaybea (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 leftwardtug rightwardzipper,
 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 10True
>>>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
teeth :: (h :> a) -> IntSource
Returns the number of siblings at the current level in the zipper.
teethz>=1
NB: If the current Traversal targets an infinite number of elements then this may not terminate.
>>>zipper ("hello","world") & teeth1
>>>zipper ("hello","world") & fromWithin both & teeth2
>>>zipper ("hello","world") & downward _1 & teeth1
>>>zipper ("hello","world") & downward _1 & fromWithin traverse & teeth5
>>>zipper ("hello","world") & fromWithin (_1.traverse) & teeth5
>>>zipper ("hello","world") & fromWithin (both.traverse) & teeth10
jerkTo :: MonadPlus m => Int -> (h :> a) -> m (h :> a)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.
jerkTon ≡jerksrightwardn .farthestleftward
>>>isNothing $ zipper "not working." & jerkTo 20True
tugTo :: Int -> (h :> a) -> h :> aSource
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
tugTon ≡tugsrightwardn .farthestleftward
>>>rezip $ zipper "not working." & fromWithin traverse & tugTo 100 & focus .~ '!' & tugTo 1 & focus .~ 'u'"nut working!"
Closing the zipper
rezip :: Zipping h a => (h :> a) -> Zipped h aSource
Close something back up that you opened as a Zipper.
Recording
saveTape :: (h :> a) -> Tape (h :> a)Source
Save the current path as as a Tape we can play back later.
restoreTape :: MonadPlus m => Tape (h :> a) -> Zipped h a -> m (h :> a)Source
Restore ourselves to a previously recorded position precisely.
If the position does not exist, then fail.
restoreNearTape :: MonadPlus m => Tape (h :> a) -> Zipped h a -> m (h :> 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 :: SimpleLensLike (Bazaar a a) s a -> (h :> s) -> (h :> s) :> 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::SimpleTraversals a -> (h :> s) -> h :> s :> afromWithin::SimpleLenss a -> (h :> s) -> h :> s :> afromWithin::SimpleIsos a -> (h :> s) -> h :> s :> a
You can reason about this function as if the definition was:
fromWithinl ≡fromJust.withinl
but it is lazier in such a way that if this invariant is violated, some code can still succeed if it is lazy enough in the use of the focused value.
unsafelyRestoreTape :: Tape (h :> a) -> Zipped h a -> h :> 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!