2
2
{-# LANGUAGE DeriveGeneric #-}
3
3
{-# LANGUAGE TypeApplications #-}
4
4
5
- {- |
6
- Module : Haskoin.Crypto.Hash
7
- Copyright : No rights reserved
8
- License : MIT
9
-
10
- Stability : experimental
11
- Portability : POSIX
12
-
13
- Hashing functions and corresponding data types. Uses functions from the
14
- cryptonite library.
15
- -}
5
+ -- |
6
+ -- Module : Haskoin.Crypto.Hash
7
+ -- Copyright : No rights reserved
8
+ -- License : MIT
9
+
10
+ -- Stability : experimental
11
+ -- Portability : POSIX
12
+ --
13
+ -- Hashing functions and corresponding data types. Uses functions from the
14
+ -- cryptonite library.
16
15
module Haskoin.Crypto.Hash (
17
16
-- * Hashes
18
17
Hash512 (getHash512 ),
@@ -45,7 +44,6 @@ import Crypto.Hash (
45
44
hashWith ,
46
45
)
47
46
import Crypto.MAC.HMAC (HMAC , hmac )
48
- import Data.Binary (Binary (.. ))
49
47
import Data.ByteArray (ByteArrayAccess )
50
48
import qualified Data.ByteArray as BA
51
49
import Data.ByteString (ByteString )
@@ -57,64 +55,66 @@ import qualified Data.Bytes.Put as Put
57
55
import Data.Bytes.Serial (Serial (.. ))
58
56
import Data.Either (fromRight )
59
57
import Data.Hashable (Hashable )
60
- import Data.Serialize (Serialize (.. ))
61
58
import Data.String (IsString , fromString )
62
59
import Data.String.Conversions (cs )
63
60
import Data.Word (Word32 )
64
61
import GHC.Generics (Generic )
65
62
import Haskoin.Util
66
63
import Text.Read as R
67
64
65
+
68
66
-- | 'Word32' wrapped for type-safe 32-bit checksums.
69
67
newtype CheckSum32 = CheckSum32
70
68
{ getCheckSum32 :: Word32
71
69
}
72
70
deriving (Eq , Ord , Serial , Show , Read , Hashable , Generic , NFData )
73
71
74
- instance Serialize CheckSum32 where
75
- put = serialize
76
- get = deserialize
77
-
78
- instance Binary CheckSum32 where
79
- put = serialize
80
- get = deserialize
81
72
82
73
-- | Type for 512-bit hashes.
83
74
newtype Hash512 = Hash512 { getHash512 :: ShortByteString }
84
75
deriving (Eq , Ord , Hashable , Generic , NFData )
85
76
77
+
86
78
-- | Type for 256-bit hashes.
87
79
newtype Hash256 = Hash256 { getHash256 :: ShortByteString }
88
80
deriving (Eq , Ord , Hashable , Generic , NFData )
89
81
82
+
90
83
-- | Type for 160-bit hashes.
91
84
newtype Hash160 = Hash160 { getHash160 :: ShortByteString }
92
85
deriving (Eq , Ord , Hashable , Generic , NFData )
93
86
87
+
94
88
instance Show Hash512 where
95
89
showsPrec _ = shows . encodeHex . BSS. fromShort . getHash512
96
90
91
+
97
92
instance Read Hash512 where
98
93
readPrec = do
99
94
R. String str <- lexP
100
95
maybe pfail return $ Hash512 . BSS. toShort <$> decodeHex (cs str)
101
96
97
+
102
98
instance Show Hash256 where
103
99
showsPrec _ = shows . encodeHex . BSS. fromShort . getHash256
104
100
101
+
105
102
instance Read Hash256 where
106
103
readPrec = do
107
104
R. String str <- lexP
108
105
maybe pfail return $ Hash256 . BSS. toShort <$> decodeHex (cs str)
109
106
107
+
110
108
instance Show Hash160 where
111
109
showsPrec _ = shows . encodeHex . BSS. fromShort . getHash160
112
110
111
+
113
112
instance Read Hash160 where
114
113
readPrec = do
115
114
R. String str <- lexP
116
115
maybe pfail return $ Hash160 . BSS. toShort <$> decodeHex (cs str)
117
116
117
+
118
118
instance IsString Hash512 where
119
119
fromString str =
120
120
case decodeHex $ cs str of
@@ -123,20 +123,14 @@ instance IsString Hash512 where
123
123
case BS. length bs of
124
124
64 -> Hash512 (BSS. toShort bs)
125
125
_ -> e
126
- where
127
- e = error " Could not decode hash from hex string"
126
+ where
127
+ e = error " Could not decode hash from hex string"
128
+
128
129
129
130
instance Serial Hash512 where
130
131
deserialize = Hash512 . BSS. toShort <$> Get. getByteString 64
131
132
serialize = Put. putByteString . BSS. fromShort . getHash512
132
133
133
- instance Serialize Hash512 where
134
- put = serialize
135
- get = deserialize
136
-
137
- instance Binary Hash512 where
138
- put = serialize
139
- get = deserialize
140
134
141
135
instance IsString Hash256 where
142
136
fromString str =
@@ -146,20 +140,14 @@ instance IsString Hash256 where
146
140
case BS. length bs of
147
141
32 -> Hash256 (BSS. toShort bs)
148
142
_ -> e
149
- where
150
- e = error " Could not decode hash from hex string"
143
+ where
144
+ e = error " Could not decode hash from hex string"
145
+
151
146
152
147
instance Serial Hash256 where
153
148
deserialize = Hash256 . BSS. toShort <$> Get. getByteString 32
154
149
serialize = Put. putByteString . BSS. fromShort . getHash256
155
150
156
- instance Serialize Hash256 where
157
- put = serialize
158
- get = deserialize
159
-
160
- instance Binary Hash256 where
161
- put = serialize
162
- get = deserialize
163
151
164
152
instance IsString Hash160 where
165
153
fromString str =
@@ -169,47 +157,47 @@ instance IsString Hash160 where
169
157
case BS. length bs of
170
158
20 -> Hash160 (BSS. toShort bs)
171
159
_ -> e
172
- where
173
- e = error " Could not decode hash from hex string"
160
+ where
161
+ e = error " Could not decode hash from hex string"
162
+
174
163
175
164
instance Serial Hash160 where
176
165
deserialize = Hash160 . BSS. toShort <$> Get. getByteString 20
177
166
serialize = Put. putByteString . BSS. fromShort . getHash160
178
167
179
- instance Serialize Hash160 where
180
- put = serialize
181
- get = deserialize
182
-
183
- instance Binary Hash160 where
184
- put = serialize
185
- get = deserialize
186
168
187
169
-- | Calculate SHA512 hash.
188
170
sha512 :: ByteArrayAccess b => b -> Hash512
189
171
sha512 = Hash512 . BSS. toShort . BA. convert . hashWith SHA512
190
172
173
+
191
174
-- | Calculate SHA256 hash.
192
175
sha256 :: ByteArrayAccess b => b -> Hash256
193
176
sha256 = Hash256 . BSS. toShort . BA. convert . hashWith SHA256
194
177
178
+
195
179
-- | Calculate RIPEMD160 hash.
196
180
ripemd160 :: ByteArrayAccess b => b -> Hash160
197
181
ripemd160 = Hash160 . BSS. toShort . BA. convert . hashWith RIPEMD160
198
182
183
+
199
184
-- | Claculate SHA1 hash.
200
185
sha1 :: ByteArrayAccess b => b -> Hash160
201
186
sha1 = Hash160 . BSS. toShort . BA. convert . hashWith SHA1
202
187
188
+
203
189
-- | Compute two rounds of SHA-256.
204
190
doubleSHA256 :: ByteArrayAccess b => b -> Hash256
205
191
doubleSHA256 =
206
192
Hash256 . BSS. toShort . BA. convert . hashWith SHA256 . hashWith SHA256
207
193
194
+
208
195
-- | Compute SHA-256 followed by RIPMED-160.
209
196
addressHash :: ByteArrayAccess b => b -> Hash160
210
197
addressHash =
211
198
Hash160 . BSS. toShort . BA. convert . hashWith RIPEMD160 . hashWith SHA256
212
199
200
+
213
201
{- CheckSum -}
214
202
215
203
-- | Computes a 32 bit checksum.
@@ -222,24 +210,28 @@ checkSum32 =
222
210
. hashWith SHA256
223
211
. hashWith SHA256
224
212
213
+
225
214
{- HMAC -}
226
215
227
216
-- | Computes HMAC over SHA-512.
228
217
hmac512 :: ByteString -> ByteString -> Hash512
229
218
hmac512 key msg =
230
219
Hash512 $ BSS. toShort $ BA. convert (hmac key msg :: HMAC SHA512 )
231
220
221
+
232
222
-- | Computes HMAC over SHA-256.
233
223
hmac256 :: (ByteArrayAccess k , ByteArrayAccess m ) => k -> m -> Hash256
234
224
hmac256 key msg =
235
225
Hash256 $ BSS. toShort $ BA. convert (hmac key msg :: HMAC SHA256 )
236
226
227
+
237
228
-- | Split a 'Hash512' into a pair of 'Hash256'.
238
229
split512 :: Hash512 -> (Hash256 , Hash256 )
239
230
split512 h =
240
231
(Hash256 (BSS. toShort a), Hash256 (BSS. toShort b))
241
- where
242
- (a, b) = BS. splitAt 32 . BSS. fromShort $ getHash512 h
232
+ where
233
+ (a, b) = BS. splitAt 32 . BSS. fromShort $ getHash512 h
234
+
243
235
244
236
-- | Join a pair of 'Hash256' into a 'Hash512'.
245
237
join512 :: (Hash256 , Hash256 ) -> Hash512
@@ -248,16 +240,16 @@ join512 (a, b) =
248
240
. BSS. toShort
249
241
$ BSS. fromShort (getHash256 a) `BS.append` BSS. fromShort (getHash256 b)
250
242
251
- {- | Initialize tagged hash specified in BIP340
252
243
253
- @since 0.21.0
254
- -}
244
+ -- | Initialize tagged hash specified in BIP340
245
+ --
246
+ -- @since 0.21.0
255
247
initTaggedHash ::
256
248
-- | Hash tag
257
249
ByteString ->
258
250
Context SHA256
259
251
initTaggedHash tag =
260
252
(`hashUpdates` [hashedTag, hashedTag]) $
261
253
hashInit @ SHA256
262
- where
263
- hashedTag = hashWith SHA256 tag
254
+ where
255
+ hashedTag = hashWith SHA256 tag
0 commit comments