hypertypes-0.1.0.2: Typed ASTs
Safe HaskellNone
LanguageHaskell2010

Hyper.Diff

Synopsis

Documentation

diff :: forall t a b. (Recursively ZipMatch t, RTraversable t) => (Ann a # t) -> (Ann b # t) -> Diff a b # t Source #

Compute the difference of two annotated trees.

data Diff a b e Source #

A HyperType which represents the difference between two annotated trees. The annotation types also function as tokens to describe which of the two trees a term comes from.

Constructors

CommonSubTree (Ann (a :*: b) e) 
CommonBody (CommonBody a b e) 
Different ((Ann a :*: Ann b) e) 

Instances

Instances details
Constraints (Diff a b e) Eq => Eq (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

(==) :: Diff a b e -> Diff a b e -> Bool #

(/=) :: Diff a b e -> Diff a b e -> Bool #

Constraints (Diff a b e) Ord => Ord (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

compare :: Diff a b e -> Diff a b e -> Ordering #

(<) :: Diff a b e -> Diff a b e -> Bool #

(<=) :: Diff a b e -> Diff a b e -> Bool #

(>) :: Diff a b e -> Diff a b e -> Bool #

(>=) :: Diff a b e -> Diff a b e -> Bool #

max :: Diff a b e -> Diff a b e -> Diff a b e #

min :: Diff a b e -> Diff a b e -> Diff a b e #

Constraints (Diff a b e) Show => Show (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

showsPrec :: Int -> Diff a b e -> ShowS #

show :: Diff a b e -> String #

showList :: [Diff a b e] -> ShowS #

Generic (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

Associated Types

type Rep (Diff a b e) :: Type -> Type #

Methods

from :: Diff a b e -> Rep (Diff a b e) x #

to :: Rep (Diff a b e) x -> Diff a b e #

Constraints (Diff a b e) Binary => Binary (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

put :: Diff a b e -> Put #

get :: Get (Diff a b e) #

putList :: [Diff a b e] -> Put #

Constraints (Diff a b e) NFData => NFData (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

rnf :: Diff a b e -> () #

type Rep (Diff a b e) Source # 
Instance details

Defined in Hyper.Diff

type Rep (Diff a b e) = D1 ('MetaData "Diff" "Hyper.Diff" "hypertypes-0.1.0.2-GDiSRF0EwgQ6Mkx3yytlTL" 'False) (C1 ('MetaCons "CommonSubTree" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ann (a :*: b) e))) :+: (C1 ('MetaCons "CommonBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CommonBody a b e))) :+: C1 ('MetaCons "Different" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((Ann a :*: Ann b) e)))))

_CommonBody :: forall a b e. Prism' (Diff a b e) (CommonBody a b e) Source #

_CommonSubTree :: forall a b e. Prism' (Diff a b e) (Ann ((:*:) a b) e) Source #

_Different :: forall a b e. Prism' (Diff a b e) ((:*:) (Ann a) (Ann b) e) Source #

data CommonBody a b e Source #

A HyperType which represents two trees which have the same top-level node, but their children may differ.

Constructors

MkCommonBody 

Fields

Instances

Instances details
Constraints (CommonBody a b e) Eq => Eq (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

(==) :: CommonBody a b e -> CommonBody a b e -> Bool #

(/=) :: CommonBody a b e -> CommonBody a b e -> Bool #

Constraints (CommonBody a b e) Ord => Ord (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

compare :: CommonBody a b e -> CommonBody a b e -> Ordering #

(<) :: CommonBody a b e -> CommonBody a b e -> Bool #

(<=) :: CommonBody a b e -> CommonBody a b e -> Bool #

(>) :: CommonBody a b e -> CommonBody a b e -> Bool #

(>=) :: CommonBody a b e -> CommonBody a b e -> Bool #

max :: CommonBody a b e -> CommonBody a b e -> CommonBody a b e #

min :: CommonBody a b e -> CommonBody a b e -> CommonBody a b e #

Constraints (CommonBody a b e) Show => Show (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

showsPrec :: Int -> CommonBody a b e -> ShowS #

show :: CommonBody a b e -> String #

showList :: [CommonBody a b e] -> ShowS #

Generic (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

Associated Types

type Rep (CommonBody a b e) :: Type -> Type #

Methods

from :: CommonBody a b e -> Rep (CommonBody a b e) x #

to :: Rep (CommonBody a b e) x -> CommonBody a b e #

Constraints (CommonBody a b e) Binary => Binary (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

put :: CommonBody a b e -> Put #

get :: Get (CommonBody a b e) #

putList :: [CommonBody a b e] -> Put #

Constraints (CommonBody a b e) NFData => NFData (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

Methods

rnf :: CommonBody a b e -> () #

type Rep (CommonBody a b e) Source # 
Instance details

Defined in Hyper.Diff

type Rep (CommonBody a b e) = D1 ('MetaData "CommonBody" "Hyper.Diff" "hypertypes-0.1.0.2-GDiSRF0EwgQ6Mkx3yytlTL" 'False) (C1 ('MetaCons "MkCommonBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "_anns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((a :*: b) e)) :*: S1 ('MetaSel ('Just "_val") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (e :# Diff a b))))

anns :: forall a b e. Lens' (CommonBody a b e) ((:*:) a b e) Source #

val :: forall a b e. Lens' (CommonBody a b e) ((:#) e (Diff a b)) Source #

foldDiffs :: forall r h a b. (Monoid r, Recursively HFoldable h) => (forall n. HRecWitness h n -> (Ann a # n) -> (Ann b # n) -> r) -> (Diff a b # h) -> r Source #

data DiffP h Source #

Instances

Instances details
Constraints (DiffP h) Eq => Eq (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

Methods

(==) :: DiffP h -> DiffP h -> Bool #

(/=) :: DiffP h -> DiffP h -> Bool #

Constraints (DiffP h) Ord => Ord (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

Methods

compare :: DiffP h -> DiffP h -> Ordering #

(<) :: DiffP h -> DiffP h -> Bool #

(<=) :: DiffP h -> DiffP h -> Bool #

(>) :: DiffP h -> DiffP h -> Bool #

(>=) :: DiffP h -> DiffP h -> Bool #

max :: DiffP h -> DiffP h -> DiffP h #

min :: DiffP h -> DiffP h -> DiffP h #

Constraints (DiffP h) Show => Show (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

Methods

showsPrec :: Int -> DiffP h -> ShowS #

show :: DiffP h -> String #

showList :: [DiffP h] -> ShowS #

Generic (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

Associated Types

type Rep (DiffP h) :: Type -> Type #

Methods

from :: DiffP h -> Rep (DiffP h) x #

to :: Rep (DiffP h) x -> DiffP h #

Constraints (DiffP h) Binary => Binary (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

Methods

put :: DiffP h -> Put #

get :: Get (DiffP h) #

putList :: [DiffP h] -> Put #

Constraints (DiffP h) NFData => NFData (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

Methods

rnf :: DiffP h -> () #

type Rep (DiffP h) Source # 
Instance details

Defined in Hyper.Diff

_CommonBodyP :: forall h. Prism' (DiffP h) ((:#) h DiffP) Source #

foldDiffsP :: forall r h. (Monoid r, Recursively HFoldable h, Recursively HasHPlain h) => (forall n. HasHPlain n => HRecWitness h n -> HPlain n -> HPlain n -> r) -> (DiffP # h) -> r Source #