Annotations-0.2.1: Constructing, analyzing and destructing annotated trees

Copyright(c) 2008--2009 Universiteit Utrecht
LicenseBSD3
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell98

Annotations.MultiRec.Zipper

Contents

Description

The generic zipper.

Synopsis

Locations

data Loc :: (* -> *) -> ((* -> *) -> * -> *) -> (* -> *) -> * -> * where 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.

Constructors

Loc :: phi ix -> r ix -> Ctxs phi f ix r a -> Loc phi f r a 

Instances

Zipper phi f => HFunctor phi (Loc phi f) 

Context frames

data family Ctx f :: * -> (* -> *) -> * -> * Source

Abstract type of context frames. Not required for the high-level navigation functions.

Instances

Zipper phi f => HFunctor phi (Ctx f b) 
data Ctx U 
data Ctx (I xi) = CId ((:=:) b xi) 
data Ctx (K a) 
data Ctx ((:+:) f g)  
data Ctx ((:*:) f g)
  • = C1 (Ctx f b r ix) (g r ix)
  • | C2 (f r ix) (Ctx g b r ix)
 
data Ctx ((:>:) f xi) = CTag ((:=:) ix xi) (Ctx f b r ix) 
data Ctx (C c f) = CC (Ctx f b r ix) 

data Ctxs :: (* -> *) -> ((* -> *) -> * -> *) -> * -> (* -> *) -> * -> * where Source

Constructors

Empty :: Ctxs phi f a r a 
Push :: phi ix -> Ctx f b r ix -> Ctxs phi f ix r a -> Ctxs phi f b r a 

Instances

Zipper phi f => HFunctor phi (Ctxs phi f b) 

Generic zipper class

class HFunctor phi f => Zipper phi f where Source

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 ix Source

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

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

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 f, Zipper phi g) => Zipper phi ((:*:) f g) 
(Zipper phi f, Zipper phi g) => Zipper phi ((:+:) f g) 

Interface

enter :: Zipper phi f => phi ix -> r ix -> Loc phi f r ix Source

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

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

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

update :: (forall xi. phi xi -> r xi -> r xi) -> Loc phi f r ix -> Loc phi f r ix Source

Update the current focus without changing its type.