project-m36-0.9.8: Relational Algebra Engine
Safe HaskellSafe-Inferred
LanguageHaskell2010

ProjectM36.HashSecurely

Description

A unified class for walking the database structure to produce a hash used for Merkle trees and validation.

Synopsis

Documentation

newtype SecureHash Source #

Constructors

SecureHash 

Instances

Instances details
Show SecureHash Source # 
Instance details

Defined in ProjectM36.HashSecurely

Eq SecureHash Source # 
Instance details

Defined in ProjectM36.HashSecurely

Serialise SecureHash Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

schemaGen :: Proxy SecureHash -> SchemaGen Schema

toBuilder :: SecureHash -> Builder

extractor :: Extractor SecureHash

decodeCurrent :: Decoder SecureHash

bundleSerialise :: BundleSerialise SecureHash

class HashBytes a where Source #

Methods

hashBytes :: a -> Ctx -> Ctx Source #

Instances

Instances details
HashBytes Atom Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Atom -> Ctx -> Ctx Source #

HashBytes AtomFunction Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: AtomFunction -> Ctx -> Ctx Source #

HashBytes AtomFunctions Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: AtomFunctions -> Ctx -> Ctx Source #

HashBytes AtomType Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: AtomType -> Ctx -> Ctx Source #

HashBytes Attribute Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Attribute -> Ctx -> Ctx Source #

HashBytes Attributes Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Attributes -> Ctx -> Ctx Source #

HashBytes DataConstructorDef Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: DataConstructorDef -> Ctx -> Ctx Source #

HashBytes DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: DataConstructorDefArg -> Ctx -> Ctx Source #

HashBytes DatabaseContext Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: DatabaseContext -> Ctx -> Ctx Source #

HashBytes DatabaseContextFunction Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: DatabaseContextFunction -> Ctx -> Ctx Source #

HashBytes DatabaseContextFunctions Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: DatabaseContextFunctions -> Ctx -> Ctx Source #

HashBytes GraphRefTransactionMarker Source # 
Instance details

Defined in ProjectM36.HashSecurely

HashBytes InclusionDependencies Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: InclusionDependencies -> Ctx -> Ctx Source #

HashBytes InclusionDependency Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: InclusionDependency -> Ctx -> Ctx Source #

HashBytes Notification Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Notification -> Ctx -> Ctx Source #

HashBytes Notifications Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Notifications -> Ctx -> Ctx Source #

HashBytes Relation Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Relation -> Ctx -> Ctx Source #

HashBytes RelationTuple Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: RelationTuple -> Ctx -> Ctx Source #

HashBytes RelationTupleSet Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: RelationTupleSet -> Ctx -> Ctx Source #

HashBytes RelationVariables Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: RelationVariables -> Ctx -> Ctx Source #

HashBytes Schema Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Schema -> Ctx -> Ctx Source #

HashBytes SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: SchemaIsomorph -> Ctx -> Ctx Source #

HashBytes TransactionId Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: TransactionId -> Ctx -> Ctx Source #

HashBytes TypeConstructor Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: TypeConstructor -> Ctx -> Ctx Source #

HashBytes TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: TypeConstructorDef -> Ctx -> Ctx Source #

HashBytes TypeConstructorMapping Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: TypeConstructorMapping -> Ctx -> Ctx Source #

HashBytes MerkleHash Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: MerkleHash -> Ctx -> Ctx Source #

HashBytes Text Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Text -> Ctx -> Ctx Source #

HashBytes UTCTime Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: UTCTime -> Ctx -> Ctx Source #

HashBytes () Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: () -> Ctx -> Ctx Source #

HashBytes a => HashBytes (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: AtomExprBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: AttributeExprBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: AttributeNamesBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: ExtendTupleExprBase a -> Ctx -> Ctx Source #

HashBytes (FunctionBody a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: FunctionBody a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: RelationalExprBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

HashBytes a => HashBytes (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: TupleExprBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (TupleExprsBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: TupleExprsBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (WithNameExprBase a) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: WithNameExprBase a -> Ctx -> Ctx Source #

HashBytes a => HashBytes (Maybe [AttributeExprBase a]) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Maybe [AttributeExprBase a] -> Ctx -> Ctx Source #

HashBytes [DataConstructorDef] Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: [DataConstructorDef] -> Ctx -> Ctx Source #

HashBytes (Map RelVarName Relation) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: Map RelVarName Relation -> Ctx -> Ctx Source #

(HashBytes a, HashBytes b) => HashBytes (a, b) Source # 
Instance details

Defined in ProjectM36.HashSecurely

Methods

hashBytes :: (a, b) -> Ctx -> Ctx Source #

data SHash Source #

Constructors

forall a.HashBytes a => SHash !a 

hashBytesL :: Foldable f => Ctx -> ByteString -> f SHash -> Ctx Source #

hashTransaction :: Transaction -> Set Transaction -> MerkleHash Source #

Hash a transaction within its graph context to create a Merkle hash for it.

mkDDLHash :: DatabaseContext -> Map RelVarName Relation -> SecureHash Source #

Return a hash of just DDL-specific (schema) attributes. This is useful for determining if a client has the appropriate updates needed to work with the current schema.