{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Api.Crypto.Ed25519Bip32
( Ed25519Bip32DSIGN
, SigDSIGN (..)
, SignKeyDSIGN (..)
, VerKeyDSIGN (..)
, xPrvToBytes
, xPrvFromBytes
)
where
import Cardano.Prelude hiding (show)
import Prelude (show)
import Data.ByteArray as BA (ByteArrayAccess, ScrubbedBytes, convert)
import qualified Data.ByteString as BS
import NoThunks.Class (InspectHeap (..), NoThunks)
import Cardano.Binary (FromCBOR (..), ToCBOR (..))
import qualified Cardano.Crypto.Wallet as CC
import Cardano.Crypto.DSIGN.Class
import Cardano.Crypto.Seed
import Cardano.Crypto.Util (SignableRepresentation (..))
import qualified Crypto.ECC.Edwards25519 as Ed25519
import Crypto.Error (eitherCryptoError)
data Ed25519Bip32DSIGN
instance DSIGNAlgorithm Ed25519Bip32DSIGN where
type SeedSizeDSIGN Ed25519Bip32DSIGN = 32
type SizeVerKeyDSIGN Ed25519Bip32DSIGN = 64
type SizeSignKeyDSIGN Ed25519Bip32DSIGN = 96
type SizeSigDSIGN Ed25519Bip32DSIGN = 64
newtype VerKeyDSIGN Ed25519Bip32DSIGN = VerKeyEd25519Bip32DSIGN CC.XPub
deriving (Int -> VerKeyDSIGN Ed25519Bip32DSIGN -> ShowS
[VerKeyDSIGN Ed25519Bip32DSIGN] -> ShowS
VerKeyDSIGN Ed25519Bip32DSIGN -> String
(Int -> VerKeyDSIGN Ed25519Bip32DSIGN -> ShowS)
-> (VerKeyDSIGN Ed25519Bip32DSIGN -> String)
-> ([VerKeyDSIGN Ed25519Bip32DSIGN] -> ShowS)
-> Show (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerKeyDSIGN Ed25519Bip32DSIGN] -> ShowS
$cshowList :: [VerKeyDSIGN Ed25519Bip32DSIGN] -> ShowS
show :: VerKeyDSIGN Ed25519Bip32DSIGN -> String
$cshow :: VerKeyDSIGN Ed25519Bip32DSIGN -> String
showsPrec :: Int -> VerKeyDSIGN Ed25519Bip32DSIGN -> ShowS
$cshowsPrec :: Int -> VerKeyDSIGN Ed25519Bip32DSIGN -> ShowS
Show, VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool
(VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool)
-> (VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool)
-> Eq (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool
$c/= :: VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool
== :: VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool
$c== :: VerKeyDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN -> Bool
Eq, (forall x.
VerKeyDSIGN Ed25519Bip32DSIGN
-> Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x)
-> (forall x.
Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x
-> VerKeyDSIGN Ed25519Bip32DSIGN)
-> Generic (VerKeyDSIGN Ed25519Bip32DSIGN)
forall x.
Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x
-> VerKeyDSIGN Ed25519Bip32DSIGN
forall x.
VerKeyDSIGN Ed25519Bip32DSIGN
-> Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x
-> VerKeyDSIGN Ed25519Bip32DSIGN
$cfrom :: forall x.
VerKeyDSIGN Ed25519Bip32DSIGN
-> Rep (VerKeyDSIGN Ed25519Bip32DSIGN) x
Generic)
deriving newtype VerKeyDSIGN Ed25519Bip32DSIGN -> ()
(VerKeyDSIGN Ed25519Bip32DSIGN -> ())
-> NFData (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: VerKeyDSIGN Ed25519Bip32DSIGN -> ()
$crnf :: VerKeyDSIGN Ed25519Bip32DSIGN -> ()
NFData
deriving Context -> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> String
(Context -> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo))
-> (Context
-> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo))
-> (Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> String)
-> NoThunks (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> String
$cshowTypeOf :: Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> String
wNoThunks :: Context -> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> VerKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
NoThunks via InspectHeap CC.XPub
newtype SignKeyDSIGN Ed25519Bip32DSIGN = SignKeyEd25519Bip32DSIGN CC.XPrv
deriving ((forall x.
SignKeyDSIGN Ed25519Bip32DSIGN
-> Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x)
-> (forall x.
Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x
-> SignKeyDSIGN Ed25519Bip32DSIGN)
-> Generic (SignKeyDSIGN Ed25519Bip32DSIGN)
forall x.
Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x
-> SignKeyDSIGN Ed25519Bip32DSIGN
forall x.
SignKeyDSIGN Ed25519Bip32DSIGN
-> Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x
-> SignKeyDSIGN Ed25519Bip32DSIGN
$cfrom :: forall x.
SignKeyDSIGN Ed25519Bip32DSIGN
-> Rep (SignKeyDSIGN Ed25519Bip32DSIGN) x
Generic, SignKeyDSIGN Ed25519Bip32DSIGN -> Int
SignKeyDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
SignKeyDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
(SignKeyDSIGN Ed25519Bip32DSIGN -> Int)
-> (forall p a.
SignKeyDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a)
-> (forall p. SignKeyDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ())
-> ByteArrayAccess (SignKeyDSIGN Ed25519Bip32DSIGN)
forall p. SignKeyDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a.
SignKeyDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
copyByteArrayToPtr :: SignKeyDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
$ccopyByteArrayToPtr :: forall p. SignKeyDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
withByteArray :: SignKeyDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
$cwithByteArray :: forall p a.
SignKeyDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
length :: SignKeyDSIGN Ed25519Bip32DSIGN -> Int
$clength :: SignKeyDSIGN Ed25519Bip32DSIGN -> Int
ByteArrayAccess)
deriving newtype SignKeyDSIGN Ed25519Bip32DSIGN -> ()
(SignKeyDSIGN Ed25519Bip32DSIGN -> ())
-> NFData (SignKeyDSIGN Ed25519Bip32DSIGN)
forall a. (a -> ()) -> NFData a
rnf :: SignKeyDSIGN Ed25519Bip32DSIGN -> ()
$crnf :: SignKeyDSIGN Ed25519Bip32DSIGN -> ()
NFData
deriving Context -> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> String
(Context -> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo))
-> (Context
-> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo))
-> (Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> String)
-> NoThunks (SignKeyDSIGN Ed25519Bip32DSIGN)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> String
$cshowTypeOf :: Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> String
wNoThunks :: Context -> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SignKeyDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
NoThunks via InspectHeap CC.XPrv
newtype SigDSIGN Ed25519Bip32DSIGN = SigEd25519Bip32DSIGN CC.XSignature
deriving (Int -> SigDSIGN Ed25519Bip32DSIGN -> ShowS
[SigDSIGN Ed25519Bip32DSIGN] -> ShowS
SigDSIGN Ed25519Bip32DSIGN -> String
(Int -> SigDSIGN Ed25519Bip32DSIGN -> ShowS)
-> (SigDSIGN Ed25519Bip32DSIGN -> String)
-> ([SigDSIGN Ed25519Bip32DSIGN] -> ShowS)
-> Show (SigDSIGN Ed25519Bip32DSIGN)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigDSIGN Ed25519Bip32DSIGN] -> ShowS
$cshowList :: [SigDSIGN Ed25519Bip32DSIGN] -> ShowS
show :: SigDSIGN Ed25519Bip32DSIGN -> String
$cshow :: SigDSIGN Ed25519Bip32DSIGN -> String
showsPrec :: Int -> SigDSIGN Ed25519Bip32DSIGN -> ShowS
$cshowsPrec :: Int -> SigDSIGN Ed25519Bip32DSIGN -> ShowS
Show, SigDSIGN Ed25519Bip32DSIGN -> SigDSIGN Ed25519Bip32DSIGN -> Bool
(SigDSIGN Ed25519Bip32DSIGN -> SigDSIGN Ed25519Bip32DSIGN -> Bool)
-> (SigDSIGN Ed25519Bip32DSIGN
-> SigDSIGN Ed25519Bip32DSIGN -> Bool)
-> Eq (SigDSIGN Ed25519Bip32DSIGN)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigDSIGN Ed25519Bip32DSIGN -> SigDSIGN Ed25519Bip32DSIGN -> Bool
$c/= :: SigDSIGN Ed25519Bip32DSIGN -> SigDSIGN Ed25519Bip32DSIGN -> Bool
== :: SigDSIGN Ed25519Bip32DSIGN -> SigDSIGN Ed25519Bip32DSIGN -> Bool
$c== :: SigDSIGN Ed25519Bip32DSIGN -> SigDSIGN Ed25519Bip32DSIGN -> Bool
Eq, (forall x.
SigDSIGN Ed25519Bip32DSIGN -> Rep (SigDSIGN Ed25519Bip32DSIGN) x)
-> (forall x.
Rep (SigDSIGN Ed25519Bip32DSIGN) x -> SigDSIGN Ed25519Bip32DSIGN)
-> Generic (SigDSIGN Ed25519Bip32DSIGN)
forall x.
Rep (SigDSIGN Ed25519Bip32DSIGN) x -> SigDSIGN Ed25519Bip32DSIGN
forall x.
SigDSIGN Ed25519Bip32DSIGN -> Rep (SigDSIGN Ed25519Bip32DSIGN) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep (SigDSIGN Ed25519Bip32DSIGN) x -> SigDSIGN Ed25519Bip32DSIGN
$cfrom :: forall x.
SigDSIGN Ed25519Bip32DSIGN -> Rep (SigDSIGN Ed25519Bip32DSIGN) x
Generic, SigDSIGN Ed25519Bip32DSIGN -> Int
SigDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
SigDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
(SigDSIGN Ed25519Bip32DSIGN -> Int)
-> (forall p a.
SigDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a)
-> (forall p. SigDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ())
-> ByteArrayAccess (SigDSIGN Ed25519Bip32DSIGN)
forall p. SigDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. SigDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
copyByteArrayToPtr :: SigDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
$ccopyByteArrayToPtr :: forall p. SigDSIGN Ed25519Bip32DSIGN -> Ptr p -> IO ()
withByteArray :: SigDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
$cwithByteArray :: forall p a. SigDSIGN Ed25519Bip32DSIGN -> (Ptr p -> IO a) -> IO a
length :: SigDSIGN Ed25519Bip32DSIGN -> Int
$clength :: SigDSIGN Ed25519Bip32DSIGN -> Int
ByteArrayAccess)
deriving Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
Proxy (SigDSIGN Ed25519Bip32DSIGN) -> String
(Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo))
-> (Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo))
-> (Proxy (SigDSIGN Ed25519Bip32DSIGN) -> String)
-> NoThunks (SigDSIGN Ed25519Bip32DSIGN)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (SigDSIGN Ed25519Bip32DSIGN) -> String
$cshowTypeOf :: Proxy (SigDSIGN Ed25519Bip32DSIGN) -> String
wNoThunks :: Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
noThunks :: Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SigDSIGN Ed25519Bip32DSIGN -> IO (Maybe ThunkInfo)
NoThunks via InspectHeap CC.XSignature
algorithmNameDSIGN :: proxy Ed25519Bip32DSIGN -> String
algorithmNameDSIGN proxy Ed25519Bip32DSIGN
_ = String
"ed25519_bip32"
deriveVerKeyDSIGN :: SignKeyDSIGN Ed25519Bip32DSIGN -> VerKeyDSIGN Ed25519Bip32DSIGN
deriveVerKeyDSIGN (SignKeyEd25519Bip32DSIGN sk) =
XPub -> VerKeyDSIGN Ed25519Bip32DSIGN
VerKeyEd25519Bip32DSIGN (XPub -> VerKeyDSIGN Ed25519Bip32DSIGN)
-> XPub -> VerKeyDSIGN Ed25519Bip32DSIGN
forall a b. (a -> b) -> a -> b
$ HasCallStack => XPrv -> XPub
XPrv -> XPub
CC.toXPub XPrv
sk
type Signable Ed25519Bip32DSIGN = SignableRepresentation
signDSIGN :: ContextDSIGN Ed25519Bip32DSIGN
-> a
-> SignKeyDSIGN Ed25519Bip32DSIGN
-> SigDSIGN Ed25519Bip32DSIGN
signDSIGN () a
a (SignKeyEd25519Bip32DSIGN sk) =
XSignature -> SigDSIGN Ed25519Bip32DSIGN
SigEd25519Bip32DSIGN (XSignature -> SigDSIGN Ed25519Bip32DSIGN)
-> XSignature -> SigDSIGN Ed25519Bip32DSIGN
forall a b. (a -> b) -> a -> b
$
ScrubbedBytes -> XPrv -> ByteString -> XSignature
forall passPhrase msg.
(ByteArrayAccess passPhrase, ByteArrayAccess msg) =>
passPhrase -> XPrv -> msg -> XSignature
CC.sign (ScrubbedBytes
forall a. Monoid a => a
mempty :: ScrubbedBytes) XPrv
sk (a -> ByteString
forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
a)
verifyDSIGN :: ContextDSIGN Ed25519Bip32DSIGN
-> VerKeyDSIGN Ed25519Bip32DSIGN
-> a
-> SigDSIGN Ed25519Bip32DSIGN
-> Either String ()
verifyDSIGN () (VerKeyEd25519Bip32DSIGN vk) a
a (SigEd25519Bip32DSIGN sig) =
if XPub -> ByteString -> XSignature -> Bool
forall msg.
ByteArrayAccess msg =>
XPub -> msg -> XSignature -> Bool
CC.verify XPub
vk (a -> ByteString
forall a. SignableRepresentation a => a -> ByteString
getSignableRepresentation a
a) XSignature
sig
then () -> Either String ()
forall a b. b -> Either a b
Right ()
else String -> Either String ()
forall a b. a -> Either a b
Left String
"Verification failed"
genKeyDSIGN :: Seed -> SignKeyDSIGN Ed25519Bip32DSIGN
genKeyDSIGN Seed
seed =
XPrv -> SignKeyDSIGN Ed25519Bip32DSIGN
SignKeyEd25519Bip32DSIGN (XPrv -> SignKeyDSIGN Ed25519Bip32DSIGN)
-> XPrv -> SignKeyDSIGN Ed25519Bip32DSIGN
forall a b. (a -> b) -> a -> b
$
ByteString -> ScrubbedBytes -> ScrubbedBytes -> XPrv
forall keyPassPhrase generationPassPhrase seed.
(ByteArrayAccess keyPassPhrase,
ByteArrayAccess generationPassPhrase, ByteArrayAccess seed) =>
seed -> generationPassPhrase -> keyPassPhrase -> XPrv
CC.generateNew
(Seed -> ByteString
getSeedBytes Seed
seed)
(ScrubbedBytes
forall a. Monoid a => a
mempty :: ScrubbedBytes)
(ScrubbedBytes
forall a. Monoid a => a
mempty :: ScrubbedBytes)
rawSerialiseVerKeyDSIGN :: VerKeyDSIGN Ed25519Bip32DSIGN -> ByteString
rawSerialiseVerKeyDSIGN (VerKeyEd25519Bip32DSIGN vk) = XPub -> ByteString
CC.unXPub XPub
vk
rawSerialiseSignKeyDSIGN :: SignKeyDSIGN Ed25519Bip32DSIGN -> ByteString
rawSerialiseSignKeyDSIGN (SignKeyEd25519Bip32DSIGN sk) = XPrv -> ByteString
xPrvToBytes XPrv
sk
rawSerialiseSigDSIGN :: SigDSIGN Ed25519Bip32DSIGN -> ByteString
rawSerialiseSigDSIGN = SigDSIGN Ed25519Bip32DSIGN -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert
rawDeserialiseVerKeyDSIGN :: ByteString -> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
rawDeserialiseVerKeyDSIGN =
(String -> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN))
-> (XPub -> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN))
-> Either String XPub
-> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
-> String -> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a b. a -> b -> a
const Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a. Maybe a
Nothing) (VerKeyDSIGN Ed25519Bip32DSIGN
-> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
forall a. a -> Maybe a
Just (VerKeyDSIGN Ed25519Bip32DSIGN
-> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN))
-> (XPub -> VerKeyDSIGN Ed25519Bip32DSIGN)
-> XPub
-> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. XPub -> VerKeyDSIGN Ed25519Bip32DSIGN
VerKeyEd25519Bip32DSIGN) (Either String XPub -> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN))
-> (ByteString -> Either String XPub)
-> ByteString
-> Maybe (VerKeyDSIGN Ed25519Bip32DSIGN)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Either String XPub
CC.xpub
rawDeserialiseSignKeyDSIGN :: ByteString -> Maybe (SignKeyDSIGN Ed25519Bip32DSIGN)
rawDeserialiseSignKeyDSIGN =
(XPrv -> SignKeyDSIGN Ed25519Bip32DSIGN)
-> Maybe XPrv -> Maybe (SignKeyDSIGN Ed25519Bip32DSIGN)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap XPrv -> SignKeyDSIGN Ed25519Bip32DSIGN
SignKeyEd25519Bip32DSIGN (Maybe XPrv -> Maybe (SignKeyDSIGN Ed25519Bip32DSIGN))
-> (ByteString -> Maybe XPrv)
-> ByteString
-> Maybe (SignKeyDSIGN Ed25519Bip32DSIGN)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Maybe XPrv
xPrvFromBytes
rawDeserialiseSigDSIGN :: ByteString -> Maybe (SigDSIGN Ed25519Bip32DSIGN)
rawDeserialiseSigDSIGN =
(String -> Maybe (SigDSIGN Ed25519Bip32DSIGN))
-> (XSignature -> Maybe (SigDSIGN Ed25519Bip32DSIGN))
-> Either String XSignature
-> Maybe (SigDSIGN Ed25519Bip32DSIGN)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (SigDSIGN Ed25519Bip32DSIGN)
-> String -> Maybe (SigDSIGN Ed25519Bip32DSIGN)
forall a b. a -> b -> a
const Maybe (SigDSIGN Ed25519Bip32DSIGN)
forall a. Maybe a
Nothing) (SigDSIGN Ed25519Bip32DSIGN -> Maybe (SigDSIGN Ed25519Bip32DSIGN)
forall a. a -> Maybe a
Just (SigDSIGN Ed25519Bip32DSIGN -> Maybe (SigDSIGN Ed25519Bip32DSIGN))
-> (XSignature -> SigDSIGN Ed25519Bip32DSIGN)
-> XSignature
-> Maybe (SigDSIGN Ed25519Bip32DSIGN)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. XSignature -> SigDSIGN Ed25519Bip32DSIGN
SigEd25519Bip32DSIGN) (Either String XSignature -> Maybe (SigDSIGN Ed25519Bip32DSIGN))
-> (ByteString -> Either String XSignature)
-> ByteString
-> Maybe (SigDSIGN Ed25519Bip32DSIGN)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Either String XSignature
CC.xsignature
instance Show (SignKeyDSIGN Ed25519Bip32DSIGN) where
show :: SignKeyDSIGN Ed25519Bip32DSIGN -> String
show (SignKeyEd25519Bip32DSIGN sk) = ByteString -> String
forall a. Show a => a -> String
show (ByteString -> String) -> ByteString -> String
forall a b. (a -> b) -> a -> b
$ XPrv -> ByteString
xPrvToBytes XPrv
sk
instance ToCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) where
toCBOR :: VerKeyDSIGN Ed25519Bip32DSIGN -> Encoding
toCBOR = VerKeyDSIGN Ed25519Bip32DSIGN -> Encoding
forall v. DSIGNAlgorithm v => VerKeyDSIGN v -> Encoding
encodeVerKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (VerKeyDSIGN Ed25519Bip32DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (VerKeyDSIGN v) -> Size
encodedVerKeyDSIGNSizeExpr
instance FromCBOR (VerKeyDSIGN Ed25519Bip32DSIGN) where
fromCBOR :: Decoder s (VerKeyDSIGN Ed25519Bip32DSIGN)
fromCBOR = Decoder s (VerKeyDSIGN Ed25519Bip32DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (VerKeyDSIGN v)
decodeVerKeyDSIGN
instance ToCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) where
toCBOR :: SignKeyDSIGN Ed25519Bip32DSIGN -> Encoding
toCBOR = SignKeyDSIGN Ed25519Bip32DSIGN -> Encoding
forall v. DSIGNAlgorithm v => SignKeyDSIGN v -> Encoding
encodeSignKeyDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (SignKeyDSIGN Ed25519Bip32DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (SignKeyDSIGN v) -> Size
encodedSignKeyDESIGNSizeExpr
instance FromCBOR (SignKeyDSIGN Ed25519Bip32DSIGN) where
fromCBOR :: Decoder s (SignKeyDSIGN Ed25519Bip32DSIGN)
fromCBOR = Decoder s (SignKeyDSIGN Ed25519Bip32DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SignKeyDSIGN v)
decodeSignKeyDSIGN
instance ToCBOR (SigDSIGN Ed25519Bip32DSIGN) where
toCBOR :: SigDSIGN Ed25519Bip32DSIGN -> Encoding
toCBOR = SigDSIGN Ed25519Bip32DSIGN -> Encoding
forall v. DSIGNAlgorithm v => SigDSIGN v -> Encoding
encodeSigDSIGN
encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size)
-> Proxy (SigDSIGN Ed25519Bip32DSIGN) -> Size
encodedSizeExpr forall t. ToCBOR t => Proxy t -> Size
_ = Proxy (SigDSIGN Ed25519Bip32DSIGN) -> Size
forall v. DSIGNAlgorithm v => Proxy (SigDSIGN v) -> Size
encodedSigDSIGNSizeExpr
instance FromCBOR (SigDSIGN Ed25519Bip32DSIGN) where
fromCBOR :: Decoder s (SigDSIGN Ed25519Bip32DSIGN)
fromCBOR = Decoder s (SigDSIGN Ed25519Bip32DSIGN)
forall v s. DSIGNAlgorithm v => Decoder s (SigDSIGN v)
decodeSigDSIGN
xPrvToBytes :: CC.XPrv -> ByteString
xPrvToBytes :: XPrv -> ByteString
xPrvToBytes XPrv
xPrv = ByteString
privateKeyBytes ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
chainCodeBytes
where
privateKeyBytes :: ByteString
privateKeyBytes :: ByteString
privateKeyBytes = Int -> ByteString -> ByteString
BS.take Int
64 (XPrv -> ByteString
CC.unXPrv XPrv
xPrv)
chainCodeBytes :: ByteString
chainCodeBytes :: ByteString
chainCodeBytes = Int -> ByteString -> ByteString
BS.drop Int
96 (XPrv -> ByteString
CC.unXPrv XPrv
xPrv)
xPrvFromBytes :: ByteString -> Maybe CC.XPrv
xPrvFromBytes :: ByteString -> Maybe XPrv
xPrvFromBytes ByteString
bytes
| ByteString -> Int
BS.length ByteString
bytes Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
96 = Maybe XPrv
forall a. Maybe a
Nothing
| Bool
otherwise = do
let (ByteString
prv, ByteString
cc) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt Int
64 ByteString
bytes
ByteString
pub <- ByteString -> Maybe ByteString
ed25519ScalarMult (Int -> ByteString -> ByteString
BS.take Int
32 ByteString
prv)
Either String XPrv -> Maybe XPrv
forall a b. Either a b -> Maybe b
eitherToMaybe (Either String XPrv -> Maybe XPrv)
-> Either String XPrv -> Maybe XPrv
forall a b. (a -> b) -> a -> b
$ ByteString -> Either String XPrv
forall bin. ByteArrayAccess bin => bin -> Either String XPrv
CC.xprv (ByteString -> Either String XPrv)
-> ByteString -> Either String XPrv
forall a b. (a -> b) -> a -> b
$ ByteString
prv ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
pub ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
cc
where
eitherToMaybe :: Either a b -> Maybe b
eitherToMaybe :: Either a b -> Maybe b
eitherToMaybe = (a -> Maybe b) -> (b -> Maybe b) -> Either a b -> Maybe b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe b -> a -> Maybe b
forall a b. a -> b -> a
const Maybe b
forall a. Maybe a
Nothing) b -> Maybe b
forall a. a -> Maybe a
Just
ed25519ScalarMult :: ByteString -> Maybe ByteString
ed25519ScalarMult :: ByteString -> Maybe ByteString
ed25519ScalarMult ByteString
bs = do
Scalar
scalar <- Either CryptoError Scalar -> Maybe Scalar
forall a b. Either a b -> Maybe b
eitherToMaybe (Either CryptoError Scalar -> Maybe Scalar)
-> (CryptoFailable Scalar -> Either CryptoError Scalar)
-> CryptoFailable Scalar
-> Maybe Scalar
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. CryptoFailable Scalar -> Either CryptoError Scalar
forall a. CryptoFailable a -> Either CryptoError a
eitherCryptoError (CryptoFailable Scalar -> Maybe Scalar)
-> CryptoFailable Scalar -> Maybe Scalar
forall a b. (a -> b) -> a -> b
$ ByteString -> CryptoFailable Scalar
forall bs. ByteArrayAccess bs => bs -> CryptoFailable Scalar
Ed25519.scalarDecodeLong ByteString
bs
ByteString -> Maybe ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ByteString -> Maybe ByteString) -> ByteString -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Point -> ByteString
forall bs. ByteArray bs => Point -> bs
Ed25519.pointEncode (Point -> ByteString) -> Point -> ByteString
forall a b. (a -> b) -> a -> b
$ Scalar -> Point
Ed25519.toPoint Scalar
scalar