Skip to content

Commit 8d72647

Browse files
committed
wip
1 parent 327ecc2 commit 8d72647

File tree

2 files changed

+201
-184
lines changed
  • pub/hs-bitcoin-keys/bitcoin-keys

2 files changed

+201
-184
lines changed

pub/hs-bitcoin-keys/bitcoin-keys/lib/Bitcoin/Keys/GHC.hs

Lines changed: 40 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -1,28 +1,29 @@
11
{-# LANGUAGE DerivingStrategies #-}
22
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
3+
34
-- | Implementation to be used when compiled with GHC
45
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
2020

2121
import Control.Monad
2222
import qualified Crypto.Secp256k1 as K
2323
import qualified Data.ByteString as B
24-
import qualified Data.ByteString.Lazy.Char8 as BL8
2524
import qualified Data.ByteString.Builder as BB
25+
import qualified Data.ByteString.Lazy.Char8 as BL8
26+
import qualified System.IO.Unsafe as Unsafe
2627

2728
--------------------------------------------------------------------------------
2829

@@ -38,9 +39,10 @@ instance Ord Prv where
3839

3940
-- | Big-endian base-16.
4041
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))))
4446

4547
-- | Obtain the 32 raw bytes inside a 'Prv' (big-endian).
4648
--
@@ -49,7 +51,7 @@ instance Show Prv where
4951
-- @
5052
prvRaw :: Prv -> B.ByteString
5153
{-# INLINE prvRaw #-}
52-
prvRaw (Prv x) = K.getSecKey x
54+
prvRaw (Prv (K.SecKey x)) = x
5355

5456
-- | Construct a 'Prv' key from its raw 32 bytes (big-endian).
5557
--
@@ -67,7 +69,7 @@ parsePrv x = do
6769
-- | Obtain the 'Pub' key for 'Prv'.
6870
prvToPub :: Prv -> Pub
6971
{-# INLINE prvToPub #-}
70-
prvToPub (Prv x) = Pub (K.derivePubKey x)
72+
prvToPub (Prv x) = Pub $ (withCtx K.derivePubKey) x
7173

7274
-- | Tweak a 'Prv'ate key by adding 'Tweak' times the generator to it.
7375
--
@@ -78,7 +80,7 @@ prvToPub (Prv x) = Pub (K.derivePubKey x)
7880
-- @
7981
prvAddTweak :: Tweak -> Prv -> Maybe Prv
8082
{-# 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
8284

8385
--------------------------------------------------------------------------------
8486

@@ -94,9 +96,10 @@ instance Ord Pub where
9496

9597
-- | SEC compressed base-16.
9698
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))))
100103

101104
-- | Obtain the 33-bytes contatining the SEC compressed 'Pub'lic key.
102105
--
@@ -105,7 +108,7 @@ instance Show Pub where
105108
-- @
106109
pubCompressed :: Pub -> B.ByteString
107110
{-# INLINE pubCompressed #-}
108-
pubCompressed (Pub x) = K.exportPubKey True x
111+
pubCompressed (Pub x) = (withCtx K.exportPubKey) True x
109112

110113
-- | Obtain the 65-bytes contatining the SEC uncompressed 'Pub'lic key.
111114
--
@@ -114,7 +117,7 @@ pubCompressed (Pub x) = K.exportPubKey True x
114117
-- @
115118
pubUncompressed :: Pub -> B.ByteString
116119
{-# INLINE pubUncompressed #-}
117-
pubUncompressed (Pub x) = K.exportPubKey False x
120+
pubUncompressed (Pub x) = (withCtx K.exportPubKey) False x
118121

119122
-- | Builds a public key from its compressed SEC-encoded bytes.
120123
--
@@ -129,7 +132,7 @@ parsePubCompressed :: B.ByteString -> Maybe Pub
129132
{-# INLINE parsePubCompressed #-}
130133
parsePubCompressed x = do
131134
guard (B.length x == 33)
132-
Pub <$> K.importPubKey x
135+
Pub <$> (withCtx K.importPubKey) x
133136

134137
-- | Tweak a 'Pub'lic key by adding 'Tweak' times the generator to it.
135138
--
@@ -140,7 +143,7 @@ parsePubCompressed x = do
140143
-- @
141144
pubAddTweak :: Tweak -> Pub -> Maybe Pub
142145
{-# 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
144147

145148
--------------------------------------------------------------------------------
146149

@@ -150,13 +153,14 @@ newtype Tweak = Tweak K.Tweak
150153
deriving newtype (Eq)
151154

152155
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
154157

155158
-- | Big-endian base-16.
156159
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)))
160164

161165
-- | Construct a 'Tweak' from its raw 32 bytes (big-endian).
162166
--
@@ -166,3 +170,6 @@ parseTweak :: B.ByteString -> Maybe Tweak
166170
parseTweak x = do
167171
guard (B.length x == 32)
168172
Tweak <$> K.tweak x
173+
174+
withCtx :: (K.Ctx -> a) -> a
175+
withCtx f = Unsafe.unsafePerformIO $ K.withContext (pure . f)

0 commit comments

Comments
 (0)