-
Notifications
You must be signed in to change notification settings - Fork 23
/
Copy pathHash.hs
188 lines (166 loc) · 5.35 KB
/
Hash.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-|
Description : Cryptographic hashing interface for hnix-store, on top
of the cryptohash family of libraries.
-}
module System.Nix.Hash
( HashAlgo(..)
, NamedAlgo(..)
, algoToText
, textToAlgo
, mkNamedDigest
, mkStorePathHash
, System.Nix.Base.BaseEncoding(..)
, encodeDigestWith
, decodeDigestWith
, algoDigestBuilder
, digestBuilder
) where
import Crypto.Hash (Digest, HashAlgorithm, MD5(..), SHA1(..), SHA256(..), SHA512(..))
import Data.ByteString (ByteString)
import Data.Constraint.Extras (Has(has))
import Data.Constraint.Extras.TH (deriveArgDict)
import Data.Dependent.Sum (DSum((:=>)))
import Data.GADT.Compare.TH (deriveGEq, deriveGCompare)
import Data.GADT.Show.TH (deriveGShow)
import Data.Kind (Type)
import Data.Some (Some(Some))
import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder)
import System.Nix.Base (BaseEncoding(..))
import qualified Crypto.Hash
import qualified Data.ByteArray
import qualified Data.Text
import qualified Data.Text.Lazy.Builder
import qualified System.Nix.Base
import qualified System.Nix.Hash.Truncation
-- | A 'HashAlgorithm' with a canonical name, for serialization
-- purposes (e.g. SRI hashes)
class HashAlgorithm a => NamedAlgo a where
algoName :: Text
instance NamedAlgo MD5 where
algoName = "md5"
instance NamedAlgo SHA1 where
algoName = "sha1"
instance NamedAlgo SHA256 where
algoName = "sha256"
instance NamedAlgo SHA512 where
algoName = "sha512"
data HashAlgo :: Type -> Type where
HashAlgo_MD5 :: HashAlgo MD5
HashAlgo_SHA1 :: HashAlgo SHA1
HashAlgo_SHA256 :: HashAlgo SHA256
HashAlgo_SHA512 :: HashAlgo SHA512
deriveGEq ''HashAlgo
deriveGCompare ''HashAlgo
deriveGShow ''HashAlgo
deriveArgDict ''HashAlgo
algoToText :: forall t. HashAlgo t -> Text
algoToText x = has @NamedAlgo x (algoName @t)
hashAlgoValue :: HashAlgo a -> a
hashAlgoValue = \case
HashAlgo_MD5 -> MD5
HashAlgo_SHA1 -> SHA1
HashAlgo_SHA256 -> SHA256
HashAlgo_SHA512 -> SHA512
textToAlgo :: Text -> Either String (Some HashAlgo)
textToAlgo = \case
"md5" -> Right $ Some HashAlgo_MD5
"sha1" -> Right $ Some HashAlgo_SHA1
"sha256" -> Right $ Some HashAlgo_SHA256
"sha512" -> Right $ Some HashAlgo_SHA512
name -> Left $ "Unknown hash name: " <> Data.Text.unpack name
-- | Make @DSum HashAlgo Digest@ based on provided SRI hash name
-- and its encoded form
mkNamedDigest
:: Text -- ^ SRI name
-> Text -- ^ base encoded hash
-> Either String (DSum HashAlgo Digest)
mkNamedDigest name sriHash =
let (sriName, h) = Data.Text.breakOnEnd "-" sriHash in
if sriName == "" || sriName == name <> "-"
then mkDigest h
else
Left
$ Data.Text.unpack
$ "Sri hash method"
<> " "
<> sriName
<> " "
<> "does not match the required hash type"
<> " "
<> name
where
mkDigest h =
textToAlgo name
>>= \(Some a) -> has @HashAlgorithm a $ fmap (a :=>) $ decodeGo a h
decodeGo :: HashAlgorithm a => HashAlgo a -> Text -> Either String (Digest a)
decodeGo a h
| size == base16Len = decodeDigestWith Base16 h
| size == base32Len = decodeDigestWith NixBase32 h
| size == base64Len = decodeDigestWith Base64 h
| otherwise =
Left
$ Data.Text.unpack
$ sriHash
<> " "
<> "is not a valid"
<> " "
<> name
<> " "
<> "hash. Its length ("
<> Data.Text.pack (show size)
<> ") does not match any of"
<> " "
<> Data.Text.pack (show [base16Len, base32Len, base64Len])
where
size = Data.Text.length h
hsize = Crypto.Hash.hashDigestSize (hashAlgoValue a)
base16Len = hsize * 2
base32Len = ((hsize * 8 - 1) `div` 5) + 1;
base64Len = ((4 * hsize `div` 3) + 3) `div` 4 * 4;
mkStorePathHash
:: forall a
. HashAlgorithm a
=> ByteString
-> ByteString
mkStorePathHash bs =
System.Nix.Hash.Truncation.truncateInNixWay 20
$ Data.ByteArray.convert
$ Crypto.Hash.hash @ByteString @a bs
-- | Take BaseEncoding type of the output -> take the Digeest as input -> encode Digest
encodeDigestWith :: BaseEncoding -> Digest a -> Text
encodeDigestWith b = System.Nix.Base.encodeWith b . Data.ByteArray.convert
-- | Take BaseEncoding type of the input -> take the input itself -> decodeBase into Digest
decodeDigestWith
:: HashAlgorithm a
=> BaseEncoding
-> Text
-> Either String (Digest a)
decodeDigestWith b x =
do
bs <- System.Nix.Base.decodeWith b x
let
toEither =
maybeToRight
("Crypton was not able to convert '(ByteString -> Digest a)' for: '" <> show bs <>"'.")
(toEither . Crypto.Hash.digestFromByteString) bs
where
-- To not depend on @extra@
maybeToRight :: b -> Maybe a -> Either b a
maybeToRight _ (Just r) = pure r
maybeToRight y Nothing = Left y
-- | Builder for @Digest@s
digestBuilder :: forall hashAlgo . (NamedAlgo hashAlgo) => Digest hashAlgo -> Builder
digestBuilder digest =
Data.Text.Lazy.Builder.fromText (System.Nix.Hash.algoName @hashAlgo)
<> ":"
<> Data.Text.Lazy.Builder.fromText
(System.Nix.Hash.encodeDigestWith NixBase32 digest)
-- | Builder for @DSum HashAlgo Digest@s
algoDigestBuilder :: DSum HashAlgo Digest -> Builder
algoDigestBuilder (a :=> d) = has @NamedAlgo a $ digestBuilder d