Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module has been taken from arianvp/generics-mrsop-diff, it essentially isolates Arian's fixes over GDiff and adapts them to work over newer versions of generics-mrsop.
Synopsis
- data Cof (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: Atom kon -> [Atom kon] -> * where
- cofIdx :: forall ki codes xs n. IsNat n => Cof ki codes (I n) xs -> SNat n
- cofWitnessI :: Cof ki codes (I n) t -> Proxy n
- cofHeq :: (EqHO ki, TestEquality ki) => Cof ki codes a t1 -> Cof ki codes b t2 -> Maybe (a :~: b, t1 :~: t2)
- data ES (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: [Atom kon] -> [Atom kon] -> * where
- apply :: forall ki fam codes ty1 ty2 ix1 ix2. (Family ki fam codes, ix1 ~ Idx ty1 fam, ix2 ~ Idx ty2 fam, Lkup ix1 fam ~ ty1, Lkup ix2 fam ~ ty2, IsNat ix1, IsNat ix2, EqHO ki, TestEquality ki) => ES ki codes '[I ix1] '[I ix2] -> ty1 -> Maybe ty2
- apply' :: (IsNat ix1, IsNat ix2, EqHO ki) => ES ki codes '[I ix1] '[I ix2] -> Fix ki codes ix1 -> Maybe (Fix ki codes ix2)
- applyES :: EqHO ki => ES ki codes xs ys -> PoA ki (Fix ki codes) xs -> Maybe (PoA ki (Fix ki codes) ys)
- diff :: forall fam ki codes ix1 ix2 ty1 ty2. (Family ki fam codes, ix1 ~ Idx ty1 fam, ix2 ~ Idx ty2 fam, Lkup ix1 fam ~ ty1, Lkup ix2 fam ~ ty2, IsNat ix1, IsNat ix2, EqHO ki, TestEquality ki) => ty1 -> ty2 -> ES ki codes '[I ix1] '[I ix2]
- diff' :: (EqHO ki, IsNat ix1, IsNat ix2, TestEquality ki) => Fix ki codes ix1 -> Fix ki codes ix2 -> ES ki codes '[I ix1] '[I ix2]
- cost :: ES ki codes txs tys -> Int
Documentation
data Cof (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: Atom kon -> [Atom kon] -> * where Source #
A Cof
represents a leaf of the flattened representation of our tree. Hence,
it will be either a constructor of a particular datatype or an opaque value.
ConstrI :: (IsNat c, IsNat n) => Constr (Lkup n codes) c -> ListPrf (Lkup c (Lkup n codes)) -> Cof ki codes (I n) (Lkup c (Lkup n codes)) | A constructor tells us the type of its arguments and which type in the family it constructs |
ConstrK :: ki k -> Cof ki codes (K k) '[] | Requires no arguments to complete |
cofHeq :: (EqHO ki, TestEquality ki) => Cof ki codes a t1 -> Cof ki codes b t2 -> Maybe (a :~: b, t1 :~: t2) Source #
Values of type Cof
support heterogeneous equality checking.
data ES (ki :: kon -> *) (codes :: [[[Atom kon]]]) :: [Atom kon] -> [Atom kon] -> * where Source #
An edit script will insert, delete or copy Cof
s. We keep the cost
of the edit script annotated in the constructor