transformations-0.2.0.0: Generic representation of tree transformations

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

Generics.MultiRec.Zipper

Contents

Description

The generic zipper.

Synopsis

Locations and context stacks

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 :: (Fam phi, Zipper phi (PF phi)) => phi ix -> r ix -> Ctxs phi ix r a -> Loc phi r a 

Instances

HFunctor phi (Loc phi) 

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

Constructors

Empty :: Ctxs phi a r a 
Push :: phi a -> Ctx (PF phi) a r ix -> Ctxs phi b r a -> Ctxs phi b r ix 

Instances

Zipper phi (PF phi) => HFunctor phi (Ctxs phi b) 
ShowPath (PF phi) => Show (Path phi t i) 

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) where 
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) where 
data Ctx ((:.:) [] g) = CCL [g r ix] (Ctx g b r ix) [g r ix] 
data Ctx ((:.:) Maybe g) = CCM (Ctx g b r ix) 
data Ctx (C c f) = CC (Ctx f b r ix) 

Contexts and locations are functors

Generic navigation functions

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 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) 

Internal functions

impossible :: a -> b Source