1
1
{-# LANGUAGE DerivingStrategies #-}
2
2
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3
+
3
4
-- | Implementation to be used when compiled with GHC
4
5
module Bitcoin.Keys.GHC
5
- ( Prv
6
- , parsePrv
7
- , prvRaw
8
- , prvToPub
9
- , prvAddTweak
10
-
11
- , Pub
12
- , parsePubCompressed
13
- , pubCompressed
14
- , pubUncompressed
15
- , pubAddTweak
16
-
17
- , Tweak
18
- , parseTweak
19
- ) where
6
+ ( Prv ,
7
+ parsePrv ,
8
+ prvRaw ,
9
+ prvToPub ,
10
+ prvAddTweak ,
11
+ Pub ,
12
+ parsePubCompressed ,
13
+ pubCompressed ,
14
+ pubUncompressed ,
15
+ pubAddTweak ,
16
+ Tweak ,
17
+ parseTweak ,
18
+ )
19
+ where
20
20
21
21
import Control.Monad
22
22
import qualified Crypto.Secp256k1 as K
23
23
import qualified Data.ByteString as B
24
- import qualified Data.ByteString.Lazy.Char8 as BL8
25
24
import qualified Data.ByteString.Builder as BB
25
+ import qualified Data.ByteString.Lazy.Char8 as BL8
26
+ import qualified System.IO.Unsafe as Unsafe
26
27
27
28
--------------------------------------------------------------------------------
28
29
@@ -38,9 +39,10 @@ instance Ord Prv where
38
39
39
40
-- | Big-endian base-16.
40
41
instance Show Prv where
41
- showsPrec n p = showParen (n > 10 ) $
42
- showString " Prv " .
43
- mappend (BL8. unpack (BB. toLazyByteString (BB. byteStringHex (prvRaw p))))
42
+ showsPrec n p =
43
+ showParen (n > 10 ) $
44
+ showString " Prv "
45
+ . mappend (BL8. unpack (BB. toLazyByteString (BB. byteStringHex (prvRaw p))))
44
46
45
47
-- | Obtain the 32 raw bytes inside a 'Prv' (big-endian).
46
48
--
@@ -49,7 +51,7 @@ instance Show Prv where
49
51
-- @
50
52
prvRaw :: Prv -> B. ByteString
51
53
{-# INLINE prvRaw #-}
52
- prvRaw (Prv x) = K. getSecKey x
54
+ prvRaw (Prv ( K. SecKey x)) = x
53
55
54
56
-- | Construct a 'Prv' key from its raw 32 bytes (big-endian).
55
57
--
@@ -67,7 +69,7 @@ parsePrv x = do
67
69
-- | Obtain the 'Pub' key for 'Prv'.
68
70
prvToPub :: Prv -> Pub
69
71
{-# INLINE prvToPub #-}
70
- prvToPub (Prv x) = Pub ( K. derivePubKey x)
72
+ prvToPub (Prv x) = Pub $ (withCtx K. derivePubKey) x
71
73
72
74
-- | Tweak a 'Prv'ate key by adding 'Tweak' times the generator to it.
73
75
--
@@ -78,7 +80,7 @@ prvToPub (Prv x) = Pub (K.derivePubKey x)
78
80
-- @
79
81
prvAddTweak :: Tweak -> Prv -> Maybe Prv
80
82
{-# INLINE prvAddTweak #-}
81
- prvAddTweak (Tweak t) (Prv p) = Prv <$> K. tweakAddSecKey p t
83
+ prvAddTweak (Tweak t) (Prv p) = Prv <$> (withCtx K. tweakAddSecKey) p t
82
84
83
85
--------------------------------------------------------------------------------
84
86
@@ -94,9 +96,10 @@ instance Ord Pub where
94
96
95
97
-- | SEC compressed base-16.
96
98
instance Show Pub where
97
- showsPrec n p = showParen (n > 10 ) $
98
- showString " Pub " .
99
- mappend (BL8. unpack (BB. toLazyByteString (BB. byteStringHex (pubCompressed p))))
99
+ showsPrec n p =
100
+ showParen (n > 10 ) $
101
+ showString " Pub "
102
+ . mappend (BL8. unpack (BB. toLazyByteString (BB. byteStringHex (pubCompressed p))))
100
103
101
104
-- | Obtain the 33-bytes contatining the SEC compressed 'Pub'lic key.
102
105
--
@@ -105,7 +108,7 @@ instance Show Pub where
105
108
-- @
106
109
pubCompressed :: Pub -> B. ByteString
107
110
{-# INLINE pubCompressed #-}
108
- pubCompressed (Pub x) = K. exportPubKey True x
111
+ pubCompressed (Pub x) = (withCtx K. exportPubKey) True x
109
112
110
113
-- | Obtain the 65-bytes contatining the SEC uncompressed 'Pub'lic key.
111
114
--
@@ -114,7 +117,7 @@ pubCompressed (Pub x) = K.exportPubKey True x
114
117
-- @
115
118
pubUncompressed :: Pub -> B. ByteString
116
119
{-# INLINE pubUncompressed #-}
117
- pubUncompressed (Pub x) = K. exportPubKey False x
120
+ pubUncompressed (Pub x) = (withCtx K. exportPubKey) False x
118
121
119
122
-- | Builds a public key from its compressed SEC-encoded bytes.
120
123
--
@@ -129,7 +132,7 @@ parsePubCompressed :: B.ByteString -> Maybe Pub
129
132
{-# INLINE parsePubCompressed #-}
130
133
parsePubCompressed x = do
131
134
guard (B. length x == 33 )
132
- Pub <$> K. importPubKey x
135
+ Pub <$> (withCtx K. importPubKey) x
133
136
134
137
-- | Tweak a 'Pub'lic key by adding 'Tweak' times the generator to it.
135
138
--
@@ -140,7 +143,7 @@ parsePubCompressed x = do
140
143
-- @
141
144
pubAddTweak :: Tweak -> Pub -> Maybe Pub
142
145
{-# INLINE pubAddTweak #-}
143
- pubAddTweak (Tweak t) (Pub p) = Pub <$> K. tweakAddPubKey p t
146
+ pubAddTweak (Tweak t) (Pub p) = Pub <$> (withCtx K. tweakAddPubKey) p t
144
147
145
148
--------------------------------------------------------------------------------
146
149
@@ -150,13 +153,14 @@ newtype Tweak = Tweak K.Tweak
150
153
deriving newtype (Eq )
151
154
152
155
instance Ord Tweak where
153
- compare (Tweak a) (Tweak b) = compare ( K. getTweak a) ( K. getTweak b)
156
+ compare (Tweak ( K. Tweak a)) (Tweak ( K. Tweak b)) = compare a b
154
157
155
158
-- | Big-endian base-16.
156
159
instance Show Tweak where
157
- showsPrec n (Tweak x) = showParen (n > 10 ) $
158
- showString " Tweak " .
159
- mappend (BL8. unpack (BB. toLazyByteString (BB. byteStringHex (K. getTweak x))))
160
+ showsPrec n (Tweak (K. Tweak x)) =
161
+ showParen (n > 10 ) $
162
+ showString " Tweak "
163
+ . mappend (BL8. unpack (BB. toLazyByteString (BB. byteStringHex x)))
160
164
161
165
-- | Construct a 'Tweak' from its raw 32 bytes (big-endian).
162
166
--
@@ -166,3 +170,6 @@ parseTweak :: B.ByteString -> Maybe Tweak
166
170
parseTweak x = do
167
171
guard (B. length x == 32 )
168
172
Tweak <$> K. tweak x
173
+
174
+ withCtx :: (K. Ctx -> a ) -> a
175
+ withCtx f = Unsafe. unsafePerformIO $ K. withContext (pure . f)
0 commit comments