hdiff-0.0.1: Pattern-Expression-based differencing of arbitrary types.

Safe HaskellNone
LanguageHaskell2010

Generics.MRSOP.HDiff.Holes

Contents

Synopsis

Documentation

holesPretty Source #

Arguments

:: (HasDatatypeInfo ki fam codes, RendererHO ki) 
=> Proxy fam 
-> (Doc ann -> Doc ann)

styling

-> (forall at'. f at' -> Doc ann) 
-> Holes ki codes f at 
-> Doc ann 

Pretty-prints a treefix using a specific function to print holes.

holesZipRep :: MonadPlus m => Holes ki codes f at -> NA ki (Fix ki codes) at -> m (Holes ki codes (f :*: NA ki (Fix ki codes)) at) Source #

Zips a Holes and a generic value together. Returns mzero whenever the structure of the value is not compatible with that requird by the holed value.

Test Equality Instance

class HasIKProjInj (ki :: kon -> *) (f :: Atom kon -> *) where Source #

Methods

konInj :: ki k -> f (K k) Source #

varProj :: Proxy ki -> f x -> Maybe (IsI x) Source #

Instances
HasIKProjInj (ki :: kon -> Type) (MetaVarIK ki :: Atom kon -> Type) Source # 
Instance details

Defined in Data.HDiff.MetaVar

Methods

konInj :: ki k -> MetaVarIK ki (K k) Source #

varProj :: Proxy ki -> MetaVarIK ki x -> Maybe (IsI x) Source #

HasIKProjInj (ki :: kon -> Type) (CChange ki codes :: Atom kon -> Type) Source # 
Instance details

Defined in Data.HDiff.Change

Methods

konInj :: ki k -> CChange ki codes (K k) Source #

varProj :: Proxy ki -> CChange ki codes x -> Maybe (IsI x) Source #

HasIKProjInj (ki :: kon -> Type) (Holes2 ki codes :: Atom kon -> Type) Source # 
Instance details

Defined in Data.HDiff.Change

Methods

konInj :: ki k -> Holes2 ki codes (K k) Source #

varProj :: Proxy ki -> Holes2 ki codes x -> Maybe (IsI x) Source #

HasIKProjInj ki phi => HasIKProjInj (ki :: kon -> Type) (Holes ki codes phi :: Atom kon -> Type) Source # 
Instance details

Defined in Generics.MRSOP.HDiff.Holes

Methods

konInj :: ki k -> Holes ki codes phi (K k) Source #

varProj :: Proxy ki -> Holes ki codes phi x -> Maybe (IsI x) Source #

data IsI :: Atom kon -> * where Source #

Constructors

IsI :: IsNat i => IsI (I i) 

getIsISNat :: IsI (I i) -> SNat i Source #

Orphan instances

HolesTestEqualityCnstr ki f => TestEquality (Holes ki codes f :: Atom kon -> Type) Source # 
Instance details

Methods

testEquality :: Holes ki codes f a -> Holes ki codes f b -> Maybe (a :~: b) #