{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-full-laziness #-}
module Cardano.Crypto.DSIGN.SchnorrSecp256k1 (
SchnorrSecp256k1DSIGN,
VerKeyDSIGN,
SignKeyDSIGN,
SigDSIGN,
) where
import Cardano.Binary (FromCBOR (fromCBOR), ToCBOR (encodedSizeExpr, toCBOR))
import Cardano.Crypto.DSIGN.Class (
DSIGNAlgorithm (
SeedSizeDSIGN,
SigDSIGN,
SignKeyDSIGN,
Signable,
SizeSigDSIGN,
SizeSignKeyDSIGN,
SizeVerKeyDSIGN,
VerKeyDSIGN,
algorithmNameDSIGN,
deriveVerKeyDSIGN,
genKeyDSIGN,
rawDeserialiseSigDSIGN,
rawDeserialiseSignKeyDSIGN,
rawDeserialiseVerKeyDSIGN,
rawSerialiseSigDSIGN,
rawSerialiseSignKeyDSIGN,
rawSerialiseVerKeyDSIGN,
signDSIGN,
verifyDSIGN
),
decodeSigDSIGN,
decodeSignKeyDSIGN,
decodeVerKeyDSIGN,
encodeSigDSIGN,
encodeSignKeyDSIGN,
encodeVerKeyDSIGN,
encodedSigDSIGNSizeExpr,
encodedSignKeyDSIGNSizeExpr,
encodedVerKeyDSIGNSizeExpr,
seedSizeDSIGN,
)
import Cardano.Crypto.PinnedSizedBytes (
PinnedSizedBytes,
psbCreate,
psbCreateSized,
psbCreateSizedResult,
psbFromByteStringCheck,
psbToByteString,
psbUseAsSizedPtr,
)
import Cardano.Crypto.SECP256K1.C (
secpCtxPtr,
secpKeyPairCreate,
secpKeyPairXOnlyPub,
secpSchnorrSigSignCustom,
secpSchnorrSigVerify,
secpXOnlyPubkeyParse,
secpXOnlyPubkeySerialize,
)
import Cardano.Crypto.SECP256K1.Constants (
SECP256K1_SCHNORR_PRIVKEY_BYTES,
SECP256K1_SCHNORR_PUBKEY_BYTES,
SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL,
SECP256K1_SCHNORR_SIGNATURE_BYTES,
)
import Cardano.Crypto.Seed (getBytesFromSeedT)
import Cardano.Crypto.Util (SignableRepresentation (getSignableRepresentation))
import Cardano.Foreign (allocaSized)
import Control.DeepSeq (NFData)
import Control.Monad (when)
import Data.ByteString (useAsCStringLen)
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Data.Primitive.Ptr (copyPtr)
import Data.Proxy (Proxy (Proxy))
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (castPtr, nullPtr)
import GHC.Generics (Generic)
import GHC.TypeNats (natVal)
import NoThunks.Class (NoThunks)
import System.IO.Unsafe (unsafeDupablePerformIO)
data SchnorrSecp256k1DSIGN
instance DSIGNAlgorithm SchnorrSecp256k1DSIGN where
type SeedSizeDSIGN SchnorrSecp256k1DSIGN = SECP256K1_SCHNORR_PRIVKEY_BYTES
type SizeSigDSIGN SchnorrSecp256k1DSIGN = SECP256K1_SCHNORR_SIGNATURE_BYTES
type SizeSignKeyDSIGN SchnorrSecp256k1DSIGN = SECP256K1_SCHNORR_PRIVKEY_BYTES
type SizeVerKeyDSIGN SchnorrSecp256k1DSIGN = SECP256K1_SCHNORR_PUBKEY_BYTES
type Signable SchnorrSecp256k1DSIGN = SignableRepresentation
newtype VerKeyDSIGN SchnorrSecp256k1DSIGN
= VerKeySchnorrSecp256k1 (PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL)
deriving newtype (VerKeyDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerKeyDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
$c/= :: VerKeyDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
== :: VerKeyDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
$c== :: VerKeyDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
Eq, VerKeyDSIGN SchnorrSecp256k1DSIGN -> ()
forall a. (a -> ()) -> NFData a
rnf :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> ()
$crnf :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> ()
NFData)
deriving stock (Int -> VerKeyDSIGN SchnorrSecp256k1DSIGN -> ShowS
[VerKeyDSIGN SchnorrSecp256k1DSIGN] -> ShowS
VerKeyDSIGN SchnorrSecp256k1DSIGN -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerKeyDSIGN SchnorrSecp256k1DSIGN] -> ShowS
$cshowList :: [VerKeyDSIGN SchnorrSecp256k1DSIGN] -> ShowS
show :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> String
$cshow :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> String
showsPrec :: Int -> VerKeyDSIGN SchnorrSecp256k1DSIGN -> ShowS
$cshowsPrec :: Int -> VerKeyDSIGN SchnorrSecp256k1DSIGN -> ShowS
Show, forall x.
Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x
-> VerKeyDSIGN SchnorrSecp256k1DSIGN
forall x.
VerKeyDSIGN SchnorrSecp256k1DSIGN
-> Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x
-> VerKeyDSIGN SchnorrSecp256k1DSIGN
$cfrom :: forall x.
VerKeyDSIGN SchnorrSecp256k1DSIGN
-> Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) x
Generic)
deriving anyclass (Context
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
Proxy (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> String
$cshowTypeOf :: Proxy (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> String
wNoThunks :: Context
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context
-> VerKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
NoThunks)
newtype SignKeyDSIGN SchnorrSecp256k1DSIGN
= SignKeySchnorrSecp256k1 (PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN))
deriving newtype (SignKeyDSIGN SchnorrSecp256k1DSIGN
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignKeyDSIGN SchnorrSecp256k1DSIGN
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
$c/= :: SignKeyDSIGN SchnorrSecp256k1DSIGN
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
== :: SignKeyDSIGN SchnorrSecp256k1DSIGN
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
$c== :: SignKeyDSIGN SchnorrSecp256k1DSIGN
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> Bool
Eq, SignKeyDSIGN SchnorrSecp256k1DSIGN -> ()
forall a. (a -> ()) -> NFData a
rnf :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> ()
$crnf :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> ()
NFData)
deriving stock (Int -> SignKeyDSIGN SchnorrSecp256k1DSIGN -> ShowS
[SignKeyDSIGN SchnorrSecp256k1DSIGN] -> ShowS
SignKeyDSIGN SchnorrSecp256k1DSIGN -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignKeyDSIGN SchnorrSecp256k1DSIGN] -> ShowS
$cshowList :: [SignKeyDSIGN SchnorrSecp256k1DSIGN] -> ShowS
show :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> String
$cshow :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> String
showsPrec :: Int -> SignKeyDSIGN SchnorrSecp256k1DSIGN -> ShowS
$cshowsPrec :: Int -> SignKeyDSIGN SchnorrSecp256k1DSIGN -> ShowS
Show, forall x.
Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x
-> SignKeyDSIGN SchnorrSecp256k1DSIGN
forall x.
SignKeyDSIGN SchnorrSecp256k1DSIGN
-> Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x
-> SignKeyDSIGN SchnorrSecp256k1DSIGN
$cfrom :: forall x.
SignKeyDSIGN SchnorrSecp256k1DSIGN
-> Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) x
Generic)
deriving anyclass (Context
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
Proxy (SignKeyDSIGN SchnorrSecp256k1DSIGN) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SignKeyDSIGN SchnorrSecp256k1DSIGN) -> String
$cshowTypeOf :: Proxy (SignKeyDSIGN SchnorrSecp256k1DSIGN) -> String
wNoThunks :: Context
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context
-> SignKeyDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
NoThunks)
newtype SigDSIGN SchnorrSecp256k1DSIGN
= SigSchnorrSecp256k1 (PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN))
deriving newtype (SigDSIGN SchnorrSecp256k1DSIGN
-> SigDSIGN SchnorrSecp256k1DSIGN -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigDSIGN SchnorrSecp256k1DSIGN
-> SigDSIGN SchnorrSecp256k1DSIGN -> Bool
$c/= :: SigDSIGN SchnorrSecp256k1DSIGN
-> SigDSIGN SchnorrSecp256k1DSIGN -> Bool
== :: SigDSIGN SchnorrSecp256k1DSIGN
-> SigDSIGN SchnorrSecp256k1DSIGN -> Bool
$c== :: SigDSIGN SchnorrSecp256k1DSIGN
-> SigDSIGN SchnorrSecp256k1DSIGN -> Bool
Eq, SigDSIGN SchnorrSecp256k1DSIGN -> ()
forall a. (a -> ()) -> NFData a
rnf :: SigDSIGN SchnorrSecp256k1DSIGN -> ()
$crnf :: SigDSIGN SchnorrSecp256k1DSIGN -> ()
NFData)
deriving stock (Int -> SigDSIGN SchnorrSecp256k1DSIGN -> ShowS
[SigDSIGN SchnorrSecp256k1DSIGN] -> ShowS
SigDSIGN SchnorrSecp256k1DSIGN -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigDSIGN SchnorrSecp256k1DSIGN] -> ShowS
$cshowList :: [SigDSIGN SchnorrSecp256k1DSIGN] -> ShowS
show :: SigDSIGN SchnorrSecp256k1DSIGN -> String
$cshow :: SigDSIGN SchnorrSecp256k1DSIGN -> String
showsPrec :: Int -> SigDSIGN SchnorrSecp256k1DSIGN -> ShowS
$cshowsPrec :: Int -> SigDSIGN SchnorrSecp256k1DSIGN -> ShowS
Show, forall x.
Rep (SigDSIGN SchnorrSecp256k1DSIGN) x
-> SigDSIGN SchnorrSecp256k1DSIGN
forall x.
SigDSIGN SchnorrSecp256k1DSIGN
-> Rep (SigDSIGN SchnorrSecp256k1DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SigDSIGN SchnorrSecp256k1DSIGN) x
-> SigDSIGN SchnorrSecp256k1DSIGN
$cfrom :: forall x.
SigDSIGN SchnorrSecp256k1DSIGN
-> Rep (SigDSIGN SchnorrSecp256k1DSIGN) x
Generic)
deriving anyclass (Context -> SigDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
Proxy (SigDSIGN SchnorrSecp256k1DSIGN) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SigDSIGN SchnorrSecp256k1DSIGN) -> String
$cshowTypeOf :: Proxy (SigDSIGN SchnorrSecp256k1DSIGN) -> String
wNoThunks :: Context -> SigDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SigDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> SigDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SigDSIGN SchnorrSecp256k1DSIGN -> IO (Maybe ThunkInfo)
NoThunks)
algorithmNameDSIGN :: forall (proxy :: * -> *). proxy SchnorrSecp256k1DSIGN -> String
algorithmNameDSIGN proxy SchnorrSecp256k1DSIGN
_ = String
"schnorr-secp256k1"
{-# NOINLINE deriveVerKeyDSIGN #-}
deriveVerKeyDSIGN :: SignKeyDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN
deriveVerKeyDSIGN (SignKeySchnorrSecp256k1 PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
psb) =
forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
psb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
skp ->
forall (n :: Nat) b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
kpp ->
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
CInt
res <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
-> SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
-> IO CInt
secpKeyPairCreate Ptr SECP256k1Context
ctx SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
kpp SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
skp
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when
(CInt
res forall a. Eq a => a -> a -> Bool
/= CInt
1)
(forall a. HasCallStack => String -> a
error String
"deriveVerKeyDSIGN: Failed to create keypair for SchnorrSecp256k1DSIGN")
PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
xonlyPSB <- forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (PinnedSizedBytes n)
psbCreateSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
xonlyp -> do
CInt
res' <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> Ptr CInt
-> SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
-> IO CInt
secpKeyPairXOnlyPub Ptr SECP256k1Context
ctx SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
xonlyp forall a. Ptr a
nullPtr SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
kpp
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when
(CInt
res' forall a. Eq a => a -> a -> Bool
/= CInt
1)
(forall a. HasCallStack => String -> a
error String
"deriveVerKeyDSIGN: could not extract xonly pubkey for SchnorrSecp256k1DSIGN")
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN SchnorrSecp256k1DSIGN
VerKeySchnorrSecp256k1 forall a b. (a -> b) -> a -> b
$ PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
xonlyPSB
{-# NOINLINE signDSIGN #-}
signDSIGN :: forall a.
(Signable SchnorrSecp256k1DSIGN a, HasCallStack) =>
ContextDSIGN SchnorrSecp256k1DSIGN
-> a
-> SignKeyDSIGN SchnorrSecp256k1DSIGN
-> SigDSIGN SchnorrSecp256k1DSIGN
signDSIGN () a
msg (SignKeySchnorrSecp256k1 PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
skpsb) =
forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
skpsb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
skp -> do
let bs :: ByteString
bs = forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
msg
forall (n :: Nat) b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
kpp ->
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
CInt
res <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
-> SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
-> IO CInt
secpKeyPairCreate Ptr SECP256k1Context
ctx SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
kpp SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
skp
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
res forall a. Eq a => a -> a -> Bool
/= CInt
1) (forall a. HasCallStack => String -> a
error String
"signDSIGN: Failed to create keypair for SchnorrSecp256k1DSIGN")
PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
sigPSB <- forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (PinnedSizedBytes n)
psbCreateSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
sigp -> forall a. ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
msgp, Int
msgLen) -> do
CInt
res' <-
Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> Ptr CUChar
-> CSize
-> SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
-> Ptr SECP256k1SchnorrExtraParams
-> IO CInt
secpSchnorrSigSignCustom
Ptr SECP256k1Context
ctx
SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
sigp
(forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
msgp)
(forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
msgLen)
SizedPtr SECP256K1_SCHNORR_KEYPAIR_BYTES
kpp
forall a. Ptr a
nullPtr
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
res' forall a. Eq a => a -> a -> Bool
/= CInt
1) (forall a. HasCallStack => String -> a
error String
"signDSIGN: Failed to sign SchnorrSecp256k1DSIGN message")
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN)
-> SigDSIGN SchnorrSecp256k1DSIGN
SigSchnorrSecp256k1 forall a b. (a -> b) -> a -> b
$ PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
sigPSB
{-# NOINLINE verifyDSIGN #-}
verifyDSIGN :: forall a.
(Signable SchnorrSecp256k1DSIGN a, HasCallStack) =>
ContextDSIGN SchnorrSecp256k1DSIGN
-> VerKeyDSIGN SchnorrSecp256k1DSIGN
-> a
-> SigDSIGN SchnorrSecp256k1DSIGN
-> Either String ()
verifyDSIGN () (VerKeySchnorrSecp256k1 PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
pubkeyPSB) a
msg (SigSchnorrSecp256k1 PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN)
sigPSB) =
forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
pubkeyPSB forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
pkp ->
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN)
sigPSB forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
sigp -> do
let bs :: ByteString
bs = forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
msg
CInt
res <- forall a. ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
msgp, Int
msgLen) ->
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> Ptr CUChar
-> CSize
-> SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> CInt
secpSchnorrSigVerify
Ptr SECP256k1Context
ctx
SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
sigp
(forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
msgp)
(forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
msgLen)
SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
pkp
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
if CInt
res forall a. Eq a => a -> a -> Bool
== CInt
0
then forall a b. a -> Either a b
Left String
"SigDSIGN SchnorrSecp256k1DSIGN failed to verify."
else forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
{-# NOINLINE genKeyDSIGN #-}
genKeyDSIGN :: Seed -> SignKeyDSIGN SchnorrSecp256k1DSIGN
genKeyDSIGN Seed
seed =
PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
-> SignKeyDSIGN SchnorrSecp256k1DSIGN
SignKeySchnorrSecp256k1 forall a b. (a -> b) -> a -> b
$
let (ByteString
bs, Seed
_) = Word -> Seed -> (ByteString, Seed)
getBytesFromSeedT (forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
seedSizeDSIGN (forall {k} (t :: k). Proxy t
Proxy @SchnorrSecp256k1DSIGN)) Seed
seed
in forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(Ptr Word8 -> m ()) -> m (PinnedSizedBytes n)
psbCreate forall a b. (a -> b) -> a -> b
$ \Ptr Word8
skp ->
forall a. ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
bsp, Int
sz) ->
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Ptr a -> Ptr a -> Int -> m ()
copyPtr Ptr Word8
skp (forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
bsp) Int
sz
rawSerialiseSigDSIGN :: SigDSIGN SchnorrSecp256k1DSIGN -> ByteString
rawSerialiseSigDSIGN (SigSchnorrSecp256k1 PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN)
sigPSB) = forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN)
sigPSB
{-# NOINLINE rawSerialiseVerKeyDSIGN #-}
rawSerialiseVerKeyDSIGN :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> ByteString
rawSerialiseVerKeyDSIGN (VerKeySchnorrSecp256k1 PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
vkPSB) =
forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
vkPSB forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
pkbPtr -> do
PinnedSizedBytes SECP256K1_SCHNORR_PRIVKEY_BYTES
res <- forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (PinnedSizedBytes n)
psbCreateSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
bsPtr ->
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
CInt
res' <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
-> SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> IO CInt
secpXOnlyPubkeySerialize Ptr SECP256k1Context
ctx SizedPtr SECP256K1_SCHNORR_PRIVKEY_BYTES
bsPtr SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
pkbPtr
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when
(CInt
res' forall a. Eq a => a -> a -> Bool
/= CInt
1)
(forall a. HasCallStack => String -> a
error String
"rawSerialiseVerKeyDSIGN: Failed to serialise VerKeyDSIGN SchnorrSecp256k1DSIGN")
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString forall a b. (a -> b) -> a -> b
$ PinnedSizedBytes SECP256K1_SCHNORR_PRIVKEY_BYTES
res
rawSerialiseSignKeyDSIGN :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> ByteString
rawSerialiseSignKeyDSIGN (SignKeySchnorrSecp256k1 PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
skPSB) = forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
skPSB
{-# NOINLINE rawDeserialiseVerKeyDSIGN #-}
rawDeserialiseVerKeyDSIGN :: ByteString -> Maybe (VerKeyDSIGN SchnorrSecp256k1DSIGN)
rawDeserialiseVerKeyDSIGN ByteString
bs =
forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ByteString -> (CStringLen -> IO a) -> IO a
unsafeUseAsCStringLen ByteString
bs forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
if Int
len forall a. Eq a => a -> a -> Bool
/= (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (proxy :: Nat -> *). KnownNat n => proxy n -> Nat
natVal forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @(SizeVerKeyDSIGN SchnorrSecp256k1DSIGN))
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
else do
let dataPtr :: Ptr CUChar
dataPtr = forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
ptr
(PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
vkPsb, CInt
res) <- forall (n :: Nat) r (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m r) -> m (PinnedSizedBytes n, r)
psbCreateSizedResult forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
outPtr ->
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx ->
Ptr SECP256k1Context
-> SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> Ptr CUChar
-> IO CInt
secpXOnlyPubkeyParse Ptr SECP256k1Context
ctx SizedPtr SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
outPtr Ptr CUChar
dataPtr
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case CInt
res of
CInt
1 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN SchnorrSecp256k1DSIGN
VerKeySchnorrSecp256k1 forall a b. (a -> b) -> a -> b
$ PinnedSizedBytes SECP256K1_SCHNORR_PUBKEY_BYTES_INTERNAL
vkPsb
CInt
_ -> forall a. Maybe a
Nothing
rawDeserialiseSignKeyDSIGN :: ByteString -> Maybe (SignKeyDSIGN SchnorrSecp256k1DSIGN)
rawDeserialiseSignKeyDSIGN ByteString
bs =
PinnedSizedBytes (SizeSignKeyDSIGN SchnorrSecp256k1DSIGN)
-> SignKeyDSIGN SchnorrSecp256k1DSIGN
SignKeySchnorrSecp256k1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs
rawDeserialiseSigDSIGN :: ByteString -> Maybe (SigDSIGN SchnorrSecp256k1DSIGN)
rawDeserialiseSigDSIGN ByteString
bs =
PinnedSizedBytes (SizeSigDSIGN SchnorrSecp256k1DSIGN)
-> SigDSIGN SchnorrSecp256k1DSIGN
SigSchnorrSecp256k1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs
instance ToCBOR (VerKeyDSIGN SchnorrSecp256k1DSIGN) where
toCBOR :: VerKeyDSIGN SchnorrSecp256k1DSIGN -> Encoding
toCBOR = forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> Encoding
encodeVerKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr
instance FromCBOR (VerKeyDSIGN SchnorrSecp256k1DSIGN) where
fromCBOR :: forall s. Decoder s (VerKeyDSIGN SchnorrSecp256k1DSIGN)
fromCBOR = forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
decodeVerKeyDSIGN
instance ToCBOR (SignKeyDSIGN SchnorrSecp256k1DSIGN) where
toCBOR :: SignKeyDSIGN SchnorrSecp256k1DSIGN -> Encoding
toCBOR = forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> Encoding
encodeSignKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SignKeyDSIGN SchnorrSecp256k1DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDSIGNSizeExpr
instance FromCBOR (SignKeyDSIGN SchnorrSecp256k1DSIGN) where
fromCBOR :: forall s. Decoder s (SignKeyDSIGN SchnorrSecp256k1DSIGN)
fromCBOR = forall v s. DSIGNAlgorithm v => Decoder s (SignKeyDSIGN v)
decodeSignKeyDSIGN
instance ToCBOR (SigDSIGN SchnorrSecp256k1DSIGN) where
toCBOR :: SigDSIGN SchnorrSecp256k1DSIGN -> Encoding
toCBOR = forall v. DSIGNAlgorithm v => SigDSIGN v -> Encoding
encodeSigDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigDSIGN SchnorrSecp256k1DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr
instance FromCBOR (SigDSIGN SchnorrSecp256k1DSIGN) where
fromCBOR :: forall s. Decoder s (SigDSIGN SchnorrSecp256k1DSIGN)
fromCBOR = forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN