{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeApplications #-}
-- Needed to ensure that our hash is the right size
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
-- According to the documentation for unsafePerformIO:
--
-- > Make sure that the either you switch off let-floating
-- > (-fno-full-laziness), or that the call to unsafePerformIO cannot float
-- > outside a lambda.
--
-- If we do not switch off let-floating, our calls to unsafeDupablePerformIO for
-- FFI functions become nondeterministic in their behaviour when run with
-- parallelism enabled (such as -with-rtsopts=-N), possibly yielding wrong
-- answers on a range of tasks, including serialization.
{-# 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,
  )

-- | As ECDSA signatures on the SECP256k1 curve sign 32-byte hashes, rather than
-- whole messages, we provide a helper (opaque) newtype to ensure that the size
-- of the input for signing and verification is strictly bounded.
--
-- = Important note
--
-- If you are verifying a message using the algorithm provided here, you should
-- hash the message yourself before verifying. Specifically, the sender should
-- give you the message itself to verify, rather than the hash of the message
-- used to compute the signature.
newtype MessageHash = MH (PinnedSizedBytes SECP256K1_ECDSA_MESSAGE_BYTES)
  deriving MessageHash -> MessageHash -> Bool
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
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

-- | Take a blob of bytes (which is presumed to be a 32-byte hash), verify its
-- length, and package it into a 'MessageHash' if that length is exactly 32.
toMessageHash :: ByteString -> Maybe MessageHash
toMessageHash :: ByteString -> Maybe MessageHash
toMessageHash ByteString
bs = PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES -> MessageHash
MH forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs

-- | Turn a 'MessageHash' into its bytes without a length marker.
fromMessageHash :: MessageHash -> ByteString
fromMessageHash :: MessageHash -> ByteString
fromMessageHash (MH PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb) = forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb

-- | A helper to use with the 'HashAlgorithm' API, as this can ensure sizing.
hashAndPack :: forall (h :: Type) .
  (HashAlgorithm h, SizeHash h ~ SECP256K1_ECDSA_MESSAGE_BYTES) =>
  Proxy h -> ByteString -> MessageHash
hashAndPack :: forall h.
(HashAlgorithm h, SizeHash h ~ SECP256K1_ECDSA_PRIVKEY_BYTES) =>
Proxy h -> ByteString -> MessageHash
hashAndPack Proxy h
p ByteString
bs = case forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall h (proxy :: * -> *).
HashAlgorithm h =>
proxy h -> ByteString -> ByteString
digest Proxy h
p forall a b. (a -> b) -> a -> b
$ ByteString
bs of
  Maybe (PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES)
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"hashAndPack: unexpected mismatch of guaranteed hash length\n" forall a. Semigroup a => a -> a -> a
<>
                     String
"Please report this, it's a bug!"
  Just PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb -> PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES -> MessageHash
MH PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_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
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 -> ()
forall a. (a -> ()) -> NFData a
rnf :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> ()
$crnf :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> ()
NFData)
      deriving stock (Int -> VerKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
[VerKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
VerKeyDSIGN EcdsaSecp256k1DSIGN -> String
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.
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
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
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 -> ()
forall a. (a -> ()) -> NFData a
rnf :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> ()
$crnf :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> ()
NFData)
      deriving stock (Int -> SignKeyDSIGN EcdsaSecp256k1DSIGN -> ShowS
[SignKeyDSIGN EcdsaSecp256k1DSIGN] -> ShowS
SignKeyDSIGN EcdsaSecp256k1DSIGN -> String
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.
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
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
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 -> ()
forall a. (a -> ()) -> NFData a
rnf :: SigDSIGN EcdsaSecp256k1DSIGN -> ()
$crnf :: SigDSIGN EcdsaSecp256k1DSIGN -> ()
NFData)
      deriving stock (Int -> SigDSIGN EcdsaSecp256k1DSIGN -> ShowS
[SigDSIGN EcdsaSecp256k1DSIGN] -> ShowS
SigDSIGN EcdsaSecp256k1DSIGN -> String
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.
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
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 :: forall (proxy :: * -> *). proxy EcdsaSecp256k1DSIGN -> String
algorithmNameDSIGN proxy EcdsaSecp256k1DSIGN
_ = String
"ecdsa-secp256k1"
    {-# NOINLINE deriveVerKeyDSIGN #-}
    deriveVerKeyDSIGN :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> VerKeyDSIGN EcdsaSecp256k1DSIGN
deriveVerKeyDSIGN (SignKeyEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
skBytes) =
      PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
VerKeyEcdsaSecp256k1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
skBytes forall a b. (a -> b) -> a -> b
$
        \SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
skp -> forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp ->
          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_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
-> IO CInt
secpEcPubkeyCreate Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp SizedPtr SECP256K1_ECDSA_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 derive VerKeyDSIGN EcdsaSecp256k1DSIGN")
    {-# NOINLINE signDSIGN #-}
    signDSIGN :: forall a.
(Signable EcdsaSecp256k1DSIGN a, HasCallStack) =>
ContextDSIGN EcdsaSecp256k1DSIGN
-> a
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
-> SigDSIGN EcdsaSecp256k1DSIGN
signDSIGN () (MH PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb) (SignKeyEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
skBytes) =
      PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SigDSIGN EcdsaSecp256k1DSIGN
SigEcdsaSecp256k1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
psp -> do
        forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
skBytes forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
skp ->
          forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp ->
            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
              -- The two nullPtr arguments correspond to nonces and extra nonce
              -- data. We use neither, so we pass nullPtrs to indicate this to the
              -- C API.
              CInt
res <- Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
-> SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
-> Ptr CUChar
-> Ptr CUChar
-> IO CInt
secpEcdsaSign Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
psp SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
skp forall a. Ptr a
nullPtr 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 EcdsaSecp256k1DSIGN message")
    {-# NOINLINE verifyDSIGN #-}
    verifyDSIGN :: forall a.
(Signable EcdsaSecp256k1DSIGN a, HasCallStack) =>
ContextDSIGN EcdsaSecp256k1DSIGN
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
-> a
-> SigDSIGN EcdsaSecp256k1DSIGN
-> Either String ()
verifyDSIGN () (VerKeyEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkBytes) (MH PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb) (SigEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigBytes) =
      forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
psp -> do
        forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigBytes forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp ->
          forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkBytes forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp ->
            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
              let res :: CInt
res = Ptr SECP256k1Context
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
-> SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> CInt
secpEcdsaVerify Ptr SECP256k1Context
ctx SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp SizedPtr SECP256K1_ECDSA_PRIVKEY_BYTES
psp SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp
              forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ case CInt
res of
                CInt
0 -> forall a b. a -> Either a b
Left String
"verifyDSIGN: Incorrect or unparseable SigDSIGN EcdsaSecp256k1DSIGN"
                CInt
_ -> forall a b. b -> Either a b
Right ()
    genKeyDSIGN :: Seed -> SignKeyDSIGN EcdsaSecp256k1DSIGN
genKeyDSIGN Seed
seed = forall a. Seed -> (forall (m :: * -> *). MonadRandom m => m a) -> a
runMonadRandomWithSeed Seed
seed forall a b. (a -> b) -> a -> b
$ do
      ByteString
bs <- forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
32
      case forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs of
        Maybe (PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES)
Nothing -> forall a. HasCallStack => String -> a
error String
"genKeyDSIGN: Failed to generate SignKeyDSIGN EcdsaSecp256k1DSIGN unexpectedly"
        Just PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
SignKeyEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb
    {-# NOINLINE rawSerialiseSigDSIGN #-}
    rawSerialiseSigDSIGN :: SigDSIGN EcdsaSecp256k1DSIGN -> ByteString
rawSerialiseSigDSIGN (SigEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb) =
      forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString @SECP256K1_ECDSA_SIGNATURE_BYTES forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$ do
        forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp ->
          forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
dstp ->
            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. Functor f => f a -> f ()
void 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 PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb) =
      forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp ->
        forall (n :: Nat).
KnownNat n =>
(Ptr Word8 -> CSize -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateLen @SECP256K1_ECDSA_PUBKEY_BYTES forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr CSize
len -> do
          let dstp :: Ptr CUChar
dstp = forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr
          -- This is necessary because of how the C API handles checking writes:
          -- maximum permissible length is given as a pointer, which is
          -- overwritten to indicate the number of bytes we actually wrote; if
          -- we get a mismatch, then the serialization failed. While an odd
          -- choice, we have to go with it.
          forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \(Ptr CSize
lenPtr :: Ptr CSize) -> do
            forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CSize
lenPtr CSize
len
            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
ret <- 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 <- forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
lenPtr
              forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CSize
writtenLen forall a. Eq a => a -> a -> Bool
== CSize
len)
                     (forall a. HasCallStack => String -> a
error String
"rawSerializeVerKeyDSIGN: Did not write correct length for VerKeyDSIGN EcdsaSecp256k1DSIGN")
              -- This should never happen, since `secpEcPubkeySerialize` in the current
              -- version of `secp256k1` library always returns 1:
              forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (CInt
ret forall a. Eq a => a -> a -> Bool
== CInt
1)
                     (forall a. HasCallStack => String -> a
error String
"rawSerializeVerKeyDSIGN: Failed for unknown reason")
    rawSerialiseSignKeyDSIGN :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> ByteString
rawSerialiseSignKeyDSIGN (SignKeyEcdsaSecp256k1 PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb) = forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
psb
    {-# NOINLINE rawDeserialiseSigDSIGN #-}
    rawDeserialiseSigDSIGN :: ByteString -> Maybe (SigDSIGN EcdsaSecp256k1DSIGN)
rawDeserialiseSigDSIGN ByteString
bs =
      PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> SigDSIGN EcdsaSecp256k1DSIGN
SigEcdsaSecp256k1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs 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 = forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psb forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
psp -> do
          (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigPsb, CInt
res) <- forall (n :: Nat) r.
KnownNat n =>
(SizedPtr n -> IO r) -> IO (PinnedSizedBytes n, r)
psbCreateSizedResult forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigp ->
            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_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
          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 PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
sigPsb
            CInt
_ -> forall a. Maybe a
Nothing
    {-# NOINLINE rawDeserialiseVerKeyDSIGN #-}
    rawDeserialiseVerKeyDSIGN :: ByteString -> Maybe (VerKeyDSIGN EcdsaSecp256k1DSIGN)
rawDeserialiseVerKeyDSIGN ByteString
bs =
      PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
-> VerKeyDSIGN EcdsaSecp256k1DSIGN
VerKeyEcdsaSecp256k1 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck ByteString
bs 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 = forall a. IO a -> a
unsafeDupablePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) r.
KnownNat n =>
PinnedSizedBytes n -> (Ptr Word8 -> CSize -> IO r) -> IO r
psbUseAsCPtrLen PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES
psb forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p CSize
srcLen -> do
          let srcp :: Ptr CUChar
srcp = forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
p
          (PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkPsb, CInt
res) <- forall (n :: Nat) r.
KnownNat n =>
(SizedPtr n -> IO r) -> IO (PinnedSizedBytes n, r)
psbCreateSizedResult forall a b. (a -> b) -> a -> b
$ \SizedPtr SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkp ->
            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_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
          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 PinnedSizedBytes SECP256K1_ECDSA_PUBKEY_BYTES_INTERNAL
vkPsb
            CInt
_ -> forall a. Maybe a
Nothing
    rawDeserialiseSignKeyDSIGN :: ByteString -> Maybe (SignKeyDSIGN EcdsaSecp256k1DSIGN)
rawDeserialiseSignKeyDSIGN ByteString
bs =
      PinnedSizedBytes SECP256K1_ECDSA_PRIVKEY_BYTES
-> SignKeyDSIGN EcdsaSecp256k1DSIGN
SignKeyEcdsaSecp256k1 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 EcdsaSecp256k1DSIGN) where
  toCBOR :: VerKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding
toCBOR = 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
_ = forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr

instance FromCBOR (VerKeyDSIGN EcdsaSecp256k1DSIGN) where
  fromCBOR :: forall s. Decoder s (VerKeyDSIGN EcdsaSecp256k1DSIGN)
fromCBOR = forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
decodeVerKeyDSIGN

instance ToCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) where
  toCBOR :: SignKeyDSIGN EcdsaSecp256k1DSIGN -> Encoding
toCBOR = 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
_ = forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDESIGNSizeExpr

instance FromCBOR (SignKeyDSIGN EcdsaSecp256k1DSIGN) where
  fromCBOR :: forall s. Decoder s (SignKeyDSIGN EcdsaSecp256k1DSIGN)
fromCBOR = forall v s. DSIGNAlgorithm v => Decoder s (SignKeyDSIGN v)
decodeSignKeyDSIGN

instance ToCBOR (SigDSIGN EcdsaSecp256k1DSIGN) where
  toCBOR :: SigDSIGN EcdsaSecp256k1DSIGN -> Encoding
toCBOR = 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
_ = forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr

instance FromCBOR (SigDSIGN EcdsaSecp256k1DSIGN) where
  fromCBOR :: forall s. Decoder s (SigDSIGN EcdsaSecp256k1DSIGN)
fromCBOR = forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN