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

Safe HaskellNone
LanguageHaskell2010

Generics.MRSOP.HDiff.Digest

Synopsis

Documentation

newtype Digest Source #

Our digests come from Blake2s_256

Constructors

Digest 
Instances
Eq Digest Source # 
Instance details

Defined in Generics.MRSOP.HDiff.Digest

Methods

(==) :: Digest -> Digest -> Bool #

(/=) :: Digest -> Digest -> Bool #

Show Digest Source # 
Instance details

Defined in Generics.MRSOP.HDiff.Digest

toW64s :: Digest -> [Word64] Source #

Unpacks a digest into a list of Word64.

snat2W64 :: SNat n -> Word64 Source #

Process an SNat into a Word64. This is useful in order to use type-level info as salt.

hash :: ByteString -> Digest Source #

Auxiliar hash function with the correct types instantiated.

hashStr :: String -> Digest Source #

Auxiliar hash functions for strings

digestConcat :: [Digest] -> Digest Source #

Concatenates digests together and hashes the result.

class Digestible (v :: *) where Source #

A Value is digestible if we know how to hash it.

Methods

digest :: v -> Digest Source #

Instances
Digestible Word64 Source #

A Word64 is digestible

Instance details

Defined in Generics.MRSOP.HDiff.Digest

Methods

digest :: Word64 -> Digest Source #

class DigestibleHO (f :: k -> *) where Source #

A functor is digestible if we can hash its value pointwise.

Methods

digestHO :: forall ki. f ki -> Digest Source #

Instances
DigestibleHO Singl Source # 
Instance details

Defined in Data.HDiff.Example

Methods

digestHO :: Singl ki -> Digest Source #

DigestibleHO W Source # 
Instance details

Defined in Languages.RTree

Methods

digestHO :: W ki -> Digest Source #

DigestibleHO (Const Void :: k -> Type) Source # 
Instance details

Defined in Generics.MRSOP.HDiff.Digest

Methods

digestHO :: Const Void ki -> Digest Source #

DigestibleHO ki => DigestibleHO (MetaVarIK ki :: Atom kon -> Type) Source # 
Instance details

Defined in Data.HDiff.MetaVar

Methods

digestHO :: MetaVarIK ki ki0 -> Digest Source #

authPeel' :: forall sum ann i. (forall ix. ann ix -> Digest) -> Word64 -> Constr sum i -> NP ann (Lkup i sum) -> Digest Source #

Authenticates a HPeel without caring for the type information. Only use this if you are sure of what you are doing, as there can be colissions. For example:

data A = A1 B | A2 Int Int
data B = B1 A | B2 Int Int 
xA :: NP ann (Lkup 1 codesA)
xB :: NP ann (Lkup 1 codesB)

authPeel' f 0 (CS CZ) xA == authPeel' f 0 (CS CZ) xB

That's because A2 and B2 have the exact same signature and are within the exact same position within the datatype. We must use the salt to pass type information:

authPeel' f (snat2W64 IdxA) (CS CZ) xA
  =/ authPeel' f (snat2W64 IdxB) (CS CZ) xB

One should stick to authPeel whenever in doubt.

authPeel :: forall codes ix ann i. IsNat ix => (forall iy. ann iy -> Digest) -> Proxy codes -> Proxy ix -> Constr (Lkup ix codes) i -> NP ann (Lkup i (Lkup ix codes)) -> Digest Source #

This function correctly salts authPeel' and produces a unique hash per constructor.