11{-# LANGUAGE DeriveGeneric #-}
22{-# LANGUAGE FlexibleContexts #-}
33{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4- {-# LANGUAGE MultiParamTypeClasses #-}
54{-# LANGUAGE ImportQualifiedPost #-}
5+ {-# LANGUAGE MultiParamTypeClasses #-}
66
77-- |
88-- Module : Crypto.Secp256k1
1212-- Portability : POSIX
1313--
1414-- Crytpographic functions from Bitcoin’s secp256k1 library.
15- module Crypto.Secp256k1
16- ( -- * Messages
17- Msg ,
18- msg ,
19- getMsg ,
20-
21- -- * Secret Keys
22- SecKey ,
23- secKey ,
24- getSecKey ,
25- derivePubKey ,
26-
27- -- * Public Keys
28- PubKey ,
29- importPubKey ,
30- exportPubKey ,
31-
32- -- * Signatures
33- Sig ,
34- signMsg ,
35- verifySig ,
36- normalizeSig ,
37-
38- -- ** DER
39- importSig ,
40- exportSig ,
41-
42- -- ** Compact
43- CompactSig ,
44- getCompactSig ,
45- compactSig ,
46- exportCompactSig ,
47- importCompactSig ,
48-
49- -- * Addition & Multiplication
50- Tweak ,
51- tweak ,
52- getTweak ,
53- tweakAddSecKey ,
54- tweakMulSecKey ,
55- tweakAddPubKey ,
56- tweakMulPubKey ,
57- combinePubKeys ,
58- tweakNegate ,
59- )
60- where
15+ --
16+ -- The API for this module may change at any time. This is an internal module only
17+ -- exposed for hacking and experimentation.
18+ module Crypto.Secp256k1.Internal.Base where
6119
6220import Control.DeepSeq (NFData )
6321import Control.Monad (replicateM , unless , (<=<) )
64- import Crypto.Secp256k1.Internal
65- import Data.Base16.Types (assertBase16 , extractBase16 )
22+ import Crypto.Secp256k1.Internal.BaseOps
23+ ( ecPubKeyCombine ,
24+ ecPubKeyCreate ,
25+ ecPubKeyParse ,
26+ ecPubKeySerialize ,
27+ ecPubKeyTweakAdd ,
28+ ecPubKeyTweakMul ,
29+ ecSecKeyTweakAdd ,
30+ ecSecKeyTweakMul ,
31+ ecTweakNegate ,
32+ ecdsaSign ,
33+ ecdsaSignatureNormalize ,
34+ ecdsaSignatureParseCompact ,
35+ ecdsaSignatureParseDer ,
36+ ecdsaSignatureSerializeCompact ,
37+ ecdsaSignatureSerializeDer ,
38+ ecdsaVerify ,
39+ )
40+ import Crypto.Secp256k1.Internal.Context (ctx )
41+ import Crypto.Secp256k1.Internal.ForeignTypes
42+ ( compressed ,
43+ isSuccess ,
44+ uncompressed ,
45+ )
46+ import Crypto.Secp256k1.Internal.Util
47+ ( decodeHex ,
48+ packByteString ,
49+ showsHex ,
50+ unsafePackByteString ,
51+ unsafeUseByteString ,
52+ )
6653import Data.ByteString (ByteString )
6754import Data.ByteString qualified as BS
68- import Data.ByteString.Base16 (decodeBase16 , encodeBase16 , isBase16 )
6955import Data.Hashable (Hashable (.. ))
7056import Data.Maybe (fromJust , fromMaybe , isJust )
7157import Data.Serialize
@@ -74,7 +60,6 @@ import Data.Serialize
7460 putByteString ,
7561 )
7662import Data.String (IsString (.. ))
77- import Data.String.Conversions (ConvertibleStrings , cs )
7863import Foreign
7964 ( alloca ,
8065 allocaArray ,
@@ -144,12 +129,6 @@ instance Serialize CompactSig where
144129 put (CompactSig bs) = putByteString bs
145130 get = CompactSig <$> getByteString 64
146131
147- decodeHex :: (ConvertibleStrings a ByteString ) => a -> Maybe ByteString
148- decodeHex str =
149- if isBase16 $ cs str
150- then Just . decodeBase16 $ assertBase16 $ cs str
151- else Nothing
152-
153132instance Read PubKey where
154133 readPrec = do
155134 String str <- lexP
@@ -164,7 +143,7 @@ instance IsString PubKey where
164143 e = error " Could not decode public key from hex string"
165144
166145instance Show PubKey where
167- showsPrec _ = shows . extractBase16 . encodeBase16 . exportPubKey True
146+ showsPrec _ = showsHex . exportPubKey True
168147
169148instance Read Msg where
170149 readPrec = parens $ do
@@ -180,7 +159,7 @@ instance IsString Msg where
180159 e = error " Could not decode message from hex string"
181160
182161instance Show Msg where
183- showsPrec _ = shows . extractBase16 . encodeBase16 . getMsg
162+ showsPrec _ = showsHex . getMsg
184163
185164instance Read Sig where
186165 readPrec = parens $ do
@@ -196,7 +175,7 @@ instance Hashable Sig where
196175 i `hashWithSalt` s = i `hashWithSalt` exportSig s
197176
198177instance Show Sig where
199- showsPrec _ = shows . extractBase16 . encodeBase16 . exportSig
178+ showsPrec _ = showsHex . exportSig
200179
201180instance Read SecKey where
202181 readPrec = parens $ do
@@ -212,7 +191,7 @@ instance IsString SecKey where
212191 e = error " Colud not decode secret key from hex string"
213192
214193instance Show SecKey where
215- showsPrec _ = shows . extractBase16 . encodeBase16 . getSecKey
194+ showsPrec _ = showsHex . getSecKey
216195
217196instance Hashable Tweak where
218197 i `hashWithSalt` t = i `hashWithSalt` getTweak t
@@ -228,7 +207,7 @@ instance IsString Tweak where
228207 e = error " Could not decode tweak from hex string"
229208
230209instance Show Tweak where
231- showsPrec _ = shows . extractBase16 . encodeBase16 . getTweak
210+ showsPrec _ = showsHex . getTweak
232211
233212-- | Import 32-byte 'ByteString' as 'Msg'.
234213msg :: ByteString -> Maybe Msg
0 commit comments