{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-full-laziness #-}
module Cardano.Crypto.DSIGN.Ed25519
( Ed25519DSIGN
, SigDSIGN (..)
, SignKeyDSIGN (..)
, VerKeyDSIGN (..)
)
where
import Control.DeepSeq (NFData)
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks)
import System.IO.Unsafe (unsafeDupablePerformIO)
import GHC.IO.Exception (ioException)
import Control.Monad (unless)
import Foreign.C.Error (errnoToIOError, getErrno)
import Foreign.Ptr (castPtr, nullPtr)
import qualified Data.ByteString as BS
import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Foreign
import Cardano.Crypto.PinnedSizedBytes
import Cardano.Crypto.Libsodium.C
import Cardano.Crypto.DSIGN.Class
import Cardano.Crypto.Seed
import Cardano.Crypto.Util (SignableRepresentation(..))
import Data.Proxy
data Ed25519DSIGN
instance NoThunks (VerKeyDSIGN Ed25519DSIGN)
instance NoThunks (SignKeyDSIGN Ed25519DSIGN)
instance NoThunks (SigDSIGN Ed25519DSIGN)
cOrError :: String -> String -> IO Int -> IO ()
cOrError :: String -> String -> IO Int -> IO ()
cOrError String
contextDesc String
cFunName IO Int
action = do
Int
res <- IO Int
action
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int
res Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Errno
errno <- IO Errno
getErrno
IOException -> IO ()
forall a. IOException -> IO a
ioException (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Errno -> Maybe Handle -> Maybe String -> IOException
errnoToIOError (String
contextDesc String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
cFunName) Errno
errno Maybe Handle
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
instance DSIGNAlgorithm Ed25519DSIGN where
type SeedSizeDSIGN Ed25519DSIGN = CRYPTO_SIGN_ED25519_SEEDBYTES
type SizeVerKeyDSIGN Ed25519DSIGN = CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
type SizeSignKeyDSIGN Ed25519DSIGN = CRYPTO_SIGN_ED25519_SEEDBYTES
type SizeSigDSIGN Ed25519DSIGN = CRYPTO_SIGN_ED25519_BYTES
newtype VerKeyDSIGN Ed25519DSIGN = VerKeyEd25519DSIGN (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
deriving (Int -> VerKeyDSIGN Ed25519DSIGN -> String -> String
[VerKeyDSIGN Ed25519DSIGN] -> String -> String
VerKeyDSIGN Ed25519DSIGN -> String
(Int -> VerKeyDSIGN Ed25519DSIGN -> String -> String)
-> (VerKeyDSIGN Ed25519DSIGN -> String)
-> ([VerKeyDSIGN Ed25519DSIGN] -> String -> String)
-> Show (VerKeyDSIGN Ed25519DSIGN)
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VerKeyDSIGN Ed25519DSIGN] -> String -> String
$cshowList :: [VerKeyDSIGN Ed25519DSIGN] -> String -> String
show :: VerKeyDSIGN Ed25519DSIGN -> String
$cshow :: VerKeyDSIGN Ed25519DSIGN -> String
showsPrec :: Int -> VerKeyDSIGN Ed25519DSIGN -> String -> String
$cshowsPrec :: Int -> VerKeyDSIGN Ed25519DSIGN -> String -> String
Show, VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
(VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool)
-> (VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool)
-> Eq (VerKeyDSIGN Ed25519DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
$c/= :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
== :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
$c== :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
Eq, (forall x.
VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x)
-> (forall x.
Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN)
-> Generic (VerKeyDSIGN Ed25519DSIGN)
forall x.
Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN
forall x.
VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN
$cfrom :: forall x.
VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x
Generic)
deriving newtype VerKeyDSIGN Ed25519DSIGN -> ()
(VerKeyDSIGN Ed25519DSIGN -> ())
-> NFData (VerKeyDSIGN Ed25519DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: VerKeyDSIGN Ed25519DSIGN -> ()
$crnf :: VerKeyDSIGN Ed25519DSIGN -> ()
NFData
newtype SignKeyDSIGN Ed25519DSIGN = SignKeyEd25519DSIGN (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
deriving (Int -> SignKeyDSIGN Ed25519DSIGN -> String -> String
[SignKeyDSIGN Ed25519DSIGN] -> String -> String
SignKeyDSIGN Ed25519DSIGN -> String
(Int -> SignKeyDSIGN Ed25519DSIGN -> String -> String)
-> (SignKeyDSIGN Ed25519DSIGN -> String)
-> ([SignKeyDSIGN Ed25519DSIGN] -> String -> String)
-> Show (SignKeyDSIGN Ed25519DSIGN)
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SignKeyDSIGN Ed25519DSIGN] -> String -> String
$cshowList :: [SignKeyDSIGN Ed25519DSIGN] -> String -> String
show :: SignKeyDSIGN Ed25519DSIGN -> String
$cshow :: SignKeyDSIGN Ed25519DSIGN -> String
showsPrec :: Int -> SignKeyDSIGN Ed25519DSIGN -> String -> String
$cshowsPrec :: Int -> SignKeyDSIGN Ed25519DSIGN -> String -> String
Show, SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
(SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool)
-> (SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool)
-> Eq (SignKeyDSIGN Ed25519DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
$c/= :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
== :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
$c== :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
Eq, (forall x.
SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x)
-> (forall x.
Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN)
-> Generic (SignKeyDSIGN Ed25519DSIGN)
forall x.
Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN
forall x.
SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN
$cfrom :: forall x.
SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x
Generic)
deriving newtype SignKeyDSIGN Ed25519DSIGN -> ()
(SignKeyDSIGN Ed25519DSIGN -> ())
-> NFData (SignKeyDSIGN Ed25519DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: SignKeyDSIGN Ed25519DSIGN -> ()
$crnf :: SignKeyDSIGN Ed25519DSIGN -> ()
NFData
newtype SigDSIGN Ed25519DSIGN = SigEd25519DSIGN (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
deriving (Int -> SigDSIGN Ed25519DSIGN -> String -> String
[SigDSIGN Ed25519DSIGN] -> String -> String
SigDSIGN Ed25519DSIGN -> String
(Int -> SigDSIGN Ed25519DSIGN -> String -> String)
-> (SigDSIGN Ed25519DSIGN -> String)
-> ([SigDSIGN Ed25519DSIGN] -> String -> String)
-> Show (SigDSIGN Ed25519DSIGN)
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SigDSIGN Ed25519DSIGN] -> String -> String
$cshowList :: [SigDSIGN Ed25519DSIGN] -> String -> String
show :: SigDSIGN Ed25519DSIGN -> String
$cshow :: SigDSIGN Ed25519DSIGN -> String
showsPrec :: Int -> SigDSIGN Ed25519DSIGN -> String -> String
$cshowsPrec :: Int -> SigDSIGN Ed25519DSIGN -> String -> String
Show, SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
(SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool)
-> (SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool)
-> Eq (SigDSIGN Ed25519DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
$c/= :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
== :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
$c== :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
Eq, (forall x. SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x)
-> (forall x.
Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN)
-> Generic (SigDSIGN Ed25519DSIGN)
forall x. Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN
forall x. SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN
$cfrom :: forall x. SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x
Generic)
deriving newtype SigDSIGN Ed25519DSIGN -> ()
(SigDSIGN Ed25519DSIGN -> ()) -> NFData (SigDSIGN Ed25519DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: SigDSIGN Ed25519DSIGN -> ()
$crnf :: SigDSIGN Ed25519DSIGN -> ()
NFData
algorithmNameDSIGN :: proxy Ed25519DSIGN -> String
algorithmNameDSIGN proxy Ed25519DSIGN
_ = String
"ed25519"
deriveVerKeyDSIGN :: SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
deriveVerKeyDSIGN (SignKeyEd25519DSIGN sk) =
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
-> VerKeyDSIGN Ed25519DSIGN
VerKeyEd25519DSIGN (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
-> VerKeyDSIGN Ed25519DSIGN)
-> PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
-> VerKeyDSIGN Ed25519DSIGN
forall a b. (a -> b) -> a -> b
$
IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall a b. (a -> b) -> a -> b
$
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
(SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr ->
String -> String -> IO Int -> IO ()
cOrError String
"deriveVerKeyDSIGN @Ed25519DSIGN" String
"c_crypto_sign_ed25519_sk_to_pk"
(IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO Int
c_crypto_sign_ed25519_sk_to_pk SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr
type Signable Ed25519DSIGN = SignableRepresentation
signDSIGN :: ContextDSIGN Ed25519DSIGN
-> a -> SignKeyDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN
signDSIGN () a
a (SignKeyEd25519DSIGN sk) =
let bs :: ByteString
bs = a -> ByteString
forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
a
in PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
-> SigDSIGN Ed25519DSIGN
SigEd25519DSIGN (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
-> SigDSIGN Ed25519DSIGN)
-> PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
-> SigDSIGN Ed25519DSIGN
forall a b. (a -> b) -> a -> b
$ IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
forall a b. (a -> b) -> a -> b
$
ByteString
-> (CStringLen
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
bs ((CStringLen
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> (CStringLen
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
(SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat) b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr -> do
String -> String -> IO Int -> IO ()
cOrError String
"signDSIGN @Ed25519DSIGN" String
"c_crypto_sign_ed25519_sk_to_pk"
(IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO Int
c_crypto_sign_ed25519_sk_to_pk SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr
(SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sigPtr -> do
String -> String -> IO Int -> IO ()
cOrError String
"signDSIGN @Ed25519DSIGN" String
"c_crypto_sign_ed25519_detached"
(IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> Ptr CULLong
-> Ptr CUChar
-> CULLong
-> SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO Int
c_crypto_sign_ed25519_detached SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sigPtr Ptr CULLong
forall a. Ptr a
nullPtr (Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
ptr) (Int -> CULLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr
verifyDSIGN :: ContextDSIGN Ed25519DSIGN
-> VerKeyDSIGN Ed25519DSIGN
-> a
-> SigDSIGN Ed25519DSIGN
-> Either String ()
verifyDSIGN () (VerKeyEd25519DSIGN vk) a
a (SigEd25519DSIGN sig) =
let bs :: ByteString
bs = a -> ByteString
forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
a
in IO (Either String ()) -> Either String ()
forall a. IO a -> a
unsafeDupablePerformIO (IO (Either String ()) -> Either String ())
-> IO (Either String ()) -> Either String ()
forall a b. (a -> b) -> a -> b
$
ByteString
-> (CStringLen -> IO (Either String ())) -> IO (Either String ())
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
bs ((CStringLen -> IO (Either String ())) -> IO (Either String ()))
-> (CStringLen -> IO (Either String ())) -> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (Either String ()))
-> IO (Either String ())
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
vk ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (Either String ()))
-> IO (Either String ()))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (Either String ()))
-> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
vkPtr ->
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (Either String ()))
-> IO (Either String ())
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
sig ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (Either String ()))
-> IO (Either String ()))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (Either String ()))
-> IO (Either String ())
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sigPtr -> do
Int
res <- SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> Ptr CUChar
-> CULLong
-> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO Int
c_crypto_sign_ed25519_verify_detached SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sigPtr (Ptr CChar -> Ptr CUChar
forall a b. Ptr a -> Ptr b
castPtr Ptr CChar
ptr) (Int -> CULLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
vkPtr
if Int
res Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then Either String () -> IO (Either String ())
forall (m :: * -> *) a. Monad m => a -> m a
return (() -> Either String ()
forall a b. b -> Either a b
Right ())
else do
Either String () -> IO (Either String ())
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Either String ()
forall a b. a -> Either a b
Left String
"Verification failed")
genKeyDSIGN :: Seed -> SignKeyDSIGN Ed25519DSIGN
genKeyDSIGN Seed
seed = PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGN Ed25519DSIGN
SignKeyEd25519DSIGN (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGN Ed25519DSIGN)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGN Ed25519DSIGN
forall a b. (a -> b) -> a -> b
$
let (ByteString
sb, Seed
_) = Word -> Seed -> (ByteString, Seed)
getBytesFromSeedT (Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
seedSizeDSIGN (Proxy Ed25519DSIGN
forall k (t :: k). Proxy t
Proxy @Ed25519DSIGN)) Seed
seed
in IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
forall a b. (a -> b) -> a -> b
$ do
(SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
sb ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
seedPtr, Int
_) ->
(SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ()) -> IO ()
forall (n :: Nat) b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ()) -> IO ())
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr -> do
String -> String -> IO Int -> IO ()
cOrError String
"genKeyDSIGN @Ed25519DSIGN" String
"c_crypto_sign_ed25519_seed_keypair"
(IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO Int
c_crypto_sign_ed25519_seed_keypair SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr (Ptr Void -> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall (n :: Nat). Ptr Void -> SizedPtr n
SizedPtr (Ptr Void -> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> (Ptr CChar -> Ptr Void)
-> Ptr CChar
-> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr CChar -> Ptr Void
forall a b. Ptr a -> Ptr b
castPtr (Ptr CChar -> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Ptr CChar -> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall a b. (a -> b) -> a -> b
$ Ptr CChar
seedPtr)
rawSerialiseVerKeyDSIGN :: VerKeyDSIGN Ed25519DSIGN -> ByteString
rawSerialiseVerKeyDSIGN (VerKeyEd25519DSIGN vk) = PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
vk
rawSerialiseSignKeyDSIGN :: SignKeyDSIGN Ed25519DSIGN -> ByteString
rawSerialiseSignKeyDSIGN (SignKeyEd25519DSIGN sk) =
PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN) -> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString @(SeedSizeDSIGN Ed25519DSIGN) (PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN) -> ByteString)
-> PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN) -> ByteString
forall a b. (a -> b) -> a -> b
$ IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall a b. (a -> b) -> a -> b
$ do
(SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat).
KnownNat n =>
(SizedPtr n -> IO ()) -> IO (PinnedSizedBytes n)
psbCreateSized ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> IO ())
-> IO (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seedPtr ->
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ()) -> IO ()
forall (n :: Nat) r.
PinnedSizedBytes n -> (SizedPtr n -> IO r) -> IO r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ()) -> IO ())
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
String -> String -> IO Int -> IO ()
cOrError String
"deriveVerKeyDSIGN @Ed25519DSIGN" String
"c_crypto_sign_ed25519_sk_to_seed"
(IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO Int
c_crypto_sign_ed25519_sk_to_seed SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seedPtr SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr
rawSerialiseSigDSIGN :: SigDSIGN Ed25519DSIGN -> ByteString
rawSerialiseSigDSIGN (SigEd25519DSIGN sig) = PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> ByteString
forall (n :: Nat). PinnedSizedBytes n -> ByteString
psbToByteString PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
sig
rawDeserialiseVerKeyDSIGN :: ByteString -> Maybe (VerKeyDSIGN Ed25519DSIGN)
rawDeserialiseVerKeyDSIGN = (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> VerKeyDSIGN Ed25519DSIGN)
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> VerKeyDSIGN Ed25519DSIGN
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
-> VerKeyDSIGN Ed25519DSIGN
VerKeyEd25519DSIGN (Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Maybe (VerKeyDSIGN Ed25519DSIGN))
-> (ByteString
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> ByteString
-> Maybe (VerKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck
rawDeserialiseSignKeyDSIGN :: ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
rawDeserialiseSignKeyDSIGN = SignKeyDSIGN Ed25519DSIGN -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall a. a -> Maybe a
Just (SignKeyDSIGN Ed25519DSIGN -> Maybe (SignKeyDSIGN Ed25519DSIGN))
-> (ByteString -> SignKeyDSIGN Ed25519DSIGN)
-> ByteString
-> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seed -> SignKeyDSIGN Ed25519DSIGN
forall v. DSIGNAlgorithm v => Seed -> SignKeyDSIGN v
genKeyDSIGN (Seed -> SignKeyDSIGN Ed25519DSIGN)
-> (ByteString -> Seed) -> ByteString -> SignKeyDSIGN Ed25519DSIGN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Seed
mkSeedFromBytes
rawDeserialiseSigDSIGN :: ByteString -> Maybe (SigDSIGN Ed25519DSIGN)
rawDeserialiseSigDSIGN = (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SigDSIGN Ed25519DSIGN)
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> Maybe (SigDSIGN Ed25519DSIGN)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SigDSIGN Ed25519DSIGN
PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
-> SigDSIGN Ed25519DSIGN
SigEd25519DSIGN (Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> Maybe (SigDSIGN Ed25519DSIGN))
-> (ByteString
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> ByteString
-> Maybe (SigDSIGN Ed25519DSIGN)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat).
KnownNat n =>
ByteString -> Maybe (PinnedSizedBytes n)
psbFromByteStringCheck
instance ToCBOR (VerKeyDSIGN Ed25519DSIGN) where
toCBOR :: VerKeyDSIGN Ed25519DSIGN -> Encoding
toCBOR = VerKeyDSIGN Ed25519DSIGN -> Encoding
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> Encoding
encodeVerKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerKeyDSIGN Ed25519DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (VerKeyDSIGN Ed25519DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr
instance FromCBOR (VerKeyDSIGN Ed25519DSIGN) where
fromCBOR :: Decoder s (VerKeyDSIGN Ed25519DSIGN)
fromCBOR = Decoder s (VerKeyDSIGN Ed25519DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
decodeVerKeyDSIGN
instance ToCBOR (SignKeyDSIGN Ed25519DSIGN) where
toCBOR :: SignKeyDSIGN Ed25519DSIGN -> Encoding
toCBOR = SignKeyDSIGN Ed25519DSIGN -> Encoding
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> Encoding
encodeSignKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SignKeyDSIGN Ed25519DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (SignKeyDSIGN Ed25519DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDESIGNSizeExpr
instance FromCBOR (SignKeyDSIGN Ed25519DSIGN) where
fromCBOR :: Decoder s (SignKeyDSIGN Ed25519DSIGN)
fromCBOR = Decoder s (SignKeyDSIGN Ed25519DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SignKeyDSIGN v)
decodeSignKeyDSIGN
instance ToCBOR (SigDSIGN Ed25519DSIGN) where
toCBOR :: SigDSIGN Ed25519DSIGN -> Encoding
toCBOR = SigDSIGN Ed25519DSIGN -> Encoding
forall v. DSIGNAlgorithm v => SigDSIGN v -> Encoding
encodeSigDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigDSIGN Ed25519DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (SigDSIGN Ed25519DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr
instance FromCBOR (SigDSIGN Ed25519DSIGN) where
fromCBOR :: Decoder s (SigDSIGN Ed25519DSIGN)
fromCBOR = Decoder s (SigDSIGN Ed25519DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN