transformations-0.2.0.0: Generic representation of tree transformations

Safe HaskellNone
LanguageHaskell98

Generics.MultiRec.Transformations.Path

Synopsis

Documentation

type Path phi t i = Ctxs phi t (K0 ()) i Source

A path is a list of connecting directions on a datatype. This is equivalent to a zipper context where the recursive positions are ignored (set to a constant type).

type Dir f t i = Ctx f t (K0 ()) i Source

A direction points to a single recursive position in a datatype.

data WithRef phi top r a Source

The type of pattern functors extended with references

Constructors

InR 

Fields

unInR :: PF phi r a
 
Ref 

Fields

unRef :: Path phi a top
 

Instances

(HFunctor phi (PF phi), HShow phi (PF phi), El phi ix, ShowPath (PF phi)) => Show (HWithRef phi top ix) 

type HWithRef phi top t = HFix (WithRef phi top) t Source

Closed functors extended with references

data Insert phi top ix where Source

Insertions contain a path of where to insert, and what to insert

Constructors

Insert :: phi t -> Path phi t ix -> HWithRef phi top t -> Insert phi top ix 

Instances

(HFunctor phi (PF phi), HShow phi (PF phi), El phi ix, ShowPath (PF phi)) => Show (Insert phi top ix) 

(<.>) :: forall phi a b c. Path phi b a -> Path phi c b -> Path phi c a Source

Concatenate two paths

newtype ConIndex Source

Constructors

CI Int 

class ShowPath f where Source

Methods

showsPrecPath :: ShowS -> ConIndex -> Int -> Dir f i t -> ShowS Source

Instances

ShowPath U 
ShowPath (I ix) 
ShowPath (K a) 
(ShowPath f, ShowPath g) => ShowPath ((:+:) f g) 
(ShowPath f, ShowPath g, CountIs f) => ShowPath ((:*:) f g) 
ShowPath f => ShowPath ((:>:) f ix) 
ShowPath f => ShowPath ((:.:) [] f) 
ShowPath f => ShowPath ((:.:) Maybe f) 
(ShowPath f, Constructor c) => ShowPath (C c f) 

showsPrecPathC :: ShowPath (PF phi) => ConIndex -> Int -> Path phi t i -> ShowS Source

showWR :: forall phi top ix. (HFunctor phi (PF phi), HShow phi (PF phi), ShowPath (PF phi)) => phi ix -> Int -> HWithRef phi top ix -> ShowS Source

mapP :: forall m phi i t. (Monad m, Fam phi, MapP phi (PF phi)) => phi i -> Path phi t i -> (phi t -> t -> m t) -> i -> m i Source

class MapP phi f where Source

Methods

mapP' :: Monad m => (phi t -> r t -> m (r t)) -> phi ix -> Dir f t ix -> f r ix -> m (f r ix) Source

Instances

MapP phi U 
El phi ix => MapP phi (I ix) 
MapP phi (K a) 
MapP phi f => MapP phi ((:.:) [] f) 
MapP phi f => MapP phi ((:.:) Maybe f) 
MapP phi f => MapP phi ((:>:) f ix) 
MapP phi f => MapP phi (C c f) 
(MapP phi f, MapP phi g) => MapP phi ((:*:) f g) 
(MapP phi f, MapP phi g) => MapP phi ((:+:) f g) 

mapPR :: forall phi top t a. (Fam phi, MapP phi (PF phi)) => phi a -> Path phi t a -> (phi t -> HWithRef phi top t -> Maybe (HWithRef phi top t)) -> HWithRef phi top a -> Maybe (HWithRef phi top a) Source

mapMwithI :: (Monad m, Traversable t) => (Int -> a -> m b) -> t a -> m (t b) Source

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) 

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)