zipper-0.1: Generic zipper for systems of recursive datatypesSource codeContentsIndex
Generics.MultiRec.Zipper
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Locations
Context frames
Generic zipper class
Interface
Description
The generic zipper.
Synopsis
data Loc
data family Ctx f :: (* -> *) -> (* -> *) -> * -> * -> *
class HFunctor f => Zipper f where
cmap :: (forall b. Ix s b => s b -> r b -> r' b) -> Ctx f s r ix b -> Ctx f s r' ix b
fill :: Ix s b => Ctx f s r ix b -> r b -> f s r ix
first :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> f s r ix -> Maybe a
last :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> f s r ix -> Maybe a
next :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> Ix s b => Ctx f s r ix b -> r b -> Maybe a
prev :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> Ix s b => Ctx f s r ix b -> r b -> Maybe a
enter :: (Ix s ix, Zipper (PF s)) => s ix -> ix -> Loc s I0 ix
down :: Loc s I0 ix -> Maybe (Loc s I0 ix)
down' :: Loc s I0 ix -> Maybe (Loc s I0 ix)
up :: Loc s I0 ix -> Maybe (Loc s I0 ix)
right :: Loc s r ix -> Maybe (Loc s r ix)
left :: Loc s r ix -> Maybe (Loc s r ix)
dfnext :: Loc s I0 ix -> Maybe (Loc s I0 ix)
dfprev :: Loc s I0 ix -> Maybe (Loc s I0 ix)
leave :: Loc s I0 ix -> ix
on :: (forall xi. Ix s xi => s xi -> r xi -> a) -> Loc s r ix -> a
update :: (forall xi. Ix s xi => s xi -> xi -> xi) -> Loc s I0 ix -> Loc s I0 ix
foldZipper :: (forall xi. Ix s xi => s xi -> xi -> r xi) -> Algebra s r -> Loc s I0 ix -> r ix
Locations
data Loc Source
Abstract type of locations. A location contains the current focus and its context. A location is parameterized over the system of datatypes and over the type of the complete value.
Context frames
data family Ctx f :: (* -> *) -> (* -> *) -> * -> * -> *Source
Abstract type of context frames. Not required for the high-level navigation functions.
Generic zipper class
class HFunctor f => Zipper f whereSource
It is in general not necessary to use the generic navigation functions directly. The functions listed in the `Interface' section below are more user-friendly.
Methods
cmap :: (forall b. Ix s b => s b -> r b -> r' b) -> Ctx f s r ix b -> Ctx f s r' ix bSource
fill :: Ix s b => Ctx f s r ix b -> r b -> f s r ixSource
first :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> f s r ix -> Maybe aSource
last :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> f s r ix -> Maybe aSource
next :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> Ix s b => Ctx f s r ix b -> r b -> Maybe aSource
prev :: (forall b. Ix s b => r b -> Ctx f s r ix b -> a) -> Ix s b => Ctx f s r ix b -> r b -> Maybe aSource
show/hide Instances
Zipper U
Zipper (I xi)
Zipper (K a)
(Zipper f, Zipper g) => Zipper (f :+: g)
(Zipper f, Zipper g) => Zipper (f :*: g)
Zipper f => Zipper (f :>: xi)
(Constructor c, Zipper f) => Zipper (C c f)
Interface
enter :: (Ix s ix, Zipper (PF s)) => s ix -> ix -> Loc s I0 ixSource
Start navigating a datastructure. Returns a location that focuses the entire value and has an empty context.
down :: Loc s I0 ix -> Maybe (Loc s I0 ix)Source
Move down to the leftmost child. Returns Nothing if the current focus is a leaf.
down' :: Loc s I0 ix -> Maybe (Loc s I0 ix)Source
Move down to the rightmost child. Returns Nothing if the current focus is a leaf.
up :: Loc s I0 ix -> Maybe (Loc s I0 ix)Source
Move up to the parent. Returns Nothing if the current focus is the root.
right :: Loc s r ix -> Maybe (Loc s r ix)Source
Move to the right sibling. Returns Nothing if the current focus is the rightmost sibling.
left :: Loc s r ix -> Maybe (Loc s r ix)Source
Move to the left sibling. Returns Nothing if the current focus is the leftmost sibling.
dfnext :: Loc s I0 ix -> Maybe (Loc s I0 ix)Source
Move through all positions in depth-first left-to-right order.
dfprev :: Loc s I0 ix -> Maybe (Loc s I0 ix)Source
Move through all positions in depth-first right-to-left order.
leave :: Loc s I0 ix -> ixSource
Return the entire value, independent of the current focus.
on :: (forall xi. Ix s xi => s xi -> r xi -> a) -> Loc s r ix -> aSource
Operate on the current focus. This function can be used to extract the current point of focus.
update :: (forall xi. Ix s xi => s xi -> xi -> xi) -> Loc s I0 ix -> Loc s I0 ixSource
Update the current focus without changing its type.
foldZipper :: (forall xi. Ix s xi => s xi -> xi -> r xi) -> Algebra s r -> Loc s I0 ix -> r ixSource
Most general eliminator. Both on and update can be defined in terms of foldZipper.
Produced by Haddock version 2.4.2