{- Copyright 2017 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} {-# LANGUAGE FlexibleInstances, OverloadedStrings #-} module Hash where import Types import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as C8 import qualified Crypto.Hash as H class Hashable a where hash :: a -> Hash instance Hashable B.ByteString where -- Encodes the SHA512 using base16 format hash = Hash SHA512 . Val . C8.pack . show . sha512 instance Hashable Val where hash (Val v) = hash v instance Hashable Hash where hash = id sha512 :: B.ByteString -> H.Digest H.SHA512 sha512 = H.hash -- | A value tagged with a ByteString describing the type of value. -- This is hashed by hashing the concacenation of the hash of the -- bytestring and the hash of the value. This way, items of different types -- but with the same internal content will hash differently. For example, -- a Seen "foo" and a Entered "foo" should not hash the same. data Tagged a = Tagged B.ByteString a instance Hashable a => Hashable (Tagged a) where hash (Tagged b a) = hash [hash b, hash a] instance Hashable a => Hashable (Activity a) where hash (Activity a mps mpe mt s) = hash $ Tagged "Activity" [hash a, hashOfMaybeUnsafe mps, hashOfMaybeUnsafe mpe, hash mt, hash s] instance Hashable Entered where hash v = hash $ Tagged "Entered" [hash (enteredData v), hash (echoData v)] instance Hashable Seen where hash v = hash $ Tagged "Seen" [hash (seenData v)] instance Hashable ControlAction where hash (EnteredRejected h1 h2) = hash $ Tagged "EnteredRejected" [hash h1, hashOfMaybeUnsafe h2] hash (SessionKey pk v) = hash $ Tagged "SessionKey" [hash pk, hash v] hash (SessionKeyAccepted pk) = hash $ Tagged "SessionKeyAccepted" pk hash (SessionKeyRejected pk) = hash $ Tagged "SessionKeyRejected" pk hash (ChatMessage u m) = hash $ Tagged "ChatMessage" [hash u, hash m] instance Hashable Signature where hash (Ed25519Signature s) = hash $ Tagged "Ed25519Signature" s hash (OtherSignature s) = hash $ Tagged "OtherSignature" s instance Hashable PublicKey where hash (PublicKey v) = hash $ Tagged "PublicKey" v instance Hashable GpgSig where hash (GpgSig v) = hash $ Tagged "GpgSig" v instance Hashable GpgKeyExport where hash (GpgKeyExport v) = hash $ Tagged "GpgKeyExport" v instance Hashable a => Hashable (PerhapsSigned a) where hash (GpgSigned a sig export) = hash $ Tagged "GpgSigned" [hash a, hash sig, hash export] hash (UnSigned a) = hash $ Tagged "UnSigned" a instance Hashable ElapsedTime where hash (ElapsedTime n) = hash $ Tagged "ElapsedTime" $ C8.pack $ show n -- | Hash a list of hashes by hashing the concacenation of the hashes. instance Hashable [Hash] where hash = hash . B.concat . map (val . hashValue) -- | Hash a Maybe Hash, such that -- hash Nothing /= hash (Just (hash (mempty :: B.ByteString))) instance Hashable (Maybe Hash) where hash (Just v) = hash (val (hashValue v)) hash Nothing = hash (mempty :: B.ByteString) -- | Hash a Maybe Hash using the Hash value as-is, or the hash of the empty -- string for Nothing. -- -- Note that this is only safe to use when the input value can't possibly -- itself be the hash of an empty string. For example, the hash of an -- Activity is safe, because it's the hash of a non-empty string. -- -- This is only used to avoid breaking backwards compatability; the -- above instance for Maybe Hash should be used for anything new. hashOfMaybeUnsafe :: Maybe Hash -> Hash hashOfMaybeUnsafe (Just v) = hash v hashOfMaybeUnsafe Nothing = hash (mempty :: B.ByteString)