Skip to content

Commit

Permalink
Accessor for words of 32 byte hashes
Browse files Browse the repository at this point in the history
  • Loading branch information
redxaxder committed Sep 24, 2021
1 parent 592aa61 commit 757d7a7
Showing 1 changed file with 29 additions and 1 deletion.
30 changes: 29 additions & 1 deletion cardano-crypto-class/src/Cardano/Crypto/Hash/Class.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
Expand All @@ -26,6 +27,9 @@ module Cardano.Crypto.Hash.Class
, hashFromBytes
, hashToBytesShort
, hashFromBytesShort
, ViewHash32 (..)
, unsafeMkHash32
, viewHash32

-- * Rendering and parsing
, hashToBytesAsHex
Expand All @@ -52,8 +56,10 @@ import Data.List (foldl')
import Data.Maybe (maybeToList)
import Data.Proxy (Proxy(..))
import Data.Typeable (Typeable)
import Data.Word (Word64)
import GHC.Generics (Generic)
import GHC.TypeLits (KnownNat, Nat, natVal)
import GHC.TypeLits (KnownNat, Nat, natVal, sameNat)
import Data.Type.Equality ((:~:)(Refl))

import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
Expand Down Expand Up @@ -299,6 +305,28 @@ instance (HashAlgorithm h, Typeable a) => FromCBOR (Hash h a) where
expected = sizeHash (Proxy :: Proxy h)
actual = BS.length bs

data ViewHash32 h a where
ViewHash32 :: SizeHash h ~ 32
=> Word64
-> Word64
-> Word64
-> Word64
-> ViewHash32 h a
ViewHashNot32 :: ViewHash32 h a

viewHash32 :: forall h a. HashAlgorithm h => Hash h a -> ViewHash32 h a
viewHash32 (UnsafeHashRep p) = go p
where
go :: forall n. PackedBytes n -> ViewHash32 h a
go (PackedBytes32 a b c d) =
case sameNat (Proxy :: Proxy (SizeHash h)) (Proxy :: Proxy 32) of
Just Refl -> ViewHash32 a b c d
Nothing -> ViewHashNot32
go _ = ViewHashNot32

unsafeMkHash32 ::
SizeHash h ~ 32 => Word64 -> Word64 -> Word64 -> Word64 -> Hash h a
unsafeMkHash32 a b c d = UnsafeHashRep (PackedBytes32 a b c d)

--
-- Deprecated
Expand Down

0 comments on commit 757d7a7

Please sign in to comment.