zipper-0.4.3: Generic zipper for families of recursive datatypes

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

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

Defined in Generics.MultiRec.Zipper

Methods

hmapA :: Applicative a => (forall ix1. phi ix1 -> r ix1 -> a (r' ix1)) -> phi ix -> Loc phi r ix -> a (Loc phi 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 # 
Instance details

Defined in Generics.MultiRec.Zipper

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 b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx U b r ix
data Ctx (I xi) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (I xi) b r ix = CId (b :=: xi)
data Ctx (K a) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (K a) b r ix
data Ctx (f :+: g) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (f :+: g) b r ix
data Ctx (f :*: g) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (f :*: g) b r ix
  • = C1 (Ctx f b r ix) (g r ix)
  • | C2 (f r ix) (Ctx g b r ix)
data Ctx (f :>: xi) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (f :>: xi) b r ix = CTag (ix :=: xi) (Ctx f b r ix)
data Ctx ([] :.: g) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx ([] :.: g) b r ix = CCL [g r ix] (Ctx g b r ix) [g r ix]
data Ctx (Maybe :.: g) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (Maybe :.: g) b r ix = CCM (Ctx g b r ix)
data Ctx (C c f) b r ix Source # 
Instance details

Defined in Generics.MultiRec.Zipper

data Ctx (C c f) b r ix = CC (Ctx 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.

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 :: (forall b. phi b -> r b -> Ctx f b r ix -> a) -> f r ix -> Maybe a Source #

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

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

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 # 
Instance details

Defined in Generics.MultiRec.Zipper

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 # 
Instance details

Defined in Generics.MultiRec.Zipper

Methods

cmapA :: Applicative a0 => (forall ix. phi ix -> r ix -> a0 (r' ix)) -> phi ix -> Ctx (K a) b r ix -> a0 (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 -> a0) -> K a r ix -> Maybe a0 Source #

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

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

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

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

Defined in Generics.MultiRec.Zipper

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 # 
Instance details

Defined in Generics.MultiRec.Zipper

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 # 
Instance details

Defined in Generics.MultiRec.Zipper

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 g => Zipper phi (Maybe :.: g) Source # 
Instance details

Defined in Generics.MultiRec.Zipper

Methods

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

fill :: phi b -> Ctx (Maybe :.: g) b r ix -> r b -> (Maybe :.: g) r ix Source #

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

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

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

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

Zipper phi g => Zipper phi ([] :.: g) Source # 
Instance details

Defined in Generics.MultiRec.Zipper

Methods

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

fill :: phi b -> Ctx ([] :.: g) b r ix -> r b -> ([] :.: g) r ix Source #

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

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

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

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

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

Defined in Generics.MultiRec.Zipper

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 # 
Instance details

Defined in Generics.MultiRec.Zipper

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 :: (Fam phi, Zipper phi (PF phi)) => phi ix -> ix -> Loc phi I0 ix Source #

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

Return the entire value, independent of the current focus.

on :: (forall xi. phi xi -> r xi -> a) -> Loc phi 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 -> xi -> xi) -> Loc phi I0 ix -> Loc phi I0 ix Source #

Update the current focus without changing its type.

updateF :: Functor f => (forall xi. phi xi -> xi -> f xi) -> Loc phi I0 ix -> f (Loc phi I0 ix) Source #

Update the current focus, embedded in a functor.

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

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