Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | None |
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.
- data Top
- data p :> a = Zipper (Coil p a) !(Level a)
- type family Zipped h a
- data Coil where
- focus :: SimpleIndexedLens (Tape (h :> a)) (h :> a) a
- zipper :: a -> Top :> a
- tooth :: (a :> b) -> Int
- up :: ((a :> b) :> c) -> a :> b
- left :: (a :> b) -> Maybe (a :> b)
- right :: (a :> b) -> Maybe (a :> b)
- tug :: (a -> Maybe a) -> a -> a
- tugs :: (a -> Maybe a) -> Int -> a -> a
- farthest :: (a -> Maybe a) -> a -> a
- jerks :: (a -> Maybe a) -> Int -> a -> Maybe a
- teeth :: (a :> b) -> Int
- jerkTo :: Int -> (a :> b) -> Maybe (a :> b)
- tugTo :: Int -> (a :> b) -> a :> b
- down :: SimpleLensLike (Context c c) b c -> (a :> b) -> (a :> b) :> c
- within :: SimpleLensLike (Bazaar c c) b c -> (a :> b) -> Maybe ((a :> b) :> c)
- fromWithin :: SimpleLensLike (Bazaar c c) b c -> (a :> b) -> (a :> b) :> c
- class Zipper h a where
- rezip :: Zipper h a => (h :> a) -> Zipped h a
- data Tape k where
- saveTape :: (a :> b) -> Tape (a :> b)
- restoreTape :: Tape (h :> a) -> Zipped h a -> Maybe (h :> a)
- restoreNearTape :: Tape (h :> a) -> Zipped h a -> Maybe (h :> a)
- unsafelyRestoreTape :: Tape (h :> a) -> Zipped h a -> h :> a
- peel :: Coil h a -> Track h a
- data Track where
- restoreTrack :: Track h a -> Zipped h a -> Maybe (h :> a)
- restoreNearTrack :: Track h a -> Zipped h a -> Maybe (h :> a)
- unsafelyRestoreTrack :: Track h a -> Zipped h a -> h :> a
- data Level a = Level !Int [a] a [a]
- levelWidth :: Level a -> Int
- leftLevel :: Level a -> Maybe (Level a)
- left1Level :: Level a -> Level a
- leftmostLevel :: Level a -> Level a
- rightmostLevel :: Level a -> Level a
- rightLevel :: Level a -> Maybe (Level a)
- right1Level :: Level a -> Level a
- focusLevel :: Functor f => (a -> f a) -> Level a -> f (Level a)
- rezipLevel :: Level a -> NonEmpty a
Zippers
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 (
down to String
,Double
)Char
that has an intermediate
crumb for the String
containing the Char
.
This represents the type a zipper will have when it is fully Zipped
back up.
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.
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.
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 :> cfromWithin
::Simple
Lens
b c -> (a :> b) -> a :> b :> cfromWithin
::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.
rezip :: Zipper h a => (h :> a) -> Zipped h aSource
Close something back up that you opened as a zipper
.
Tapes
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.
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
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.
levelWidth :: Level a -> IntSource
How many entries are there in this level?
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
focusLevel
≡extract
focusLevel
::Simple
Lens
(Level
a) a
rezipLevel :: Level a -> NonEmpty aSource
Zip a non-empty list zipper back up, and return the result.