11{-|
2- Description : Cryptographic hashes for hnix-store.
2+ Description : Cryptographic hashing interface for hnix-store, on top
3+ of the cryptohash family of libraries.
34-}
45{-# LANGUAGE AllowAmbiguousTypes #-}
56{-# LANGUAGE DataKinds #-}
@@ -37,15 +38,37 @@ import Data.Word (Word8)
3738import GHC.TypeLits
3839import qualified System.Nix.Base32 as Base32
3940
40- -- | A tag for different hashing algorithms
41- -- Also used as a type-level tag for hash digests
42- -- (e.g. @Digest SHA256@ is the type for a sha256 hash)
41+ -- | The universe of supported hash algorithms.
42+ --
43+ -- Currently only intended for use at the type level.
4344data HashAlgorithm
4445 = MD5
4546 | SHA1
4647 | SHA256
4748 | Truncated Nat HashAlgorithm
49+ -- ^ The hash algorithm obtained by truncating the result of the
50+ -- input 'HashAlgorithm' to the given number of bytes. See
51+ -- 'truncateDigest' for a description of the truncation algorithm.
52+
53+ -- | The result of running a 'HashAlgorithm'.
54+ newtype Digest (a :: HashAlgorithm ) =
55+ Digest BS. ByteString deriving (Show , Eq , Ord , DataHashable.Hashable )
56+
57+ -- | The primitive interface for incremental hashing for a given
58+ -- 'HashAlgorithm'. Every 'HashAlgorithm' should have an instance.
59+ class HasDigest (a :: HashAlgorithm ) where
60+ -- | The incremental state for constructing a hash.
61+ type AlgoCtx a :: Type
4862
63+ -- | Start building a new hash.
64+ initialize :: AlgoCtx a
65+ -- | Append a 'BS.ByteString' to the overall contents to be hashed.
66+ update :: AlgoCtx a -> BS. ByteString -> AlgoCtx a
67+ -- | Finish hashing and generate the output.
68+ finalize :: AlgoCtx a -> Digest a
69+
70+ -- | An algorithm with a canonical name, for serialization purposes
71+ -- (e.g. SRI hashes)
4972class NamedAlgo a where
5073 algoName :: Text
5174
@@ -58,23 +81,8 @@ instance NamedAlgo 'SHA1 where
5881instance NamedAlgo 'SHA256 where
5982 algoName = " sha256"
6083
61- -- | Types with kind @HashAlgorithm@ may be a @HasDigest@ instance
62- -- if they are able to hash bytestrings via the init/update/finalize
63- -- API of cryptonite
84+ -- | Hash an entire (strict) 'BS.ByteString' as a single call.
6485--
65- -- Each instance defined here simply defers to one of the underlying
66- -- monomorphic hashing libraries, such as `cryptohash-sha256`.
67- class HasDigest (a :: HashAlgorithm ) where
68-
69- type AlgoCtx a :: Type
70-
71- initialize :: AlgoCtx a
72- update :: AlgoCtx a -> BS. ByteString -> AlgoCtx a
73- finalize :: AlgoCtx a -> Digest a
74-
75-
76- -- | The cryptographic hash of of a strict bytestring, where hash
77- -- algorithm is chosen by the type of the digest
7886-- For example:
7987-- > let d = hash "Hello, sha-256!" :: Digest SHA256
8088-- or
@@ -84,9 +92,10 @@ hash :: forall a.HasDigest a => BS.ByteString -> Digest a
8492hash bs =
8593 finalize $ update @ a (initialize @ a ) bs
8694
87- -- | The cryptographic hash of a lazy bytestring. Use is the same
88- -- as for @hash@. This runs in constant space, but forces the
89- -- entire bytestring
95+ -- | Hash an entire (lazy) 'BSL.ByteString' as a single call.
96+ --
97+ -- Use is the same as for 'hash'. This runs in constant space, but
98+ -- forces the entire bytestring.
9099hashLazy :: forall a . HasDigest a => BSL. ByteString -> Digest a
91100hashLazy bsl =
92101 finalize $ foldl' (update @ a ) (initialize @ a ) (BSL. toChunks bsl)
@@ -99,49 +108,44 @@ encodeBase32 (Digest bs) = Base32.encode bs
99108encodeBase16 :: Digest a -> T. Text
100109encodeBase16 (Digest bs) = T. decodeUtf8 (Base16. encode bs)
101110
102-
103- instance HasDigest MD5 where
111+ instance HasDigest 'MD5 where
104112 type AlgoCtx 'MD5 = MD5. Ctx
105113 initialize = MD5. init
106114 update = MD5. update
107115 finalize = Digest . MD5. finalize
108116
109117instance HasDigest 'SHA1 where
110- type AlgoCtx SHA1 = SHA1. Ctx
118+ type AlgoCtx ' SHA1 = SHA1. Ctx
111119 initialize = SHA1. init
112120 update = SHA1. update
113121 finalize = Digest . SHA1. finalize
114122
115123instance HasDigest 'SHA256 where
116- type AlgoCtx SHA256 = SHA256. Ctx
124+ type AlgoCtx ' SHA256 = SHA256. Ctx
117125 initialize = SHA256. init
118126 update = SHA256. update
119127 finalize = Digest . SHA256. finalize
120128
121- instance (HasDigest a , KnownNat n ) => HasDigest (Truncated n a ) where
122- type AlgoCtx (Truncated n a ) = AlgoCtx a
129+ -- | Reuses the underlying 'HasDigest' instance, but does a
130+ -- 'truncateDigest' at the end.
131+ instance (HasDigest a , KnownNat n ) => HasDigest ('Truncated n a ) where
132+ type AlgoCtx ('Truncated n a ) = AlgoCtx a
123133 initialize = initialize @ a
124134 update = update @ a
125135 finalize = truncateDigest @ n . finalize @ a
126136
127- -- | A raw hash digest, with a type-level tag
128- newtype Digest (a :: HashAlgorithm ) = Digest
129- { digestBytes :: BS. ByteString
130- -- ^ The bytestring in a Digest is an opaque string of bytes,
131- -- not some particular text encoding.
132- } deriving (Show , Eq , Ord , DataHashable.Hashable )
133-
134-
135- -- | Internal function for producing the bitwise truncation of bytestrings.
136- -- When truncation length is greater than the length of the bytestring,
137- -- but less than twice the bytestring length, truncation splits the
138- -- bytestring into a head part (truncation length) and tail part (leftover
139- -- part) right-pads the leftovers with 0 to the truncation length, and
140- -- combines the two strings bytewise with `xor`
141- truncateDigest :: forall n a . (HasDigest a , KnownNat n ) => Digest a -> Digest (Truncated n a )
142- truncateDigest (Digest c) = Digest $ BS. pack $ map truncOutputByte [0 .. n- 1 ]
137+ -- | Bytewise truncation of a 'Digest'.
138+ --
139+ -- When truncation length is greater than the length of the bytestring
140+ -- but less than twice the bytestring length, truncation splits the
141+ -- bytestring into a head part (truncation length) and tail part
142+ -- (leftover part), right-pads the leftovers with 0 to the truncation
143+ -- length, and combines the two strings bytewise with 'xor'.
144+ truncateDigest
145+ :: forall n a . (KnownNat n ) => Digest a -> Digest ('Truncated n a )
146+ truncateDigest (Digest c) =
147+ Digest $ BS. pack $ map truncOutputByte [0 .. n- 1 ]
143148 where
144-
145149 n = fromIntegral $ natVal (Proxy @ n )
146150
147151 truncOutputByte :: Int -> Word8
0 commit comments