lens-3.6.0.4: Lenses, Folds and Traversals

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

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

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 trivial zipper.

Instances

data p :> a Source

This is the type of a Zipper. It visually resembes 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.

Constructors

Zipper (Coil p a) !(Level a) 

Instances

Zipper h b => Zipper (:> h b) c 

type family Zipped h a Source

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

data Coil whereSource

Coil is used internally in the definition of a Zipper.

Constructors

Coil :: Coil Top a 
Snoc :: Coil h b -> !Int -> SimpleLensLike (Bazaar a a) b a -> [b] -> (NonEmpty a -> b) -> [b] -> Coil (h :> b) a 

focus :: SimpleIndexedLens (Tape (h :> a)) (h :> a) aSource

This Lens views the current target of the zipper.

zipper :: a -> Top :> aSource

Construct a zipper that can explore anything.

tooth :: (a :> b) -> IntSource

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

jerkTo (tooth l) l = Just'

up :: ((a :> b) :> c) -> a :> bSource

Move the zipper up, closing the current level and focusing on the parent element.

left :: (a :> b) -> Maybe (a :> b)Source

Pull the zipper left within the current Traversal.

right :: (a :> b) -> Maybe (a :> b)Source

Pull the entry one entry to the right

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

This allows you to safely 'tug left' or 'tug right' on a zipper.

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

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

This allows you to safely 'tug left' or 'tug right' on a zipper, moving multiple steps in a given direction, stopping at the last place you couldn't move from.

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

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

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

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

teeth :: (a :> b) -> 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.

jerkTo :: Int -> (a :> b) -> Maybe (a :> b)Source

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

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

jerkTo n ≡ jerks right n . farthest left

tugTo :: Int -> (a :> b) -> a :> bSource

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

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

tugTo n ≡ tugs right n . farthest left

down :: SimpleLensLike (Context c c) b c -> (a :> b) -> (a :> b) :> cSource

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

 down :: Simple Lens b c -> (a :> b) -> a :> b :> c
 down :: Simple Iso b c  -> (a :> b) -> a :> b :> c

within :: SimpleLensLike (Bazaar c c) b c -> (a :> b) -> Maybe ((a :> b) :> c)Source

Step down into the leftmost entry of a Traversal.

 within :: Simple Traversal b c -> (a :> b) -> Maybe (a :> b :> c)
 within :: Simple Lens b c      -> (a :> b) -> Maybe (a :> b :> c)
 within :: Simple Iso b c       -> (a :> b) -> Maybe (a :> b :> c)

fromWithin :: SimpleLensLike (Bazaar c c) b c -> (a :> b) -> (a :> b) :> cSource

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 :: Simple Traversal b c -> (a :> b) -> a :> b :> c
 fromWithin :: Simple Lens b c      -> (a :> b) -> a :> b :> c
 fromWithin :: Simple Iso b c       -> (a :> b) -> a :> b :> c

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

fromWithin l ≡ fromJust . within l

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.

class Zipper h a whereSource

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

Methods

recoil :: Coil h a -> NonEmpty a -> Zipped h aSource

Instances

Zipper Top a 
Zipper h b => Zipper (:> h b) c 

rezip :: Zipper h a => (h :> a) -> Zipped h aSource

Close something back up that you opened as a zipper.

Tapes

data Tape k whereSource

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

Constructors

Tape :: Track h a -> !Int -> Tape (h :> a) 

saveTape :: (a :> b) -> Tape (a :> b)Source

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

restoreTape :: Tape (h :> a) -> Zipped h a -> Maybe (h :> a)Source

Restore ourselves to a previously recorded position precisely.

If the position does not exist, then fail.

restoreNearTape :: Tape (h :> a) -> Zipped h a -> Maybe (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.

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 left or right 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 a -> Track h 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 whereSource

The Track forms the bulk of a Tape.

Constructors

Track :: Track Top a 
Fork :: Track h b -> !Int -> SimpleLensLike (Bazaar a a) b a -> Track (h :> b) a 

restoreTrack :: Track h a -> Zipped h a -> Maybe (h :> a)Source

Restore ourselves to a previously recorded position precisely.

If the position does not exist, then fail.

restoreNearTrack :: Track h a -> Zipped h a -> Maybe (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.

unsafelyRestoreTrack :: Track 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 left or right are clamped, but all traversals included on the Tape are assumed to be non-empty.

Violate these assumptions at your own risk!

Levels

data Level a Source

A basic non-empty list zipper

All combinators assume the invariant that the length stored matches the number of elements in list of items to the left, and the list of items to the left is stored reversed.

Constructors

Level !Int [a] a [a] 

levelWidth :: Level a -> IntSource

How many entries are there in this level?

leftLevel :: Level a -> Maybe (Level a)Source

Pull the non-empty list zipper left one entry

left1Level :: Level a -> Level aSource

Pull the non-empty list zipper left one entry, stopping at the first entry.

leftmostLevel :: Level a -> Level aSource

Pull the non-empty list zipper all the way to the left.

rightmostLevel :: Level a -> Level aSource

Pul the non-empty list zipper all the way to the right. NB:, when given an infinite list this may not terminate.

rightLevel :: Level a -> Maybe (Level a)Source

Pull the non-empty list zipper right one entry.

right1Level :: Level a -> Level aSource

Pull the non-empty list zipper right one entry, stopping at the last entry.

focusLevel :: Functor f => (a -> f a) -> Level a -> f (Level a)Source

This is a Lens targeting the value that we would extract from the non-empty list zipper.

view focusLevelextract
focusLevel :: Simple Lens (Level a) a

rezipLevel :: Level a -> NonEmpty aSource

Zip a non-empty list zipper back up, and return the result.