zipper-0.4.1: Generic zipper for families of recursive datatypes

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.MultiRec.Zipper

Contents

Description

The generic zipper.

Synopsis

Locations

data Loc Source

Abstract type of locations. A location contains the current focus and its context. A location is parameterized over the family of datatypes and over the type of the complete value.

Instances

HFunctor phi (Loc phi) 

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 phi f => Zipper phi 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

cmapA :: Applicative a => (forall ix. phi ix -> r ix -> a (r' ix)) -> phi ix -> Ctx f b r ix -> a (Ctx f b r' ix)Source

fill :: phi b -> Ctx f b r ix -> r b -> f r ixSource

first, last :: (forall b. phi b -> r b -> Ctx f b r ix -> a) -> f r ix -> Maybe aSource

next, prev :: (forall b. phi b -> r b -> Ctx f b r ix -> a) -> phi b -> Ctx f b r ix -> r b -> Maybe aSource

Instances

Zipper phi U 
Zipper phi (K a) 
El phi xi => Zipper phi (I xi) 
(Constructor c, Zipper phi f) => Zipper phi (C c f) 
Zipper phi f => Zipper phi (:>: f xi) 
Zipper phi g => Zipper phi (:.: Maybe g) 
Zipper phi g => Zipper phi (:.: [] g) 
(Zipper phi f, Zipper phi g) => Zipper phi (:*: f g) 
(Zipper phi f, Zipper phi g) => Zipper phi (:+: f g) 

Interface

enter :: (Fam phi, Zipper phi (PF phi)) => phi ix -> ix -> Loc phi I0 ixSource

Start navigating a datastructure. Returns a location that focuses the entire value and has an empty context.

down :: Loc phi I0 ix -> Maybe (Loc phi I0 ix)Source

Move down to the leftmost child. Returns Nothing if the current focus is a leaf.

down' :: Loc phi I0 ix -> Maybe (Loc phi I0 ix)Source

Move down to the rightmost child. Returns Nothing if the current focus is a leaf.

up :: Loc phi I0 ix -> Maybe (Loc phi I0 ix)Source

Move up to the parent. Returns Nothing if the current focus is the root.

right :: Loc phi r ix -> Maybe (Loc phi r ix)Source

Move to the right sibling. Returns Nothing if the current focus is the rightmost sibling.

left :: Loc phi r ix -> Maybe (Loc phi r ix)Source

Move to the left sibling. Returns Nothing if the current focus is the leftmost sibling.

dfnext :: Loc phi I0 ix -> Maybe (Loc phi I0 ix)Source

Move through all positions in depth-first left-to-right order.

dfprev :: Loc phi I0 ix -> Maybe (Loc phi I0 ix)Source

Move through all positions in depth-first right-to-left order.

leave :: Loc phi I0 ix -> ixSource

Return the entire value, independent of the current focus.

on :: (forall xi. phi xi -> r xi -> a) -> Loc phi r ix -> aSource

Operate on the current focus. This function can be used to extract the current point of focus.

update :: (forall xi. phi xi -> xi -> xi) -> Loc phi I0 ix -> Loc phi I0 ixSource

Update the current focus without changing its type.

foldZipper :: (forall xi. phi xi -> xi -> r xi) -> Algebra phi r -> Loc phi I0 ix -> r ixSource

Most general eliminator. Both on and update can be defined in terms of foldZipper.