fixplate-0.1.8: Uniplate-style generic traversals for optionally annotated fixed-point types.

Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Fixplate.Zipper

Contents

Description

The Zipper is a data structure which maintains a location in a tree, and allows O(1) movement and local changes (to be more precise, in our case it is O(k) where k is the number of children of the node at question; typically this is a very small number).

Synopsis

Types

type Node f = Either (Mu f) (Path f) Source #

A context node.

data Path f Source #

The context or path type. The invariant we must respect is that there is exactly one child with the Right constructor.

Constructors

Top 
Path 

Fields

Instances
EqF f => Eq (Path f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Zipper

Methods

(==) :: Path f -> Path f -> Bool #

(/=) :: Path f -> Path f -> Bool #

ReadF f => Read (Path f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Zipper

ShowF f => Show (Path f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Zipper

Methods

showsPrec :: Int -> Path f -> ShowS #

show :: Path f -> String #

showList :: [Path f] -> ShowS #

data Loc f Source #

The zipper type itself, which encodes a locations in thre tree Mu f.

Constructors

Loc 

Fields

Instances
EqF f => Eq (Loc f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Zipper

Methods

(==) :: Loc f -> Loc f -> Bool #

(/=) :: Loc f -> Loc f -> Bool #

ReadF f => Read (Loc f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Zipper

ShowF f => Show (Loc f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Zipper

Methods

showsPrec :: Int -> Loc f -> ShowS #

show :: Loc f -> String #

showList :: [Loc f] -> ShowS #

Converting to and from zippers

root :: Mu f -> Loc f Source #

Creates a zipper from a tree, with the focus at the root.

defocus :: Traversable f => Loc f -> Mu f Source #

Restores a tree from a zipper.

locations :: Traversable f => Mu f -> Attr f (Loc f) Source #

We attribute all nodes with a zipper focused at that location.

locationsList :: Traversable f => Mu f -> [Loc f] Source #

The list of all locations.

locForget :: Functor f => Loc (Ann f a) -> Loc f Source #

The zipper version of forget.

Manipulating the subtree at focus

extract :: Loc f -> Mu f Source #

Extracts the subtree at focus. Synonym of focus.

replace :: Mu f -> Loc f -> Loc f Source #

Replaces the subtree at focus.

modify :: (Mu f -> Mu f) -> Loc f -> Loc f Source #

Modifies the subtree at focus.

Safe movements

moveDown :: Traversable f => Int -> Loc f -> Maybe (Loc f) Source #

Moves down to the child with the given index. The leftmost children has index 0.

moveDownL :: Traversable f => Loc f -> Maybe (Loc f) Source #

Moves down to the leftmost child.

moveDownR :: Traversable f => Loc f -> Maybe (Loc f) Source #

Moves down to the rightmost child.

moveUp :: Traversable f => Loc f -> Maybe (Loc f) Source #

Moves up.

Testing for borders

isTop :: Loc f -> Bool Source #

Checks whether we are at the top (root).

isBottom :: Traversable f => Loc f -> Bool Source #

Checks whether we cannot move down.

Location queries

horizontalPos :: Foldable f => Loc f -> Int Source #

Gives back the index of the given location among the children of its parent. Indexing starts from zero. In case of root node (no parent), we also return zero.

fullPathDown :: Foldable f => Loc f -> [Int] Source #

We return the full path from the root as a sequence of child indices. This means that

loc == foldl (flip unsafeMoveDown) (moveTop loc) (fullPathDown loc)

fullPathUp :: Foldable f => Loc f -> [Int] Source #

The following equations hold for fullPathUp and fullPathDown:

fullPathUp == reverse . fullPathDown
loc == foldr unsafeMoveDown (moveTop loc) (fullPathUp loc)

Compound movements

moveTop :: Traversable f => Loc f -> Loc f Source #

Moves to the top, by repeatedly moving up.

leftmost :: Traversable f => Loc f -> Loc f Source #

Moves left until it can. It should be faster than repeated left steps.

rightmost :: Traversable f => Loc f -> Loc f Source #

Moves right until it can. It should be faster than repeated right steps.

Unsafe movements