transformations-0.1.0.0: Generic representation of tree transformations

Safe HaskellNone

Generics.Regular.Zipper

Contents

Synopsis

Locations

data Loc whereSource

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 :: (Regular a, Zipper (PF a)) => a -> [Ctx (PF a) a] -> Loc a 

Context frames

data family Ctx f :: * -> *Source

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

Generic zipper class

class Functor f => Zipper 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

cmap :: (a -> b) -> Ctx f a -> Ctx f bSource

fill :: Ctx f a -> a -> f aSource

first, last :: f a -> Maybe (a, Ctx f a)Source

next, prev :: Ctx f a -> a -> Maybe (a, Ctx f a)Source

Instances

Zipper I 
Zipper U 
Zipper (K a) 
(Zipper f, Zipper g) => Zipper (:+: f g) 
(Zipper f, Zipper g) => Zipper (:*: f g) 
Zipper f => Zipper (C c f) 
Zipper f => Zipper (S s f) 

Interface

enter :: (Regular a, Zipper (PF a)) => a -> Loc aSource

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

down :: Loc a -> Maybe (Loc a)Source

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

down' :: Loc a -> Maybe (Loc a)Source

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

up :: Loc a -> Maybe (Loc a)Source

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

right :: Loc a -> Maybe (Loc a)Source

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

left :: Loc a -> Maybe (Loc a)Source

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

leave :: Loc a -> aSource

Return the entire value, independent of the current focus.

on :: Loc a -> aSource

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

update :: (a -> a) -> Loc a -> Loc aSource

Update the current focus without changing its type.

updateM :: Monad m => (a -> m a) -> Loc a -> m (Loc a)Source

Update the current focus without changing its type.