@@ -16,8 +16,10 @@ module System.Nix.Internal.Hash where
1616import qualified Crypto.Hash.MD5 as MD5
1717import qualified Crypto.Hash.SHA1 as SHA1
1818import qualified Crypto.Hash.SHA256 as SHA256
19+ import qualified Crypto.Hash.SHA512 as SHA512
1920import qualified Data.ByteString as BS
2021import qualified Data.ByteString.Base16 as Base16
22+ import qualified Data.ByteString.Base64 as Base64
2123import Data.Bits (xor )
2224import qualified Data.ByteString.Lazy as BSL
2325import qualified Data.Hashable as DataHashable
@@ -37,14 +39,18 @@ data HashAlgorithm
3739 = MD5
3840 | SHA1
3941 | SHA256
42+ | SHA512
4043 | Truncated Nat HashAlgorithm
4144 -- ^ The hash algorithm obtained by truncating the result of the
4245 -- input 'HashAlgorithm' to the given number of bytes. See
4346 -- 'truncateDigest' for a description of the truncation algorithm.
4447
4548-- | The result of running a 'HashAlgorithm'.
4649newtype Digest (a :: HashAlgorithm ) =
47- Digest BS. ByteString deriving (Show , Eq , Ord , DataHashable.Hashable )
50+ Digest BS. ByteString deriving (Eq , Ord , DataHashable.Hashable )
51+
52+ instance Show (Digest a ) where
53+ show = (" Digest " ++ ) . show . encodeBase32
4854
4955-- | The primitive interface for incremental hashing for a given
5056-- 'HashAlgorithm'. Every 'HashAlgorithm' should have an instance.
@@ -61,21 +67,60 @@ class ValidAlgo (a :: HashAlgorithm) where
6167
6268-- | A 'HashAlgorithm' with a canonical name, for serialization
6369-- purposes (e.g. SRI hashes)
64- class NamedAlgo (a :: HashAlgorithm ) where
70+ class ValidAlgo a => NamedAlgo (a :: HashAlgorithm ) where
6571 algoName :: Text
72+ hashSize :: Int
6673
6774instance NamedAlgo 'MD5 where
6875 algoName = " md5"
76+ hashSize = 16
6977
7078instance NamedAlgo 'SHA1 where
7179 algoName = " sha1"
80+ hashSize = 20
7281
7382instance NamedAlgo 'SHA256 where
7483 algoName = " sha256"
84+ hashSize = 32
85+
86+ instance NamedAlgo 'SHA512 where
87+ algoName = " sha512"
88+ hashSize = 64
7589
7690-- | A digest whose 'NamedAlgo' is not known at compile time.
7791data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (Digest a )
7892
93+ instance Show SomeNamedDigest where
94+ show sd = case sd of
95+ SomeDigest (digest :: Digest hashType ) -> T. unpack $ " SomeDigest " <> algoName @ hashType <> " :" <> encodeBase32 digest
96+
97+ mkNamedDigest :: Text -> Text -> Either String SomeNamedDigest
98+ mkNamedDigest name sriHash =
99+ let (sriName, hash) = T. breakOnEnd " -" sriHash in
100+ if sriName == " " || sriName == (name <> " -" )
101+ then mkDigest name hash
102+ else Left $ T. unpack $ " Sri hash method " <> sriName <> " does not match the required hash type " <> name
103+ where
104+ mkDigest name hash = case name of
105+ " md5" -> SomeDigest <$> decode @ 'MD5 hash
106+ " sha1" -> SomeDigest <$> decode @ 'SHA1 hash
107+ " sha256" -> SomeDigest <$> decode @ 'SHA256 hash
108+ " sha512" -> SomeDigest <$> decode @ 'SHA512 hash
109+ _ -> Left $ " Unknown hash name: " ++ T. unpack name
110+ decode :: forall a . (NamedAlgo a , ValidAlgo a ) => Text -> Either String (Digest a )
111+ decode hash
112+ | size == base16Len = decodeBase16 hash
113+ | size == base32Len = decodeBase32 hash
114+ | size == base64Len = decodeBase64 hash
115+ | otherwise = Left $ T. unpack sriHash ++ " is not a valid " ++ T. unpack name ++ " hash. Its length (" ++ show size ++ " ) does not match any of " ++ show [base16Len, base32Len, base64Len]
116+ where
117+ size = T. length hash
118+ hsize = hashSize @ a
119+ base16Len = hsize * 2
120+ base32Len = ((hsize * 8 - 1 ) `div` 5 ) + 1 ;
121+ base64Len = ((4 * hsize `div` 3 ) + 3 ) `div` 4 * 4 ;
122+
123+
79124-- | Hash an entire (strict) 'BS.ByteString' as a single call.
80125--
81126-- For example:
@@ -113,6 +158,16 @@ decodeBase16 t = case Base16.decode (T.encodeUtf8 t) of
113158 (x, " " ) -> Right $ Digest x
114159 _ -> Left $ " Unable to decode base16 string " ++ T. unpack t
115160
161+ -- | Encode a 'Digest' in hex.
162+ encodeBase64 :: Digest a -> T. Text
163+ encodeBase64 (Digest bs) = T. decodeUtf8 (Base64. encode bs)
164+
165+ -- | Decode a 'Digest' in hex
166+ decodeBase64 :: T. Text -> Either String (Digest a )
167+ decodeBase64 t = case Base64. decode (T. encodeUtf8 t) of
168+ Right x -> Right $ Digest x
169+ Left e -> Left $ " Unable to decode base64 string " ++ T. unpack t ++ " : " ++ e
170+
116171-- | Uses "Crypto.Hash.MD5" from cryptohash-md5.
117172instance ValidAlgo 'MD5 where
118173 type AlgoCtx 'MD5 = MD5. Ctx
@@ -134,6 +189,13 @@ instance ValidAlgo 'SHA256 where
134189 update = SHA256. update
135190 finalize = Digest . SHA256. finalize
136191
192+ -- | Uses "Crypto.Hash.SHA512" from cryptohash-sha512.
193+ instance ValidAlgo 'SHA512 where
194+ type AlgoCtx 'SHA512 = SHA512. Ctx
195+ initialize = SHA512. init
196+ update = SHA512. update
197+ finalize = Digest . SHA512. finalize
198+
137199-- | Reuses the underlying 'ValidAlgo' instance, but does a
138200-- 'truncateDigest' at the end.
139201instance (ValidAlgo a , KnownNat n ) => ValidAlgo ('Truncated n a ) where
0 commit comments