{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
{-# OPTIONS_GHC -fno-full-laziness #-}
module Cardano.Crypto.DSIGN.EcdsaSecp256k1 (
MessageHash,
toMessageHash,
fromMessageHash,
hashAndPack,
EcdsaSecp256k1DSIGN,
VerKeyDSIGN (..),
SignKeyDSIGN (..),
SigDSIGN (..)
) where
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Storable (poke, peek)
import Foreign.C.Types (CSize)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr (castPtr, nullPtr, Ptr)
import Control.Monad (when, void, unless)
import Cardano.Crypto.Hash.Class (HashAlgorithm (SizeHash, digest))
import Data.Proxy (Proxy)
import Cardano.Binary (FromCBOR (fromCBOR), ToCBOR (toCBOR, encodedSizeExpr))
import Data.ByteString (ByteString)
import Crypto.Random (getRandomBytes)
import Cardano.Crypto.Seed (runMonadRandomWithSeed)
import Data.Kind (Type)
import GHC.Generics (Generic)
import Control.DeepSeq (NFData)
import NoThunks.Class (NoThunks)
import Cardano.Crypto.DSIGN.Class (
DSIGNAlgorithm (VerKeyDSIGN,
SignKeyDSIGN,
SigDSIGN,
SeedSizeDSIGN,
SizeSigDSIGN,
SizeSignKeyDSIGN,
SizeVerKeyDSIGN,
algorithmNameDSIGN,
deriveVerKeyDSIGN,
signDSIGN,
verifyDSIGN,
genKeyDSIGN,
rawSerialiseSigDSIGN,
Signable,
rawSerialiseVerKeyDSIGN,
rawSerialiseSignKeyDSIGN,
rawDeserialiseVerKeyDSIGN,
rawDeserialiseSignKeyDSIGN,
rawDeserialiseSigDSIGN),
encodeVerKeyDSIGN,
encodedVerKeyDSIGNSizeExpr,
decodeVerKeyDSIGN,
encodeSignKeyDSIGN,
encodedSignKeyDESIGNSizeExpr,
decodeSignKeyDSIGN,
encodeSigDSIGN,
encodedSigDSIGNSizeExpr,
decodeSigDSIGN
)
import Cardano.Crypto.SECP256K1.Constants (
SECP256K1_ECDSA_PRIVKEY_BYTES,
SECP256K1_ECDSA_SIGNATURE_BYTES,
SECP256K1_ECDSA_SIGNATURE_BYTES_INTERNAL,
SECP256K1_ECDSA_PUBKEY_BYTES,
SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL,
SECP256K1_ECDSA_MESSAGE_BYTES,
)
import Cardano.Crypto.PinnedSizedBytes (
PinnedSizedBytes,
psbUseAsSizedPtr,
psbCreateSized,
psbFromByteStringCheck,
psbToByteString,
psbCreateLen,
psbCreateSizedResult,
psbUseAsCPtrLen,
)
import System.IO.Unsafe (unsafeDupablePerformIO)
import Cardano.Crypto.SECP256K1.C (
secpEcPubkeyCreate,
secpCtxPtr,
secpEcdsaSign,
secpEcdsaVerify,
secpEcdsaSignatureSerializeCompact,
secpEcPubkeySerialize,
secpEcCompressed,
secpEcdsaSignatureParseCompact,
secpEcPubkeyParse,
)
newtype MessageHash = MH (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
deriving MessageHash -> MessageHash -> Bool
(MessageHash -> MessageHash -> Bool)
-> (MessageHash -> MessageHash -> Bool) -> Eq MessageHash
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageHash -> MessageHash -> Bool
$c/= :: MessageHash -> MessageHash -> Bool
== :: MessageHash -> MessageHash -> Bool
$c== :: MessageHash -> MessageHash -> Bool
Eq via (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
deriving stock Int -> MessageHash -> ShowS
[MessageHash] -> ShowS
MessageHash -> String
(Int -> MessageHash -> ShowS)
-> (MessageHash -> String)
-> ([MessageHash] -> ShowS)
-> Show MessageHash
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageHash] -> ShowS
$cshowList :: [MessageHash] -> ShowS
show :: MessageHash -> String
$cshow :: MessageHash -> String
showsPrec :: Int -> MessageHash -> ShowS
$cshowsPrec :: Int -> MessageHash -> ShowS
Show
toMessageHash :: ByteString -> Maybe MessageHash
toMessageHash :: ByteString -> Maybe MessageHash
toMessageHash ByteString
bs = PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES -> MessageHash
MH (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES -> MessageHash)
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
-> Maybe MessageHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs
fromMessageHash :: MessageHash -> ByteString
fromMessageHash :: MessageHash -> ByteString
fromMessageHash (MH PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb) = PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES -> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb
hashAndPack :: forall (h :: Type) .
(HashAlgorithm h, SizeHash h ~ SECP256K1_ECDSA_MESSAGE_BYTES) =>
Proxy h -> ByteString -> MessageHash
hashAndPack :: Proxy h -> ByteString -> MessageHash
hashAndPack Proxy h
p ByteString
bs = case ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck (ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES))
-> (ByteString -> ByteString)
-> ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy h -> ByteString -> ByteString
forall h (proxy :: * -> *).
HashAlgorithm h =>
proxy h -> ByteString -> ByteString
digest Proxy h
p (ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES))
-> ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
forall a b. (a -> b) -> a -> b
$ ByteString
bs of
Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
Nothing -> String -> MessageHash
forall a. HasCallStack => String -> a
error (String -> MessageHash) -> String -> MessageHash
forall a b. (a -> b) -> a -> b
$ String
"hashAndPack: unexpected mismatch of guaranteed hash length\n" String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
String
"Please report this, it's a bug!"
Just PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb -> PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES -> MessageHash
MH PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb
data EcdsaSecp256k1DSIGN
instance DSIGNAlgorithm EcdsaSecp256k1DSIGN where
type SeedSizeDSIGN EcdsaSecp256k1DSIGN = SECP256K1_ECDSA_PRIVKEY_BYTES
type SizeSigDSIGN EcdsaSecp256k1DSIGN = SECP256K1_ECDSA_SIGNATURE_BYTES
type SizeSignKeyDSIGN EcdsaSecp256k1DSIGN = SECP256K1_ECDSA_PRIVKEY_BYTES
type SizeVerKeyDSIGN EcdsaSecp256k1DSIGN = SECP256K1_ECDSA_PUBKEY_BYTES
type Signable EcdsaSecp256k1DSIGN = ((~) MessageHash)
newtype VerKeyDSIGN EcdsaSecp256k1DSIGN =
VerKeyEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
deriving newtype (VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
(VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool)
-> (VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool)
-> Eq (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
$c/= :: VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
== :: VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
$c== :: VerKeyDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
Eq, VerKeyDSIGN EcdsaSecp256k1DSIGN -> ()
(VerKeyDSIGN EcdsaSecp256k1DSIGN -> ())
-> NFData (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> ()
$crnf :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> ()
NFData)
deriving stock (Int -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
[VerKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
VerKeyDSIGN EcdsaSecp256k1DSIGN -> String
(Int -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS)
-> (VerKeyDSIGN EcdsaSecp256k1DSIGN -> String)
-> ([VerKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS)
-> Show (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
$cshowList :: [VerKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
show :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> String
$cshow :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> String
showsPrec :: Int -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
$cshowsPrec :: Int -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
Show, (forall x.
VerKeyDSIGN EcdsaSecp256k1DSIGN
-> Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x)
-> (forall x.
Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x
-> VerKeyDSIGN EcdsaSecp256k1DSIGN)
-> Generic (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall x.
Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
forall x.
VerKeyDSIGN EcdsaSecp256k1DSIGN
-> Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
$cfrom :: forall x.
VerKeyDSIGN EcdsaSecp256k1DSIGN
-> Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) x
Generic)
deriving anyclass (Context -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> String
(Context
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo))
-> (Context
-> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo))
-> (Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> String)
-> NoThunks (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> String
$cshowTypeOf :: Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> String
wNoThunks :: Context -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
NoThunks)
newtype SignKeyDSIGN EcdsaSecp256k1DSIGN =
SignKeyEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES)
deriving newtype (SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
(SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool)
-> (SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool)
-> Eq (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
$c/= :: SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
== :: SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
$c== :: SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> Bool
Eq, SignKeyDSIGN EcdsaSecp256k1DSIGN -> ()
(SignKeyDSIGN EcdsaSecp256k1DSIGN -> ())
-> NFData (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> ()
$crnf :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> ()
NFData)
deriving stock (Int -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
[SignKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
SignKeyDSIGN EcdsaSecp256k1DSIGN -> String
(Int -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS)
-> (SignKeyDSIGN EcdsaSecp256k1DSIGN -> String)
-> ([SignKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS)
-> Show (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SignKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
$cshowList :: [SignKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
show :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> String
$cshow :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> String
showsPrec :: Int -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
$cshowsPrec :: Int -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
Show, (forall x.
SignKeyDSIGN EcdsaSecp256k1DSIGN
-> Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x)
-> (forall x.
Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x
-> SignKeyDSIGN EcdsaSecp256k1DSIGN)
-> Generic (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall x.
Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
forall x.
SignKeyDSIGN EcdsaSecp256k1DSIGN
-> Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
$cfrom :: forall x.
SignKeyDSIGN EcdsaSecp256k1DSIGN
-> Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) x
Generic)
deriving anyclass (Context -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> String
(Context
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo))
-> (Context
-> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo))
-> (Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> String)
-> NoThunks (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> String
$cshowTypeOf :: Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> String
wNoThunks :: Context -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
NoThunks)
newtype SigDSIGN EcdsaSecp256k1DSIGN =
SigEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_SIGNATURE_BYTES_INTERNAL)
deriving newtype (SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool
(SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool)
-> (SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool)
-> Eq (SigDSIGN EcdsaSecp256k1DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool
$c/= :: SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool
== :: SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool
$c== :: SigDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN -> Bool
Eq, SigDSIGN EcdsaSecp256k1DSIGN -> ()
(SigDSIGN EcdsaSecp256k1DSIGN -> ())
-> NFData (SigDSIGN EcdsaSecp256k1DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: SigDSIGN EcdsaSecp256k1DSIGN -> ()
$crnf :: SigDSIGN EcdsaSecp256k1DSIGN -> ()
NFData)
deriving stock (Int -> SigDSIGN EcdsaSecp256k1DSIGN -> ShowS
[SigDSIGN EcdsaSecp256k1DSIGN] -> ShowS
SigDSIGN EcdsaSecp256k1DSIGN -> String
(Int -> SigDSIGN EcdsaSecp256k1DSIGN -> ShowS)
-> (SigDSIGN EcdsaSecp256k1DSIGN -> String)
-> ([SigDSIGN EcdsaSecp256k1DSIGN] -> ShowS)
-> Show (SigDSIGN EcdsaSecp256k1DSIGN)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigDSIGN EcdsaSecp256k1DSIGN] -> ShowS
$cshowList :: [SigDSIGN EcdsaSecp256k1DSIGN] -> ShowS
show :: SigDSIGN EcdsaSecp256k1DSIGN -> String
$cshow :: SigDSIGN EcdsaSecp256k1DSIGN -> String
showsPrec :: Int -> SigDSIGN EcdsaSecp256k1DSIGN -> ShowS
$cshowsPrec :: Int -> SigDSIGN EcdsaSecp256k1DSIGN -> ShowS
Show, (forall x.
SigDSIGN EcdsaSecp256k1DSIGN
-> Rep (SigDSIGN EcdsaSecp256k1DSIGN) x)
-> (forall x.
Rep (SigDSIGN EcdsaSecp256k1DSIGN) x
-> SigDSIGN EcdsaSecp256k1DSIGN)
-> Generic (SigDSIGN EcdsaSecp256k1DSIGN)
forall x.
Rep (SigDSIGN EcdsaSecp256k1DSIGN) x
-> SigDSIGN EcdsaSecp256k1DSIGN
forall x.
SigDSIGN EcdsaSecp256k1DSIGN
-> Rep (SigDSIGN EcdsaSecp256k1DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SigDSIGN EcdsaSecp256k1DSIGN) x
-> SigDSIGN EcdsaSecp256k1DSIGN
$cfrom :: forall x.
SigDSIGN EcdsaSecp256k1DSIGN
-> Rep (SigDSIGN EcdsaSecp256k1DSIGN) x
Generic)
deriving anyclass (Context -> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> String
(Context -> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo))
-> (Context
-> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo))
-> (Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> String)
-> NoThunks (SigDSIGN EcdsaSecp256k1DSIGN)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> String
$cshowTypeOf :: Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> String
wNoThunks :: Context -> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SigDSIGN EcdsaSecp256k1DSIGN -> IO (Maybe ThunkInfo)
NoThunks)
algorithmNameDSIGN :: proxy EcdsaSecp256k1DSIGN -> String
algorithmNameDSIGN proxy EcdsaSecp256k1DSIGN
_ = String
"ecdsa-secp256k1"
{-# NOINLINE deriveVerKeyDSIGN #-}
deriveVerKeyDSIGN :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> VerKeyDSIGN EcdsaSecp256k1DSIGN
deriveVerKeyDSIGN (SignKeyEcdsaSecp256k1 skBytes) =
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
VerKeyEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN EcdsaSecp256k1DSIGN)
-> ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
skBytes ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> VerKeyDSIGN EcdsaSecp256k1DSIGN)
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
forall a b. (a -> b) -> a -> b
$
\SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
skp -> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp ->
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO ()) -> IO ())
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
CInt
res <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO CInt
secpEcPubkeyCreate Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
skp
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
1)
(String -> IO ()
forall a. HasCallStack => String -> a
error String
"deriveVerKeyDSIGN: Failed to derive VerKeyDSIGN EcdsaSecp256k1DSIGN")
{-# NOINLINE signDSIGN #-}
signDSIGN :: ContextDSIGN EcdsaSecp256k1DSIGN
-> a
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN
signDSIGN () (MH psb) (SignKeyEcdsaSecp256k1 skBytes) =
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SigDSIGN EcdsaSecp256k1DSIGN
SigEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SigDSIGN EcdsaSecp256k1DSIGN)
-> ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> SigDSIGN EcdsaSecp256k1DSIGN
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> SigDSIGN EcdsaSecp256k1DSIGN)
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> SigDSIGN EcdsaSecp256k1DSIGN
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
psp -> do
PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
skBytes ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
skp ->
(SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp ->
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO ()) -> IO ())
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
CInt
res <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> Ptr CUChar
-> Ptr CUChar
-> IO CInt
secpEcdsaSign Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
psp SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
skp Ptr CUChar
forall a. Ptr a
nullPtr Ptr CUChar
forall a. Ptr a
nullPtr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
res CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
1)
(String -> IO ()
forall a. HasCallStack => String -> a
error String
"signDSIGN: Failed to sign EcdsaSecp256k1DSIGN message")
{-# NOINLINE verifyDSIGN #-}
verifyDSIGN :: ContextDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
-> a
-> SigDSIGN EcdsaSecp256k1DSIGN
-> Either String ()
verifyDSIGN () (VerKeyEcdsaSecp256k1 vkBytes) (MH psb) (SigEcdsaSecp256k1 sigBytes) =
IO (Either String ()) -> Either String ()
forall a. IO a -> a
unsafeDupablePerformIO (IO (Either String ()) -> Either String ())
-> ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (Either String ()))
-> IO (Either String ()))
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (Either String ()))
-> Either String ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (Either String ()))
-> IO (Either String ())
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb ((SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES -> IO (Either String ()))
-> Either String ())
-> (SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> IO (Either String ()))
-> Either String ()
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
psp -> do
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (Either String ()))
-> IO (Either String ())
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigBytes ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (Either String ()))
-> IO (Either String ()))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (Either String ()))
-> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp ->
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (Either String ()))
-> IO (Either String ())
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkBytes ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (Either String ()))
-> IO (Either String ()))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (Either String ()))
-> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp ->
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO (Either String ()))
-> IO (Either String ())
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO (Either String ()))
-> IO (Either String ()))
-> (Ptr SECP256k1Context -> IO (Either String ()))
-> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
let res :: CInt
res = Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> CInt
secpEcdsaVerify Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp SizedPtr SECP256K1_ECDSA_MESSAGE_BYTES
psp SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp
Either String () -> IO (Either String ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String () -> IO (Either String ()))
-> Either String () -> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ case CInt
res of
CInt
0 -> String -> Either String ()
forall a b. a -> Either a b
Left String
"verifyDSIGN: Incorrect or unparseable SigDSIGN EcdsaSecp256k1DSIGN"
CInt
_ -> () -> Either String ()
forall a b. b -> Either a b
Right ()
genKeyDSIGN :: Seed -> SignKeyDSIGN EcdsaSecp256k1DSIGN
genKeyDSIGN Seed
seed = Seed
-> (forall (m :: * -> *).
MonadRandom m =>
m (SignKeyDSIGN EcdsaSecp256k1DSIGN))
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
forall a. Seed -> (forall (m :: * -> *). MonadRandom m => m a) -> a
runMonadRandomWithSeed Seed
seed ((forall (m :: * -> *).
MonadRandom m =>
m (SignKeyDSIGN EcdsaSecp256k1DSIGN))
-> SignKeyDSIGN EcdsaSecp256k1DSIGN)
-> (forall (m :: * -> *).
MonadRandom m =>
m (SignKeyDSIGN EcdsaSecp256k1DSIGN))
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
forall a b. (a -> b) -> a -> b
$ do
ByteString
bs <- Int -> m ByteString
forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
32
case ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs of
Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
Nothing -> String -> m (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall a. HasCallStack => String -> a
error String
"genKeyDSIGN: Failed to generate SignKeyDSIGN EcdsaSecp256k1DSIGN unexpectedly"
Just PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb -> SignKeyDSIGN EcdsaSecp256k1DSIGN
-> m (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SignKeyDSIGN EcdsaSecp256k1DSIGN
-> m (SignKeyDSIGN EcdsaSecp256k1DSIGN))
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
-> m (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall a b. (a -> b) -> a -> b
$ PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
SignKeyEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb
{-# NOINLINE rawSerialiseSigDSIGN #-}
rawSerialiseSigDSIGN :: SigDSIGN EcdsaSecp256k1DSIGN -> ByteString
rawSerialiseSigDSIGN (SigEcdsaSecp256k1 psb) =
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString @SECP256K1_ECDSA_SIGNATURE_BYTES (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> ByteString)
-> (IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> ByteString)
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> ByteString
forall a b. (a -> b) -> a -> b
$ do
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp ->
(SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
dstp ->
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO ()) -> IO ())
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx ->
IO CInt -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO CInt
secpEcdsaSignatureSerializeCompact Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
dstp SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp
{-# NOINLINE rawSerialiseVerKeyDSIGN #-}
rawSerialiseVerKeyDSIGN :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> ByteString
rawSerialiseVerKeyDSIGN (VerKeyEcdsaSecp256k1 psb) =
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES -> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES -> ByteString)
-> ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
-> ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> ByteString)
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> ByteString
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp ->
KnownNat SECP256K1_ECDSA_PUBKEY_BYTES =>
(Ptr Word8 -> CSize -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
forall (n :: Nat).
KnownNat n =>
(Ptr Word8 -> CSize -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateLen @SECP256K1_ECDSA_PUBKEY_BYTES ((Ptr Word8 -> CSize -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES))
-> (Ptr Word8 -> CSize -> IO ())
-> IO (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr CSize
len -> do
let dstp :: Ptr CUChar
dstp = Ptr Word8 -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr
(Ptr CSize -> IO ()) -> IO ()
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CSize -> IO ()) -> IO ()) -> (Ptr CSize -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CSize
lenPtr :: Ptr CSize) -> do
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CSize
lenPtr CSize
len
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO ()) -> IO ())
-> (Ptr SECP256k1Context -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx -> do
IO CInt -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SECP256k1Context
-> Ptr CUChar
-> Ptr CSize
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> CUInt
-> IO CInt
secpEcPubkeySerialize Ptr SECP256k1Context
ctx Ptr CUChar
dstp Ptr CSize
lenPtr SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp CUInt
secpEcCompressed
CSize
writtenLen <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
lenPtr
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CSize
writtenLen CSize -> CSize -> Bool
forall a. Eq a => a -> a -> Bool
== CSize
len)
(String -> IO ()
forall a. HasCallStack => String -> a
error String
"rawSerializeVerKeyDSIGN: Did not write correct length for VerKeyDSIGN EcdsaSecp256k1DSIGN")
rawSerialiseSignKeyDSIGN :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> ByteString
rawSerialiseSignKeyDSIGN (SignKeyEcdsaSecp256k1 psb) = PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES -> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
psb
{-# NOINLINE rawDeserialiseSigDSIGN #-}
rawDeserialiseSigDSIGN :: ByteString -> Maybe (SigDSIGN EcdsaSecp256k1DSIGN)
rawDeserialiseSigDSIGN ByteString
bs =
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SigDSIGN EcdsaSecp256k1DSIGN
SigEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SigDSIGN EcdsaSecp256k1DSIGN)
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> Maybe (SigDSIGN EcdsaSecp256k1DSIGN)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
go)
where
go ::
PinnedSizedBytes SECP256K1_ECDSA_SIGNATURE_BYTES ->
Maybe (PinnedSizedBytes SECP256K1_ECDSA_SIGNATURE_BYTES_INTERNAL)
go :: PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
go PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb = IO (Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a. IO a -> a
unsafeDupablePerformIO (IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp -> do
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigPsb, CInt
res) <- (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO CInt)
-> IO
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL, CInt)
forall (n :: Nat) r.
KnownNat n =>
(SizedPtr n -> IO r) -> IO (PinnedSizedBytes n, r)
psbCreateSizedResult ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO CInt)
-> IO
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL, CInt))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO CInt)
-> IO
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL, CInt)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp ->
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO CInt) -> IO CInt)
-> (Ptr SECP256k1Context -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx ->
Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> IO CInt
secpEcdsaSignatureParseCompact Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp
Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
forall a b. (a -> b) -> a -> b
$ case CInt
res of
CInt
1 -> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigPsb
CInt
_ -> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a. Maybe a
Nothing
{-# NOINLINE rawDeserialiseVerKeyDSIGN #-}
rawDeserialiseVerKeyDSIGN :: ByteString -> Maybe (VerKeyDSIGN EcdsaSecp256k1DSIGN)
rawDeserialiseVerKeyDSIGN ByteString
bs =
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
VerKeyEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN EcdsaSecp256k1DSIGN)
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> Maybe (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ByteString -> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES)
-> (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
go)
where
go ::
PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES ->
Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
go :: PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
go PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
psb = IO (Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a. IO a -> a
unsafeDupablePerformIO (IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> ((Ptr Word8
-> CSize
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> (Ptr Word8
-> CSize
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
-> (Ptr Word8
-> CSize
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
forall (n :: Nat) r.
KnownNat n =>
PinnedSizedBytes n -> (Ptr Word8 -> CSize -> IO r) -> IO r
psbUseAsCPtrLen PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
psb ((Ptr Word8
-> CSize
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
-> (Ptr Word8
-> CSize
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p CSize
srcLen -> do
let srcp :: Ptr CUChar
srcp = Ptr Word8 -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
p
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkPsb, CInt
res) <- (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO CInt)
-> IO
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL, CInt)
forall (n :: Nat) r.
KnownNat n =>
(SizedPtr n -> IO r) -> IO (PinnedSizedBytes n, r)
psbCreateSizedResult ((SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO CInt)
-> IO
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL, CInt))
-> (SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL -> IO CInt)
-> IO
(PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL, CInt)
forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp ->
ForeignPtr SECP256k1Context
-> (Ptr SECP256k1Context -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr SECP256k1Context
secpCtxPtr ((Ptr SECP256k1Context -> IO CInt) -> IO CInt)
-> (Ptr SECP256k1Context -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr SECP256k1Context
ctx ->
Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> Ptr CUChar
-> CSize
-> IO CInt
secpEcPubkeyParse Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp Ptr CUChar
srcp CSize
srcLen
Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)))
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
-> IO
(Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL))
forall a b. (a -> b) -> a -> b
$ case CInt
res of
CInt
1 -> PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall (f :: * -> *) a. Applicative f => a -> f a
pure PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkPsb
CInt
_ -> Maybe (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL)
forall a. Maybe a
Nothing
rawDeserialiseSignKeyDSIGN :: ByteString -> Maybe (SignKeyDSIGN EcdsaSecp256k1DSIGN)
rawDeserialiseSignKeyDSIGN ByteString
bs =
PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
SignKeyEcdsaSecp256k1 (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES
-> SignKeyDSIGN EcdsaSecp256k1DSIGN)
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
-> Maybe (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString
-> Maybe (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs
instance ToCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) where
toCBOR :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding
toCBOR = VerKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> Encoding
encodeVerKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (VerKeyDSIGN EcdsaSecp256k1DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr
instance FromCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) where
fromCBOR :: Decoder s (VerKeyDSIGN EcdsaSecp256k1DSIGN)
fromCBOR = Decoder s (VerKeyDSIGN EcdsaSecp256k1DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
decodeVerKeyDSIGN
instance ToCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) where
toCBOR :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding
toCBOR = SignKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> Encoding
encodeSignKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (SignKeyDSIGN EcdsaSecp256k1DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDESIGNSizeExpr
instance FromCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) where
fromCBOR :: Decoder s (SignKeyDSIGN EcdsaSecp256k1DSIGN)
fromCBOR = Decoder s (SignKeyDSIGN EcdsaSecp256k1DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SignKeyDSIGN v)
decodeSignKeyDSIGN
instance ToCBOR (SigDSIGN EcdsaSecp256k1DSIGN) where
toCBOR :: SigDSIGN EcdsaSecp256k1DSIGN -> Encoding
toCBOR = SigDSIGN EcdsaSecp256k1DSIGN -> Encoding
forall v. DSIGNAlgorithm v => SigDSIGN v -> Encoding
encodeSigDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (SigDSIGN EcdsaSecp256k1DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr
instance FromCBOR (SigDSIGN EcdsaSecp256k1DSIGN) where
fromCBOR :: Decoder s (SigDSIGN EcdsaSecp256k1DSIGN)
fromCBOR = Decoder s (SigDSIGN EcdsaSecp256k1DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN