@@ -25,6 +25,7 @@ module Crypto.Secp256k1 (
2525 KeyPair ,
2626 Signature ,
2727 RecoverableSignature ,
28+ SchnorrSignature ,
2829 Tweak ,
2930
3031 -- * Parsing and Serialization
@@ -40,6 +41,8 @@ module Crypto.Secp256k1 (
4041 exportSignatureDer ,
4142 importRecoverableSignature ,
4243 exportRecoverableSignature ,
44+ importSchnorrSignature ,
45+ exportSchnorrSignature ,
4346 importTweak ,
4447
4548 -- * ECDSA Operations
@@ -73,6 +76,8 @@ module Crypto.Secp256k1 (
7376
7477 -- * Schnorr Operations
7578 schnorrSign ,
79+ schnorrSignDeterministic ,
80+ schnorrSignNondeterministic ,
7681 schnorrVerify ,
7782
7883 -- * Other
@@ -140,6 +145,7 @@ import Foreign.Storable (Storable (..))
140145import GHC.Generics (Generic )
141146import GHC.IO.Handle.Text (memcpy )
142147import System.IO.Unsafe (unsafePerformIO )
148+ import System.Random (StdGen , newStdGen , randoms , randomIO )
143149import Text.Read (
144150 Lexeme (String ),
145151 lexP ,
@@ -283,6 +289,28 @@ instance NFData Signature where
283289 rnf Signature {.. } = seq signatureFPtr ()
284290
285291
292+ -- | Structure containing Schnorr Signature
293+ newtype SchnorrSignature = SchnorrSignature { schnorrSignatureFPtr :: ForeignPtr Prim. Sig64}
294+
295+
296+ instance Show SchnorrSignature where
297+ show sig = (B8. unpack . encodeBase16) (exportSchnorrSignature sig)
298+ instance Read SchnorrSignature where
299+ readsPrec i cs = case decodeBase16 $ B8. pack token of
300+ Left e -> []
301+ Right a -> maybeToList $ (,rest) <$> importSchnorrSignature a
302+ where
303+ trimmed = dropWhile isSpace cs
304+ (token, rest) = span isAlphaNum trimmed
305+ instance Eq SchnorrSignature where
306+ sig == sig' = unsafePerformIO . evalContT $ do
307+ sigp <- ContT $ withForeignPtr (schnorrSignatureFPtr sig)
308+ sigp' <- ContT $ withForeignPtr (schnorrSignatureFPtr sig')
309+ (EQ == ) <$> lift (memCompare (castPtr sigp) (castPtr sigp') 64 )
310+ instance NFData SchnorrSignature where
311+ rnf SchnorrSignature {.. } = seq schnorrSignatureFPtr ()
312+
313+
286314-- | Structure containing Signature AND recovery ID
287315newtype RecoverableSignature = RecoverableSignature { recoverableSignatureFPtr :: ForeignPtr Prim. RecSig65}
288316
@@ -493,6 +521,23 @@ exportRecoverableSignature RecoverableSignature{..} = unsafePerformIO . evalCont
493521 unsafePackByteString (outBuf, 65 )
494522
495523
524+ -- | Parses 'SchnorrSignature' from Schnorr (64 byte) representation
525+ importSchnorrSignature :: ByteString -> Maybe SchnorrSignature
526+ importSchnorrSignature bs
527+ | BS. length bs /= 64 = Nothing
528+ | otherwise = unsafePerformIO $ do
529+ outBuf <- mallocBytes 64
530+ unsafeUseByteString bs $ \ (ptr, _) -> do
531+ memcpy outBuf ptr 64
532+ Just . SchnorrSignature <$> newForeignPtr finalizerFree outBuf
533+
534+
535+ -- | Serializes 'SchnorrSignature' to Schnorr (64 byte) representation
536+ exportSchnorrSignature :: SchnorrSignature -> ByteString
537+ exportSchnorrSignature (SchnorrSignature fptr) = unsafePerformIO $
538+ withForeignPtr fptr $ \ ptr -> BS. packCStringLen (castPtr ptr, 64 )
539+
540+
496541-- | Parses 'Tweak' from 32 byte @ByteString@. If the @ByteString@ is an invalid 'SecKey' then this will yield @Nothing@
497542importTweak :: ByteString -> Maybe Tweak
498543importTweak = fmap (Tweak . castForeignPtr . secKeyFPtr) . importSecKey
@@ -700,30 +745,47 @@ keyPairPubKeyXOTweakAdd KeyPair{..} Tweak{..} = unsafePerformIO . evalContT $ do
700745 else free keyPairOut $> Nothing
701746
702747
703- -- | Compute a schnorr signature using a 'KeyPair'. The @ByteString@ must be 32 bytes long to get a @Just@ out of this
704- -- function
705- schnorrSign :: KeyPair -> ByteString -> Maybe Signature
706- schnorrSign KeyPair {.. } bs
748+ -- | Compute a schnorr signature using a 'KeyPair'. The @ByteString@ must be 32 bytes long to get
749+ -- a @Just@ out of this function. Optionally takes a 'StdGen' for deterministic signing.
750+ schnorrSign :: Maybe StdGen -> KeyPair -> ByteString -> Maybe SchnorrSignature
751+ schnorrSign mGen KeyPair {.. } bs
707752 | BS. length bs /= 32 = Nothing
708753 | otherwise = unsafePerformIO . evalContT $ do
709754 (msgHashPtr, _) <- ContT (unsafeUseByteString bs)
710755 keyPairPtr <- ContT (withForeignPtr keyPairFPtr)
711756 lift $ do
712757 sigBuf <- mallocBytes 64
713- -- TODO: provide randomness here instead of supplying a null pointer
714- ret <- Prim. schnorrsigSign ctx sigBuf msgHashPtr keyPairPtr nullPtr
758+ ret <- case mGen of
759+ Just gen -> do
760+ let randomBytes = BS. pack $ Prelude. take 32 $ randoms gen
761+ BS. useAsCStringLen randomBytes $ \ (ptr, _) ->
762+ Prim. schnorrsigSign ctx sigBuf msgHashPtr keyPairPtr (castPtr ptr)
763+ Nothing ->
764+ Prim. schnorrsigSign ctx sigBuf msgHashPtr keyPairPtr nullPtr
715765 if isSuccess ret
716- then Just . Signature <$> newForeignPtr finalizerFree sigBuf
717- else free sigBuf $> Nothing
766+ then Just . SchnorrSignature <$> newForeignPtr finalizerFree sigBuf
767+ else do
768+ free sigBuf
769+ return Nothing
770+
771+
772+ -- | Compute a deterministic schnorr signature using a 'KeyPair'.
773+ schnorrSignDeterministic :: KeyPair -> ByteString -> Maybe SchnorrSignature
774+ schnorrSignDeterministic = schnorrSign Nothing
775+
776+
777+ -- | Compute a non-deterministic schnorr signature using a 'KeyPair'.
778+ schnorrSignNondeterministic :: KeyPair -> ByteString -> IO (Maybe SchnorrSignature )
779+ schnorrSignNondeterministic kp bs = newStdGen >>= \ gen -> pure $ schnorrSign (Just gen) kp bs
718780
719781
720782-- | Verify the authenticity of a schnorr signature. @True@ means the 'Signature' is correct.
721- schnorrVerify :: PubKeyXO -> ByteString -> Signature -> Bool
722- schnorrVerify PubKeyXO {.. } bs Signature {.. } = unsafePerformIO . evalContT $ do
783+ schnorrVerify :: PubKeyXO -> ByteString -> SchnorrSignature -> Bool
784+ schnorrVerify PubKeyXO {.. } bs SchnorrSignature {.. } = unsafePerformIO . evalContT $ do
723785 pubKeyPtr <- ContT (withForeignPtr pubKeyXOFPtr)
724- signaturePtr <- ContT (withForeignPtr signatureFPtr )
786+ schnorrSignaturePtr <- ContT (withForeignPtr schnorrSignatureFPtr )
725787 (msgPtr, msgLen) <- ContT (unsafeUseByteString bs)
726- lift $ isSuccess <$> Prim. schnorrsigSignVerify ctx signaturePtr msgPtr msgLen pubKeyPtr
788+ lift $ isSuccess <$> Prim. schnorrsigSignVerify ctx schnorrSignaturePtr msgPtr msgLen pubKeyPtr
727789
728790
729791-- | Generate a tagged sha256 digest as specified in BIP340
0 commit comments