Annotations-0.2.2: Constructing, analyzing and destructing annotated trees

Copyright(c) 2008--2009 Universiteit Utrecht
LicenseBSD3
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
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) Source # 

Methods

hmapA :: Applicative a => (forall ix1. phi ix1 -> r ix1 -> a (r' ix1)) -> phi ix -> Loc phi f r ix -> a (Loc phi f r' ix) #

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

Methods

hmapA :: Applicative a => (forall ix1. phi ix1 -> r ix1 -> a (r' ix1)) -> phi ix -> Ctx f b r ix -> a (Ctx f b r' ix) #

data Ctx U Source # 
data Ctx U
data Ctx (I xi) Source # 
data Ctx (I xi) = CId ((:=:) b xi)
data Ctx (K a) Source # 
data Ctx (K a)
data Ctx ((:+:) f g) Source # 
data Ctx ((:+:) f g)
data Ctx ((:*:) f g) Source # 
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) Source # 
data Ctx ((:>:) f xi) = CTag ((:=:) ix xi) (Ctx f b r ix)
data Ctx (C c f) Source # 
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) Source # 

Methods

hmapA :: Applicative a => (forall ix1. phi ix1 -> r ix1 -> a (r' ix1)) -> phi ix -> Ctxs phi f b r ix -> a (Ctxs phi f b r' ix) #

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.

Minimal complete definition

cmapA, fill, first, last, next, prev

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

Methods

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

fill :: phi b -> Ctx U b r ix -> r b -> U r ix Source #

first :: (forall b. phi b -> r b -> Ctx U b r ix -> a) -> U r ix -> Maybe a Source #

last :: (forall b. phi b -> r b -> Ctx U b r ix -> a) -> U r ix -> Maybe a Source #

next :: (forall b. phi b -> r b -> Ctx U b r ix -> a) -> phi b -> Ctx U b r ix -> r b -> Maybe a Source #

prev :: (forall b. phi b -> r b -> Ctx U b r ix -> a) -> phi b -> Ctx U b r ix -> r b -> Maybe a Source #

Zipper phi (K a) Source # 

Methods

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

fill :: phi b -> Ctx (K a) b r ix -> r b -> K a r ix Source #

first :: (forall b. phi b -> r b -> Ctx (K a) b r ix -> a) -> K a r ix -> Maybe a Source #

last :: (forall b. phi b -> r b -> Ctx (K a) b r ix -> a) -> K a r ix -> Maybe a Source #

next :: (forall b. phi b -> r b -> Ctx (K a) b r ix -> a) -> phi b -> Ctx (K a) b r ix -> r b -> Maybe a Source #

prev :: (forall b. phi b -> r b -> Ctx (K a) b r ix -> a) -> phi b -> Ctx (K a) b r ix -> r b -> Maybe a Source #

El phi xi => Zipper phi (I xi) Source # 

Methods

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

fill :: phi b -> Ctx (I xi) b r ix -> r b -> I xi r ix Source #

first :: (forall b. phi b -> r b -> Ctx (I xi) b r ix -> a) -> I xi r ix -> Maybe a Source #

last :: (forall b. phi b -> r b -> Ctx (I xi) b r ix -> a) -> I xi r ix -> Maybe a Source #

next :: (forall b. phi b -> r b -> Ctx (I xi) b r ix -> a) -> phi b -> Ctx (I xi) b r ix -> r b -> Maybe a Source #

prev :: (forall b. phi b -> r b -> Ctx (I xi) b r ix -> a) -> phi b -> Ctx (I xi) b r ix -> r b -> Maybe a Source #

(Constructor c, Zipper phi f) => Zipper phi (C c f) Source # 

Methods

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

fill :: phi b -> Ctx (C c f) b r ix -> r b -> C c f r ix Source #

first :: (forall b. phi b -> r b -> Ctx (C c f) b r ix -> a) -> C c f r ix -> Maybe a Source #

last :: (forall b. phi b -> r b -> Ctx (C c f) b r ix -> a) -> C c f r ix -> Maybe a Source #

next :: (forall b. phi b -> r b -> Ctx (C c f) b r ix -> a) -> phi b -> Ctx (C c f) b r ix -> r b -> Maybe a Source #

prev :: (forall b. phi b -> r b -> Ctx (C c f) b r ix -> a) -> phi b -> Ctx (C c f) b r ix -> r b -> Maybe a Source #

Zipper phi f => Zipper phi ((:>:) f xi) Source # 

Methods

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

fill :: phi b -> Ctx (f :>: xi) b r ix -> r b -> (f :>: xi) r ix Source #

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

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

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

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

(Zipper phi f, Zipper phi g) => Zipper phi ((:*:) f g) Source # 

Methods

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

fill :: phi b -> Ctx (f :*: g) b r ix -> r b -> (f :*: g) r ix Source #

first :: (forall b. phi b -> r b -> Ctx (f :*: g) b r ix -> a) -> (f :*: g) r ix -> Maybe a Source #

last :: (forall b. phi b -> r b -> Ctx (f :*: g) b r ix -> a) -> (f :*: g) r ix -> Maybe a Source #

next :: (forall b. phi b -> r b -> Ctx (f :*: g) b r ix -> a) -> phi b -> Ctx (f :*: g) b r ix -> r b -> Maybe a Source #

prev :: (forall b. phi b -> r b -> Ctx (f :*: g) b r ix -> a) -> phi b -> Ctx (f :*: g) b r ix -> r b -> Maybe a Source #

(Zipper phi f, Zipper phi g) => Zipper phi ((:+:) f g) Source # 

Methods

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

fill :: phi b -> Ctx (f :+: g) b r ix -> r b -> (f :+: g) r ix Source #

first :: (forall b. phi b -> r b -> Ctx (f :+: g) b r ix -> a) -> (f :+: g) r ix -> Maybe a Source #

last :: (forall b. phi b -> r b -> Ctx (f :+: g) b r ix -> a) -> (f :+: g) r ix -> Maybe a Source #

next :: (forall b. phi b -> r b -> Ctx (f :+: g) b r ix -> a) -> phi b -> Ctx (f :+: g) b r ix -> r b -> Maybe a Source #

prev :: (forall b. phi b -> r b -> Ctx (f :+: g) b r ix -> a) -> phi b -> Ctx (f :+: g) b r ix -> r b -> Maybe a Source #

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.