{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-full-laziness #-}
module Cardano.Crypto.DSIGN.Ed25519 (
Ed25519DSIGN,
SigDSIGN (..),
SignKeyDSIGN (..),
SignKeyDSIGNM (..),
VerKeyDSIGN (..),
)
where
import Control.DeepSeq (NFData (..), rwhnf)
import Control.Monad (guard, unless, (<$!>))
import Control.Monad.Class.MonadST (MonadST (..))
import Control.Monad.Class.MonadThrow (MonadThrow (..), throwIO)
import Control.Monad.ST (ST)
import Control.Monad.ST.Unsafe (unsafeIOToST)
import qualified Data.ByteString as BS
import Data.Proxy
import Foreign.C.Error (Errno, errnoToIOError, getErrno)
import Foreign.Ptr (castPtr, nullPtr)
import GHC.Generics (Generic)
import GHC.IO.Exception (ioException)
import GHC.TypeLits (ErrorMessage (..), TypeError)
import NoThunks.Class (NoThunks)
import System.IO.Unsafe (unsafeDupablePerformIO)
import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Crypto.DSIGN.Class
import Cardano.Crypto.DirectSerialise
import Cardano.Crypto.Libsodium (
MLockedSizedBytes,
mlsbCopyWith,
mlsbFinalize,
mlsbFromByteStringCheckWith,
mlsbNewWith,
mlsbToByteString,
mlsbUseAsSizedPtr,
)
import Cardano.Crypto.Libsodium.C
import Cardano.Crypto.Libsodium.MLockedSeed
import Cardano.Crypto.PinnedSizedBytes (
PinnedSizedBytes,
psbCreate,
psbCreateSized,
psbCreateSizedResult,
psbFromByteStringCheck,
psbToByteString,
psbUseAsCPtrLen,
psbUseAsSizedPtr,
)
import Cardano.Crypto.Seed
import Cardano.Crypto.Util (SignableRepresentation (..))
import Cardano.Foreign
data Ed25519DSIGN
instance NoThunks (VerKeyDSIGN Ed25519DSIGN)
instance NoThunks (SignKeyDSIGN Ed25519DSIGN)
instance NoThunks (SigDSIGN Ed25519DSIGN)
deriving via
(MLockedSizedBytes (SizeSignKeyDSIGN Ed25519DSIGN))
instance
NoThunks (SignKeyDSIGNM Ed25519DSIGN)
instance NFData (SignKeyDSIGNM Ed25519DSIGN) where
rnf :: SignKeyDSIGNM Ed25519DSIGN -> ()
rnf = SignKeyDSIGNM Ed25519DSIGN -> ()
forall a. a -> ()
rwhnf
cOrThrowError :: String -> String -> IO Int -> IO ()
cOrThrowError :: String -> String -> IO Int -> IO ()
cOrThrowError 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
cOrError :: MonadST m => (forall s. ST s Int) -> m (Maybe Errno)
cOrError :: forall (m :: * -> *).
MonadST m =>
(forall s. ST s Int) -> m (Maybe Errno)
cOrError forall s. ST s Int
action = ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a. ST (PrimState m) a -> m a
forall (m :: * -> *) a. MonadST m => ST (PrimState m) a -> m a
stToIO (ST (PrimState m) (Maybe Errno) -> m (Maybe Errno))
-> ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a b. (a -> b) -> a -> b
$ do
Int
res <- ST (PrimState m) Int
forall s. ST s Int
action
if Int
res Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then
Maybe Errno -> ST (PrimState m) (Maybe Errno)
forall a. a -> ST (PrimState m) a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Errno
forall a. Maybe a
Nothing
else
Errno -> Maybe Errno
forall a. a -> Maybe a
Just (Errno -> Maybe Errno)
-> ST (PrimState m) Errno -> ST (PrimState m) (Maybe Errno)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Errno -> ST (PrimState m) Errno
forall a s. IO a -> ST s a
unsafeIOToST IO Errno
getErrno
throwOnErrno :: MonadThrow m => String -> String -> Maybe Errno -> m ()
throwOnErrno :: forall (m :: * -> *).
MonadThrow m =>
String -> String -> Maybe Errno -> m ()
throwOnErrno String
contextDesc String
cFunName Maybe Errno
maybeErrno = do
case Maybe Errno
maybeErrno of
Just Errno
errno -> IOException -> m ()
forall e a. Exception e => e -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (IOException -> m ()) -> IOException -> m ()
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
Maybe Errno
Nothing -> () -> m ()
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
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
$cshowsPrec :: Int -> VerKeyDSIGN Ed25519DSIGN -> String -> String
showsPrec :: Int -> VerKeyDSIGN Ed25519DSIGN -> String -> String
$cshow :: VerKeyDSIGN Ed25519DSIGN -> String
show :: VerKeyDSIGN Ed25519DSIGN -> String
$cshowList :: [VerKeyDSIGN Ed25519DSIGN] -> String -> String
showList :: [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
$c== :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
== :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
$c/= :: VerKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN -> Bool
/= :: 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
$cfrom :: forall x.
VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x
from :: forall x.
VerKeyDSIGN Ed25519DSIGN -> Rep (VerKeyDSIGN Ed25519DSIGN) x
$cto :: forall x.
Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN
to :: forall x.
Rep (VerKeyDSIGN Ed25519DSIGN) x -> VerKeyDSIGN Ed25519DSIGN
Generic)
deriving newtype (VerKeyDSIGN Ed25519DSIGN -> ()
(VerKeyDSIGN Ed25519DSIGN -> ())
-> NFData (VerKeyDSIGN Ed25519DSIGN)
forall a. (a -> ()) -> NFData a
$crnf :: VerKeyDSIGN Ed25519DSIGN -> ()
rnf :: 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
$cshowsPrec :: Int -> SignKeyDSIGN Ed25519DSIGN -> String -> String
showsPrec :: Int -> SignKeyDSIGN Ed25519DSIGN -> String -> String
$cshow :: SignKeyDSIGN Ed25519DSIGN -> String
show :: SignKeyDSIGN Ed25519DSIGN -> String
$cshowList :: [SignKeyDSIGN Ed25519DSIGN] -> String -> String
showList :: [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
$c== :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
== :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
$c/= :: SignKeyDSIGN Ed25519DSIGN -> SignKeyDSIGN Ed25519DSIGN -> Bool
/= :: 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
$cfrom :: forall x.
SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x
from :: forall x.
SignKeyDSIGN Ed25519DSIGN -> Rep (SignKeyDSIGN Ed25519DSIGN) x
$cto :: forall x.
Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN
to :: forall x.
Rep (SignKeyDSIGN Ed25519DSIGN) x -> SignKeyDSIGN Ed25519DSIGN
Generic)
deriving newtype (SignKeyDSIGN Ed25519DSIGN -> ()
(SignKeyDSIGN Ed25519DSIGN -> ())
-> NFData (SignKeyDSIGN Ed25519DSIGN)
forall a. (a -> ()) -> NFData a
$crnf :: SignKeyDSIGN Ed25519DSIGN -> ()
rnf :: 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
$cshowsPrec :: Int -> SigDSIGN Ed25519DSIGN -> String -> String
showsPrec :: Int -> SigDSIGN Ed25519DSIGN -> String -> String
$cshow :: SigDSIGN Ed25519DSIGN -> String
show :: SigDSIGN Ed25519DSIGN -> String
$cshowList :: [SigDSIGN Ed25519DSIGN] -> String -> String
showList :: [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
$c== :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
== :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
$c/= :: SigDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN -> Bool
/= :: 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
$cfrom :: forall x. SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x
from :: forall x. SigDSIGN Ed25519DSIGN -> Rep (SigDSIGN Ed25519DSIGN) x
$cto :: forall x. Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN
to :: forall x. Rep (SigDSIGN Ed25519DSIGN) x -> SigDSIGN Ed25519DSIGN
Generic)
deriving newtype (SigDSIGN Ed25519DSIGN -> ()
(SigDSIGN Ed25519DSIGN -> ()) -> NFData (SigDSIGN Ed25519DSIGN)
forall a. (a -> ()) -> NFData a
$crnf :: SigDSIGN Ed25519DSIGN -> ()
rnf :: SigDSIGN Ed25519DSIGN -> ()
NFData)
algorithmNameDSIGN :: forall (proxy :: * -> *). proxy Ed25519DSIGN -> String
algorithmNameDSIGN proxy Ed25519DSIGN
_ = String
"ed25519"
deriveVerKeyDSIGN :: SignKeyDSIGN Ed25519DSIGN -> VerKeyDSIGN Ed25519DSIGN
deriveVerKeyDSIGN (SignKeyEd25519DSIGN PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
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 (SizeVerKeyDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
forall a b. (a -> b) -> a -> b
$
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
(SizedPtr (SizeVerKeyDSIGN Ed25519DSIGN) -> IO ())
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (PinnedSizedBytes n)
psbCreateSized ((SizedPtr (SizeVerKeyDSIGN Ed25519DSIGN) -> IO ())
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)))
-> (SizedPtr (SizeVerKeyDSIGN Ed25519DSIGN) -> IO ())
-> IO (PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN))
forall a b. (a -> b) -> a -> b
$ \SizedPtr (SizeVerKeyDSIGN Ed25519DSIGN)
pkPtr ->
String -> String -> IO Int -> IO ()
cOrThrowError 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
SizedPtr (SizeVerKeyDSIGN Ed25519DSIGN)
pkPtr SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr
type Signable Ed25519DSIGN = SignableRepresentation
signDSIGN :: forall a.
(Signable Ed25519DSIGN a, HasCallStack) =>
ContextDSIGN Ed25519DSIGN
-> a -> SignKeyDSIGN Ed25519DSIGN -> SigDSIGN Ed25519DSIGN
signDSIGN () a
a (SignKeyEd25519DSIGN PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
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 (SizeSigDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
forall a b. (a -> b) -> a -> b
$
ByteString
-> (CStringLen
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
bs ((CStringLen -> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> (CStringLen
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m r
psbUseAsSizedPtr PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
(SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
forall (n :: Nat) b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)))
-> IO (PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN))
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr -> do
String -> String -> IO Int -> IO ()
cOrThrowError 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) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (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 ()
cOrThrowError 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 :: forall a.
(Signable Ed25519DSIGN a, HasCallStack) =>
ContextDSIGN Ed25519DSIGN
-> VerKeyDSIGN Ed25519DSIGN
-> a
-> SigDSIGN Ed25519DSIGN
-> Either String ()
verifyDSIGN () (VerKeyEd25519DSIGN PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
vk) a
a (SigEd25519DSIGN PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
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 (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m 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 (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m 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 a. a -> IO a
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 a. a -> IO a
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 (forall t. Proxy t
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) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (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 ()
cOrThrowError 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 PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
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 PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk) =
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 (SeedSizeDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN)
forall a. IO a -> a
unsafeDupablePerformIO (IO (PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN))
-> IO (PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN))
-> PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN)
forall a b. (a -> b) -> a -> b
$ do
(SizedPtr (SeedSizeDSIGN Ed25519DSIGN) -> IO ())
-> IO (PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN))
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m ()) -> m (PinnedSizedBytes n)
psbCreateSized ((SizedPtr (SeedSizeDSIGN Ed25519DSIGN) -> IO ())
-> IO (PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN)))
-> (SizedPtr (SeedSizeDSIGN Ed25519DSIGN) -> IO ())
-> IO (PinnedSizedBytes (SeedSizeDSIGN Ed25519DSIGN))
forall a b. (a -> b) -> a -> b
$ \SizedPtr (SeedSizeDSIGN Ed25519DSIGN)
seedPtr ->
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> IO ()) -> IO ()
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
PinnedSizedBytes n -> (SizedPtr n -> m r) -> m 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 ()
cOrThrowError 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
SizedPtr (SeedSizeDSIGN Ed25519DSIGN)
seedPtr SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr
rawSerialiseSigDSIGN :: SigDSIGN Ed25519DSIGN -> ByteString
rawSerialiseSigDSIGN (SigEd25519DSIGN PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
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 a b. (a -> b) -> Maybe a -> Maybe b
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
{-# INLINE rawDeserialiseVerKeyDSIGN #-}
rawDeserialiseSignKeyDSIGN :: ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
rawDeserialiseSignKeyDSIGN ByteString
bs = do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Int -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int
BS.length ByteString
bs) Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
seedSizeDSIGN (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN))
SignKeyDSIGN Ed25519DSIGN -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (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 (ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN))
-> ByteString -> Maybe (SignKeyDSIGN Ed25519DSIGN)
forall a b. (a -> b) -> a -> b
$ ByteString
bs
rawDeserialiseSigDSIGN :: ByteString -> Maybe (SigDSIGN Ed25519DSIGN)
rawDeserialiseSigDSIGN = (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SigDSIGN Ed25519DSIGN)
-> Maybe (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> Maybe (SigDSIGN Ed25519DSIGN)
forall a b. (a -> b) -> Maybe a -> Maybe b
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
{-# INLINE rawDeserialiseSigDSIGN #-}
instance DSIGNMAlgorithm Ed25519DSIGN where
newtype SignKeyDSIGNM Ed25519DSIGN
= SignKeyEd25519DSIGNM (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
deriving (Int -> SignKeyDSIGNM Ed25519DSIGN -> String -> String
[SignKeyDSIGNM Ed25519DSIGN] -> String -> String
SignKeyDSIGNM Ed25519DSIGN -> String
(Int -> SignKeyDSIGNM Ed25519DSIGN -> String -> String)
-> (SignKeyDSIGNM Ed25519DSIGN -> String)
-> ([SignKeyDSIGNM Ed25519DSIGN] -> String -> String)
-> Show (SignKeyDSIGNM Ed25519DSIGN)
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> SignKeyDSIGNM Ed25519DSIGN -> String -> String
showsPrec :: Int -> SignKeyDSIGNM Ed25519DSIGN -> String -> String
$cshow :: SignKeyDSIGNM Ed25519DSIGN -> String
show :: SignKeyDSIGNM Ed25519DSIGN -> String
$cshowList :: [SignKeyDSIGNM Ed25519DSIGN] -> String -> String
showList :: [SignKeyDSIGNM Ed25519DSIGN] -> String -> String
Show)
deriveVerKeyDSIGNM :: forall (m :: * -> *).
(MonadThrow m, MonadST m) =>
SignKeyDSIGNM Ed25519DSIGN -> m (VerKeyDSIGN Ed25519DSIGN)
deriveVerKeyDSIGNM (SignKeyEd25519DSIGNM MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk) =
PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> VerKeyDSIGN Ed25519DSIGN
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
-> VerKeyDSIGN Ed25519DSIGN
VerKeyEd25519DSIGN (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> VerKeyDSIGN Ed25519DSIGN)
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> m (VerKeyDSIGN Ed25519DSIGN)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
MLockedSizedBytes n -> (SizedPtr n -> m r) -> m r
mlsbUseAsSizedPtr MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr -> do
(PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
psb, Maybe Errno
maybeErrno) <-
(SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m (Maybe Errno))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES,
Maybe Errno)
forall (n :: Nat) r (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m r) -> m (PinnedSizedBytes n, r)
psbCreateSizedResult ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m (Maybe Errno))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES,
Maybe Errno))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m (Maybe Errno))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES,
Maybe Errno)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr ->
ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a. ST (PrimState m) a -> m a
forall (m :: * -> *) a. MonadST m => ST (PrimState m) a -> m a
stToIO (ST (PrimState m) (Maybe Errno) -> m (Maybe Errno))
-> ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a b. (a -> b) -> a -> b
$ do
(forall s. ST s Int) -> ST (PrimState m) (Maybe Errno)
forall (m :: * -> *).
MonadST m =>
(forall s. ST s Int) -> m (Maybe Errno)
cOrError ((forall s. ST s Int) -> ST (PrimState m) (Maybe Errno))
-> (forall s. ST s Int) -> ST (PrimState m) (Maybe Errno)
forall a b. (a -> b) -> a -> b
$
IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (IO Int -> ST s Int) -> IO Int -> ST s Int
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
String -> String -> Maybe Errno -> m ()
forall (m :: * -> *).
MonadThrow m =>
String -> String -> Maybe Errno -> m ()
throwOnErrno String
"deriveVerKeyDSIGN @Ed25519DSIGN" String
"c_crypto_sign_ed25519_sk_to_pk" Maybe Errno
maybeErrno
PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
psb
signDSIGNM :: forall a (m :: * -> *).
(Signable Ed25519DSIGN a, MonadST m, MonadThrow m) =>
ContextDSIGN Ed25519DSIGN
-> a -> SignKeyDSIGNM Ed25519DSIGN -> m (SigDSIGN Ed25519DSIGN)
signDSIGNM () a
a (SignKeyEd25519DSIGNM MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk) =
let bs :: ByteString
bs = a -> ByteString
forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
a
in PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SigDSIGN Ed25519DSIGN
PinnedSizedBytes (SizeSigDSIGN Ed25519DSIGN)
-> SigDSIGN Ed25519DSIGN
SigEd25519DSIGN (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SigDSIGN Ed25519DSIGN)
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> m (SigDSIGN Ed25519DSIGN)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
MLockedSizedBytes n -> (SizedPtr n -> m r) -> m r
mlsbUseAsSizedPtr MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr -> do
(PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
psb, Maybe Errno
maybeErrno) <-
(SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m (Maybe Errno))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES,
Maybe Errno)
forall (n :: Nat) r (m :: * -> *).
(KnownNat n, MonadST m) =>
(SizedPtr n -> m r) -> m (PinnedSizedBytes n, r)
psbCreateSizedResult ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m (Maybe Errno))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES,
Maybe Errno))
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m (Maybe Errno))
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES,
Maybe Errno)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sigPtr ->
ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a. ST (PrimState m) a -> m a
forall (m :: * -> *) a. MonadST m => ST (PrimState m) a -> m a
stToIO (ST (PrimState m) (Maybe Errno) -> m (Maybe Errno))
-> ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a b. (a -> b) -> a -> b
$ do
(forall s. ST s Int) -> ST (PrimState m) (Maybe Errno)
forall (m :: * -> *).
MonadST m =>
(forall s. ST s Int) -> m (Maybe Errno)
cOrError ((forall s. ST s Int) -> ST (PrimState m) (Maybe Errno))
-> (forall s. ST s Int) -> ST (PrimState m) (Maybe Errno)
forall a b. (a -> b) -> a -> b
$ IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (IO Int -> ST s Int) -> IO Int -> ST s Int
forall a b. (a -> b) -> a -> b
$ do
ByteString -> (CStringLen -> IO Int) -> IO Int
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BS.useAsCStringLen ByteString
bs ((CStringLen -> IO Int) -> IO Int)
-> (CStringLen -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \(Ptr CChar
ptr, Int
len) ->
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
String -> String -> Maybe Errno -> m ()
forall (m :: * -> *).
MonadThrow m =>
String -> String -> Maybe Errno -> m ()
throwOnErrno String
"signDSIGNM @Ed25519DSIGN" String
"c_crypto_sign_ed25519_detached" Maybe Errno
maybeErrno
PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return PinnedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
psb
{-# NOINLINE genKeyDSIGNMWith #-}
genKeyDSIGNMWith :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
MLockedAllocator m
-> MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
-> m (SignKeyDSIGNM Ed25519DSIGN)
genKeyDSIGNMWith MLockedAllocator m
allocator MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
seed =
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGNM Ed25519DSIGN
SignKeyEd25519DSIGNM (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGNM Ed25519DSIGN)
-> m (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> m (SignKeyDSIGNM Ed25519DSIGN)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> do
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk <- MLockedAllocator m
-> (KnownNat CRYPTO_SIGN_ED25519_SECRETKEYBYTES, MonadST m) =>
m (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat) (m :: * -> *).
MLockedAllocator m
-> (KnownNat n, MonadST m) => m (MLockedSizedBytes n)
mlsbNewWith MLockedAllocator m
allocator
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()) -> m ()
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
MLockedSizedBytes n -> (SizedPtr n -> m r) -> m r
mlsbUseAsSizedPtr MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()) -> m ())
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> (Ptr Word8 -> m ()) -> m ()
forall (m :: * -> *) (n :: Nat) b.
MonadST m =>
MLockedSeed n -> (Ptr Word8 -> m b) -> m b
mlockedSeedUseAsCPtr MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
seed ((Ptr Word8 -> m ()) -> m ()) -> (Ptr Word8 -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
seedPtr -> do
Maybe Errno
maybeErrno <- ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a. ST (PrimState m) a -> m a
forall (m :: * -> *) a. MonadST m => ST (PrimState m) a -> m a
stToIO (ST (PrimState m) (Maybe Errno) -> m (Maybe Errno))
-> ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a b. (a -> b) -> a -> b
$ (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> ST RealWorld (Maybe Errno))
-> ST (PrimState m) (Maybe Errno)
forall {n :: Nat} {a} {s}.
KnownNat n =>
(SizedPtr n -> ST RealWorld a) -> ST s a
allocaSizedST ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> ST RealWorld (Maybe Errno))
-> ST (PrimState m) (Maybe Errno))
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> ST RealWorld (Maybe Errno))
-> ST (PrimState m) (Maybe Errno)
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
pkPtr -> do
(forall s. ST s Int) -> ST RealWorld (Maybe Errno)
forall (m :: * -> *).
MonadST m =>
(forall s. ST s Int) -> m (Maybe Errno)
cOrError ((forall s. ST s Int) -> ST RealWorld (Maybe Errno))
-> (forall s. ST s Int) -> ST RealWorld (Maybe Errno)
forall a b. (a -> b) -> a -> b
$
IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (IO Int -> ST s Int) -> IO Int -> ST s Int
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 Word8 -> Ptr Void)
-> Ptr Word8
-> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Word8 -> Ptr Void
forall a b. Ptr a -> Ptr b
castPtr (Ptr Word8 -> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Ptr Word8 -> SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall a b. (a -> b) -> a -> b
$ Ptr Word8
seedPtr)
String -> String -> Maybe Errno -> m ()
forall (m :: * -> *).
MonadThrow m =>
String -> String -> Maybe Errno -> m ()
throwOnErrno String
"genKeyDSIGNM @Ed25519DSIGN" String
"c_crypto_sign_ed25519_seed_keypair" Maybe Errno
maybeErrno
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk
where
allocaSizedST :: (SizedPtr n -> ST RealWorld a) -> ST s a
allocaSizedST SizedPtr n -> ST RealWorld a
k =
IO a -> ST s a
forall a s. IO a -> ST s a
unsafeIOToST (IO a -> ST s a) -> IO a -> ST s a
forall a b. (a -> b) -> a -> b
$ (SizedPtr n -> IO a) -> IO a
forall (n :: Nat) b. KnownNat n => (SizedPtr n -> IO b) -> IO b
allocaSized ((SizedPtr n -> IO a) -> IO a) -> (SizedPtr n -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \SizedPtr n
ptr -> ST (PrimState IO) a -> IO a
forall a. ST (PrimState IO) a -> IO a
forall (m :: * -> *) a. MonadST m => ST (PrimState m) a -> m a
stToIO (ST (PrimState IO) a -> IO a) -> ST (PrimState IO) a -> IO a
forall a b. (a -> b) -> a -> b
$ SizedPtr n -> ST RealWorld a
k SizedPtr n
ptr
cloneKeyDSIGNMWith :: forall (m :: * -> *).
MonadST m =>
MLockedAllocator m
-> SignKeyDSIGNM Ed25519DSIGN -> m (SignKeyDSIGNM Ed25519DSIGN)
cloneKeyDSIGNMWith MLockedAllocator m
allocator (SignKeyEd25519DSIGNM MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk) =
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGNM Ed25519DSIGN
SignKeyEd25519DSIGNM (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> SignKeyDSIGNM Ed25519DSIGN)
-> m (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
-> m (SignKeyDSIGNM Ed25519DSIGN)
forall (m :: * -> *) a b. Monad m => (a -> b) -> m a -> m b
<$!> MLockedAllocator m
-> MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> m (MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES)
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
MLockedAllocator m
-> MLockedSizedBytes n -> m (MLockedSizedBytes n)
mlsbCopyWith MLockedAllocator m
allocator MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk
getSeedDSIGNMWith :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
MLockedAllocator m
-> Proxy Ed25519DSIGN
-> SignKeyDSIGNM Ed25519DSIGN
-> m (MLockedSeed (SeedSizeDSIGN Ed25519DSIGN))
getSeedDSIGNMWith MLockedAllocator m
allocator Proxy Ed25519DSIGN
_ (SignKeyEd25519DSIGNM MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk) = do
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed <- MLockedAllocator m
-> m (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
MLockedAllocator m -> m (MLockedSeed n)
mlockedSeedNewWith MLockedAllocator m
allocator
MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()) -> m ()
forall (n :: Nat) r (m :: * -> *).
MonadST m =>
MLockedSizedBytes n -> (SizedPtr n -> m r) -> m r
mlsbUseAsSizedPtr MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk ((SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()) -> m ())
-> (SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_SECRETKEYBYTES
skPtr ->
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()) -> m ()
forall (m :: * -> *) (n :: Nat) b.
MonadST m =>
MLockedSeed n -> (SizedPtr n -> m b) -> m b
mlockedSeedUseAsSizedPtr MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed ((SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()) -> m ())
-> (SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \SizedPtr CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seedPtr -> do
Maybe Errno
maybeErrno <-
ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a. ST (PrimState m) a -> m a
forall (m :: * -> *) a. MonadST m => ST (PrimState m) a -> m a
stToIO (ST (PrimState m) (Maybe Errno) -> m (Maybe Errno))
-> ST (PrimState m) (Maybe Errno) -> m (Maybe Errno)
forall a b. (a -> b) -> a -> b
$
(forall s. ST s Int) -> ST (PrimState m) (Maybe Errno)
forall (m :: * -> *).
MonadST m =>
(forall s. ST s Int) -> m (Maybe Errno)
cOrError ((forall s. ST s Int) -> ST (PrimState m) (Maybe Errno))
-> (forall s. ST s Int) -> ST (PrimState m) (Maybe Errno)
forall a b. (a -> b) -> a -> b
$
IO Int -> ST s Int
forall a s. IO a -> ST s a
unsafeIOToST (IO Int -> ST s Int) -> IO Int -> ST s Int
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
String -> String -> Maybe Errno -> m ()
forall (m :: * -> *).
MonadThrow m =>
String -> String -> Maybe Errno -> m ()
throwOnErrno String
"genKeyDSIGNM @Ed25519DSIGN" String
"c_crypto_sign_ed25519_seed_keypair" Maybe Errno
maybeErrno
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> m (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed
forgetSignKeyDSIGNMWith :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
MLockedAllocator m -> SignKeyDSIGNM Ed25519DSIGN -> m ()
forgetSignKeyDSIGNMWith MLockedAllocator m
_ (SignKeyEd25519DSIGNM MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk) = MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES -> m ()
forall (m :: * -> *) (n :: Nat).
MonadST m =>
MLockedSizedBytes n -> m ()
mlsbFinalize MLockedSizedBytes CRYPTO_SIGN_ED25519_SECRETKEYBYTES
sk
instance UnsoundDSIGNMAlgorithm Ed25519DSIGN where
rawSerialiseSignKeyDSIGNM :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
SignKeyDSIGNM Ed25519DSIGN -> m ByteString
rawSerialiseSignKeyDSIGNM SignKeyDSIGNM Ed25519DSIGN
sk = do
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed <- Proxy Ed25519DSIGN
-> SignKeyDSIGNM Ed25519DSIGN
-> m (MLockedSeed (SeedSizeDSIGN Ed25519DSIGN))
forall v (m :: * -> *).
(DSIGNMAlgorithm v, MonadST m, MonadThrow m) =>
Proxy v -> SignKeyDSIGNM v -> m (MLockedSeed (SeedSizeDSIGN v))
getSeedDSIGNM (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN) SignKeyDSIGNM Ed25519DSIGN
sk
ByteString
raw <- MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> m ByteString
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
MLockedSizedBytes n -> m ByteString
mlsbToByteString (MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> m ByteString)
-> (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> m ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall (n :: Nat). MLockedSeed n -> MLockedSizedBytes n
mlockedSeedMLSB (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ByteString)
-> MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ByteString
forall a b. (a -> b) -> a -> b
$ MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()
forall (m :: * -> *) (n :: Nat). MonadST m => MLockedSeed n -> m ()
mlockedSeedFinalize MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed
ByteString -> m ByteString
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
raw
rawDeserialiseSignKeyDSIGNMWith :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
MLockedAllocator m
-> ByteString -> m (Maybe (SignKeyDSIGNM Ed25519DSIGN))
rawDeserialiseSignKeyDSIGNMWith MLockedAllocator m
allocator ByteString
raw = do
Maybe (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
mseed <- (MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Maybe (MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Maybe (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
forall (n :: Nat). MLockedSizedBytes n -> MLockedSeed n
MLockedSeed (Maybe (MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> Maybe (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> m (Maybe (MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> m (Maybe (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MLockedAllocator m
-> ByteString
-> m (Maybe (MLockedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
MLockedAllocator m -> ByteString -> m (Maybe (MLockedSizedBytes n))
mlsbFromByteStringCheckWith MLockedAllocator m
allocator ByteString
raw
case Maybe (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
mseed of
Maybe (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
Nothing -> Maybe (SignKeyDSIGNM Ed25519DSIGN)
-> m (Maybe (SignKeyDSIGNM Ed25519DSIGN))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (SignKeyDSIGNM Ed25519DSIGN)
forall a. Maybe a
Nothing
Just MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed -> do
Maybe (SignKeyDSIGNM Ed25519DSIGN)
sk <- SignKeyDSIGNM Ed25519DSIGN -> Maybe (SignKeyDSIGNM Ed25519DSIGN)
forall a. a -> Maybe a
Just (SignKeyDSIGNM Ed25519DSIGN -> Maybe (SignKeyDSIGNM Ed25519DSIGN))
-> m (SignKeyDSIGNM Ed25519DSIGN)
-> m (Maybe (SignKeyDSIGNM Ed25519DSIGN))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MLockedAllocator m
-> MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
-> m (SignKeyDSIGNM Ed25519DSIGN)
forall v (m :: * -> *).
(DSIGNMAlgorithm v, MonadST m, MonadThrow m) =>
MLockedAllocator m
-> MLockedSeed (SeedSizeDSIGN v) -> m (SignKeyDSIGNM v)
forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
MLockedAllocator m
-> MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
-> m (SignKeyDSIGNM Ed25519DSIGN)
genKeyDSIGNMWith MLockedAllocator m
allocator MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
seed
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()
forall (m :: * -> *) (n :: Nat). MonadST m => MLockedSeed n -> m ()
mlockedSeedFinalize MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed
Maybe (SignKeyDSIGNM Ed25519DSIGN)
-> m (Maybe (SignKeyDSIGNM Ed25519DSIGN))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (SignKeyDSIGNM Ed25519DSIGN)
sk
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 :: forall s. 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
encodedSignKeyDSIGNSizeExpr
instance FromCBOR (SignKeyDSIGN Ed25519DSIGN) where
fromCBOR :: forall s. 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 :: forall s. Decoder s (SigDSIGN Ed25519DSIGN)
fromCBOR = Decoder s (SigDSIGN Ed25519DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN
instance
TypeError ('Text "CBOR encoding would violate mlocking guarantees") =>
ToCBOR (SignKeyDSIGNM Ed25519DSIGN)
where
toCBOR :: SignKeyDSIGNM Ed25519DSIGN -> Encoding
toCBOR = String -> SignKeyDSIGNM Ed25519DSIGN -> Encoding
forall a. HasCallStack => String -> a
error String
"unsupported"
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SignKeyDSIGNM Ed25519DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = String -> Proxy (SignKeyDSIGNM Ed25519DSIGN) -> Size
forall a. HasCallStack => String -> a
error String
"unsupported"
instance
TypeError ('Text "CBOR decoding would violate mlocking guarantees") =>
FromCBOR (SignKeyDSIGNM Ed25519DSIGN)
where
fromCBOR :: forall s. Decoder s (SignKeyDSIGNM Ed25519DSIGN)
fromCBOR = String -> Decoder s (SignKeyDSIGNM Ed25519DSIGN)
forall a. HasCallStack => String -> a
error String
"unsupported"
instance DirectSerialise (SignKeyDSIGNM Ed25519DSIGN) where
directSerialise :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
(Ptr CChar -> CSize -> m ()) -> SignKeyDSIGNM Ed25519DSIGN -> m ()
directSerialise Ptr CChar -> CSize -> m ()
push SignKeyDSIGNM Ed25519DSIGN
sk = do
m (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ())
-> (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ())
-> m ()
forall a b c. m a -> (a -> m b) -> (a -> m c) -> m c
forall (m :: * -> *) a b c.
MonadThrow m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket
(Proxy Ed25519DSIGN
-> SignKeyDSIGNM Ed25519DSIGN
-> m (MLockedSeed (SeedSizeDSIGN Ed25519DSIGN))
forall v (m :: * -> *).
(DSIGNMAlgorithm v, MonadST m, MonadThrow m) =>
Proxy v -> SignKeyDSIGNM v -> m (MLockedSeed (SeedSizeDSIGN v))
getSeedDSIGNM (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN) SignKeyDSIGNM Ed25519DSIGN
sk)
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()
forall (m :: * -> *) (n :: Nat). MonadST m => MLockedSeed n -> m ()
mlockedSeedFinalize
( \MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed -> MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> (Ptr Word8 -> m ()) -> m ()
forall (m :: * -> *) (n :: Nat) b.
MonadST m =>
MLockedSeed n -> (Ptr Word8 -> m b) -> m b
mlockedSeedUseAsCPtr MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed ((Ptr Word8 -> m ()) -> m ()) -> (Ptr Word8 -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
Ptr CChar -> CSize -> m ()
push
(Ptr Word8 -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr)
(Word -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> CSize) -> Word -> CSize
forall a b. (a -> b) -> a -> b
$ Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
seedSizeDSIGN (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN))
)
instance DirectDeserialise (SignKeyDSIGNM Ed25519DSIGN) where
directDeserialise :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
(Ptr CChar -> CSize -> m ()) -> m (SignKeyDSIGNM Ed25519DSIGN)
directDeserialise Ptr CChar -> CSize -> m ()
pull = do
m (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
-> (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ())
-> (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> m (SignKeyDSIGNM Ed25519DSIGN))
-> m (SignKeyDSIGNM Ed25519DSIGN)
forall a b c. m a -> (a -> m b) -> (a -> m c) -> m c
forall (m :: * -> *) a b c.
MonadThrow m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket
m (MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
m (MLockedSeed n)
mlockedSeedNew
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES -> m ()
forall (m :: * -> *) (n :: Nat). MonadST m => MLockedSeed n -> m ()
mlockedSeedFinalize
( \MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed -> do
MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> (Ptr Word8 -> m ()) -> m ()
forall (m :: * -> *) (n :: Nat) b.
MonadST m =>
MLockedSeed n -> (Ptr Word8 -> m b) -> m b
mlockedSeedUseAsCPtr MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
seed ((Ptr Word8 -> m ()) -> m ()) -> (Ptr Word8 -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr -> do
Ptr CChar -> CSize -> m ()
pull
(Ptr Word8 -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr)
(Word -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> CSize) -> Word -> CSize
forall a b. (a -> b) -> a -> b
$ Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
seedSizeDSIGN (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN))
MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
-> m (SignKeyDSIGNM Ed25519DSIGN)
forall v (m :: * -> *).
(DSIGNMAlgorithm v, MonadST m, MonadThrow m) =>
MLockedSeed (SeedSizeDSIGN v) -> m (SignKeyDSIGNM v)
genKeyDSIGNM MLockedSeed CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
MLockedSeed (SeedSizeDSIGN Ed25519DSIGN)
seed
)
instance DirectSerialise (VerKeyDSIGN Ed25519DSIGN) where
directSerialise :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
(Ptr CChar -> CSize -> m ()) -> VerKeyDSIGN Ed25519DSIGN -> m ()
directSerialise Ptr CChar -> CSize -> m ()
push (VerKeyEd25519DSIGN PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
psb) = do
PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
-> (Ptr Word8 -> CSize -> m ()) -> m ()
forall (n :: Nat) r (m :: * -> *).
(KnownNat n, MonadST m) =>
PinnedSizedBytes n -> (Ptr Word8 -> CSize -> m r) -> m r
psbUseAsCPtrLen PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
psb ((Ptr Word8 -> CSize -> m ()) -> m ())
-> (Ptr Word8 -> CSize -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr CSize
_ ->
Ptr CChar -> CSize -> m ()
push
(Ptr Word8 -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr)
(Word -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> CSize) -> Word -> CSize
forall a b. (a -> b) -> a -> b
$ Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
sizeVerKeyDSIGN (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN))
instance DirectDeserialise (VerKeyDSIGN Ed25519DSIGN) where
directDeserialise :: forall (m :: * -> *).
(MonadST m, MonadThrow m) =>
(Ptr CChar -> CSize -> m ()) -> m (VerKeyDSIGN Ed25519DSIGN)
directDeserialise Ptr CChar -> CSize -> m ()
pull = do
PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
psb <- (Ptr Word8 -> m ())
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall (n :: Nat) (m :: * -> *).
(KnownNat n, MonadST m) =>
(Ptr Word8 -> m ()) -> m (PinnedSizedBytes n)
psbCreate ((Ptr Word8 -> m ())
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES))
-> (Ptr Word8 -> m ())
-> m (PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
Ptr CChar -> CSize -> m ()
pull
(Ptr Word8 -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
ptr)
(Word -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> CSize) -> Word -> CSize
forall a b. (a -> b) -> a -> b
$ Proxy Ed25519DSIGN -> Word
forall v (proxy :: * -> *). DSIGNAlgorithm v => proxy v -> Word
sizeVerKeyDSIGN (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @Ed25519DSIGN))
VerKeyDSIGN Ed25519DSIGN -> m (VerKeyDSIGN Ed25519DSIGN)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (VerKeyDSIGN Ed25519DSIGN -> m (VerKeyDSIGN Ed25519DSIGN))
-> VerKeyDSIGN Ed25519DSIGN -> m (VerKeyDSIGN Ed25519DSIGN)
forall a b. (a -> b) -> a -> b
$! PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
-> VerKeyDSIGN Ed25519DSIGN
VerKeyEd25519DSIGN PinnedSizedBytes CRYPTO_SIGN_ED25519_PUBLICKEYBYTES
PinnedSizedBytes (SizeVerKeyDSIGN Ed25519DSIGN)
psb