module Cardano.Crypto.Wallet.Encrypted
( EncryptedKey
, encryptedKey
, unEncryptedKey
, Signature(..)
, encryptedCreate
, encryptedCreateDirectWithTweak
, encryptedChangePass
, encryptedSign
, encryptedPublic
, encryptedChainCode
, encryptedDerivePrivate
, encryptedDerivePublic
) where
import Control.DeepSeq
import Data.Word
import Foreign.C.Types
import Foreign.Ptr
import Crypto.Error
import Data.ByteArray (ByteArrayAccess, withByteArray)
import qualified Data.ByteArray as B
import Data.ByteString (ByteString)
import System.IO.Unsafe
import Cardano.Crypto.Wallet.Types (DerivationScheme(..), DerivationIndex)
totalKeySize :: Int
totalKeySize :: Int
totalKeySize = Int
encryptedKeySize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
publicKeySize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ccSize
encryptedKeySize :: Int
encryptedKeySize :: Int
encryptedKeySize = Int
64
publicKeySize :: Int
publicKeySize :: Int
publicKeySize = Int
32
ccSize :: Int
ccSize :: Int
ccSize = Int
32
signatureSize :: Int
signatureSize :: Int
signatureSize = Int
64
publicKeyOffset :: Int
publicKeyOffset :: Int
publicKeyOffset = Int
encryptedKeySize
ccOffset :: Int
ccOffset :: Int
ccOffset = Int
publicKeyOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
publicKeySize
newtype Signature = Signature ByteString
deriving (Signature -> ()
(Signature -> ()) -> NFData Signature
forall a. (a -> ()) -> NFData a
$crnf :: Signature -> ()
rnf :: Signature -> ()
NFData)
newtype EncryptedKey = EncryptedKey ByteString
deriving (EncryptedKey -> ()
(EncryptedKey -> ()) -> NFData EncryptedKey
forall a. (a -> ()) -> NFData a
$crnf :: EncryptedKey -> ()
rnf :: EncryptedKey -> ()
NFData, EncryptedKey -> Int
(EncryptedKey -> Int)
-> (forall p a. EncryptedKey -> (Ptr p -> IO a) -> IO a)
-> (forall p. EncryptedKey -> Ptr p -> IO ())
-> ByteArrayAccess EncryptedKey
forall p. EncryptedKey -> 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. EncryptedKey -> (Ptr p -> IO a) -> IO a
$clength :: EncryptedKey -> Int
length :: EncryptedKey -> Int
$cwithByteArray :: forall p a. EncryptedKey -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. EncryptedKey -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. EncryptedKey -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. EncryptedKey -> Ptr p -> IO ()
ByteArrayAccess)
type PublicKey = ByteString
type ChainCode = ByteString
data PassPhrase
encryptedKey :: ByteString -> Maybe EncryptedKey
encryptedKey :: PublicKey -> Maybe EncryptedKey
encryptedKey PublicKey
ba
| PublicKey -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length PublicKey
ba Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
totalKeySize = EncryptedKey -> Maybe EncryptedKey
forall a. a -> Maybe a
Just (EncryptedKey -> Maybe EncryptedKey)
-> EncryptedKey -> Maybe EncryptedKey
forall a b. (a -> b) -> a -> b
$ PublicKey -> EncryptedKey
EncryptedKey PublicKey
ba
| Bool
otherwise = Maybe EncryptedKey
forall a. Maybe a
Nothing
unEncryptedKey :: EncryptedKey -> ByteString
unEncryptedKey :: EncryptedKey -> PublicKey
unEncryptedKey (EncryptedKey PublicKey
e) = PublicKey
e
encryptedCreate :: (ByteArrayAccess passphrase, ByteArrayAccess secret, ByteArrayAccess cc)
=> secret
-> passphrase
-> cc
-> CryptoFailable EncryptedKey
encryptedCreate :: forall passphrase secret cc.
(ByteArrayAccess passphrase, ByteArrayAccess secret,
ByteArrayAccess cc) =>
secret -> passphrase -> cc -> CryptoFailable EncryptedKey
encryptedCreate secret
sec passphrase
pass cc
cc
| secret -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length secret
sec Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
32 = CryptoError -> CryptoFailable EncryptedKey
forall a. CryptoError -> CryptoFailable a
CryptoFailed CryptoError
CryptoError_SecretKeySizeInvalid
| Bool
otherwise = IO (CryptoFailable EncryptedKey) -> CryptoFailable EncryptedKey
forall a. IO a -> a
unsafePerformIO (IO (CryptoFailable EncryptedKey) -> CryptoFailable EncryptedKey)
-> IO (CryptoFailable EncryptedKey) -> CryptoFailable EncryptedKey
forall a b. (a -> b) -> a -> b
$ do
(CDerivationScheme
r, PublicKey
k) <- Int
-> (Ptr EncryptedKey -> IO CDerivationScheme)
-> IO (CDerivationScheme, PublicKey)
forall ba p a. ByteArray ba => Int -> (Ptr p -> IO a) -> IO (a, ba)
forall p a. Int -> (Ptr p -> IO a) -> IO (a, PublicKey)
B.allocRet Int
totalKeySize ((Ptr EncryptedKey -> IO CDerivationScheme)
-> IO (CDerivationScheme, PublicKey))
-> (Ptr EncryptedKey -> IO CDerivationScheme)
-> IO (CDerivationScheme, PublicKey)
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
ekey ->
secret
-> (Ptr Word8 -> IO CDerivationScheme) -> IO CDerivationScheme
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. secret -> (Ptr p -> IO a) -> IO a
withByteArray secret
sec ((Ptr Word8 -> IO CDerivationScheme) -> IO CDerivationScheme)
-> (Ptr Word8 -> IO CDerivationScheme) -> IO CDerivationScheme
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
psec ->
passphrase
-> (Ptr PassPhrase -> IO CDerivationScheme) -> IO CDerivationScheme
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. passphrase -> (Ptr p -> IO a) -> IO a
withByteArray passphrase
pass ((Ptr PassPhrase -> IO CDerivationScheme) -> IO CDerivationScheme)
-> (Ptr PassPhrase -> IO CDerivationScheme) -> IO CDerivationScheme
forall a b. (a -> b) -> a -> b
$ \Ptr PassPhrase
ppass ->
cc -> (Ptr Word8 -> IO CDerivationScheme) -> IO CDerivationScheme
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. cc -> (Ptr p -> IO a) -> IO a
withByteArray cc
cc ((Ptr Word8 -> IO CDerivationScheme) -> IO CDerivationScheme)
-> (Ptr Word8 -> IO CDerivationScheme) -> IO CDerivationScheme
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
pcc ->
Ptr PassPhrase
-> DerivationIndex
-> Ptr Word8
-> Ptr Word8
-> Ptr EncryptedKey
-> IO CDerivationScheme
wallet_encrypted_from_secret Ptr PassPhrase
ppass (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ passphrase -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length passphrase
pass) Ptr Word8
psec Ptr Word8
pcc Ptr EncryptedKey
ekey
if CDerivationScheme
r CDerivationScheme -> CDerivationScheme -> Bool
forall a. Eq a => a -> a -> Bool
== CDerivationScheme
0
then CryptoFailable EncryptedKey -> IO (CryptoFailable EncryptedKey)
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (CryptoFailable EncryptedKey -> IO (CryptoFailable EncryptedKey))
-> CryptoFailable EncryptedKey -> IO (CryptoFailable EncryptedKey)
forall a b. (a -> b) -> a -> b
$ EncryptedKey -> CryptoFailable EncryptedKey
forall a. a -> CryptoFailable a
CryptoPassed (EncryptedKey -> CryptoFailable EncryptedKey)
-> EncryptedKey -> CryptoFailable EncryptedKey
forall a b. (a -> b) -> a -> b
$ PublicKey -> EncryptedKey
EncryptedKey PublicKey
k
else CryptoFailable EncryptedKey -> IO (CryptoFailable EncryptedKey)
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (CryptoFailable EncryptedKey -> IO (CryptoFailable EncryptedKey))
-> CryptoFailable EncryptedKey -> IO (CryptoFailable EncryptedKey)
forall a b. (a -> b) -> a -> b
$ CryptoError -> CryptoFailable EncryptedKey
forall a. CryptoError -> CryptoFailable a
CryptoFailed CryptoError
CryptoError_SecretKeyStructureInvalid
encryptedCreateDirectWithTweak :: (ByteArrayAccess passphrase, ByteArrayAccess secret)
=> secret
-> passphrase
-> EncryptedKey
encryptedCreateDirectWithTweak :: forall passphrase secret.
(ByteArrayAccess passphrase, ByteArrayAccess secret) =>
secret -> passphrase -> EncryptedKey
encryptedCreateDirectWithTweak secret
sec passphrase
pass =
PublicKey -> EncryptedKey
EncryptedKey (PublicKey -> EncryptedKey) -> PublicKey -> EncryptedKey
forall a b. (a -> b) -> a -> b
$ Int -> (Ptr EncryptedKey -> IO ()) -> PublicKey
forall a p. ByteArray a => Int -> (Ptr p -> IO ()) -> a
B.allocAndFreeze Int
totalKeySize ((Ptr EncryptedKey -> IO ()) -> PublicKey)
-> (Ptr EncryptedKey -> IO ()) -> PublicKey
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
ekey ->
secret -> (Ptr Word8 -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. secret -> (Ptr p -> IO a) -> IO a
withByteArray secret
sec ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
psec ->
passphrase -> (Ptr PassPhrase -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. passphrase -> (Ptr p -> IO a) -> IO a
withByteArray passphrase
pass ((Ptr PassPhrase -> IO ()) -> IO ())
-> (Ptr PassPhrase -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PassPhrase
ppass ->
Ptr PassPhrase
-> DerivationIndex -> Ptr Word8 -> Ptr EncryptedKey -> IO ()
wallet_encrypted_new_from_mkg Ptr PassPhrase
ppass (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ passphrase -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length passphrase
pass) Ptr Word8
psec Ptr EncryptedKey
ekey
encryptedChangePass :: (ByteArrayAccess oldPassPhrase, ByteArrayAccess newPassPhrase)
=> oldPassPhrase
-> newPassPhrase
-> EncryptedKey
-> EncryptedKey
encryptedChangePass :: forall oldPassPhrase newPassPhrase.
(ByteArrayAccess oldPassPhrase, ByteArrayAccess newPassPhrase) =>
oldPassPhrase -> newPassPhrase -> EncryptedKey -> EncryptedKey
encryptedChangePass oldPassPhrase
oldPass newPassPhrase
newPass (EncryptedKey PublicKey
okey) =
PublicKey -> EncryptedKey
EncryptedKey (PublicKey -> EncryptedKey) -> PublicKey -> EncryptedKey
forall a b. (a -> b) -> a -> b
$ Int -> (Ptr EncryptedKey -> IO ()) -> PublicKey
forall a p. ByteArray a => Int -> (Ptr p -> IO ()) -> a
B.allocAndFreeze Int
totalKeySize ((Ptr EncryptedKey -> IO ()) -> PublicKey)
-> (Ptr EncryptedKey -> IO ()) -> PublicKey
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
ekey ->
oldPassPhrase -> (Ptr PassPhrase -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. oldPassPhrase -> (Ptr p -> IO a) -> IO a
withByteArray oldPassPhrase
oldPass ((Ptr PassPhrase -> IO ()) -> IO ())
-> (Ptr PassPhrase -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PassPhrase
opass ->
newPassPhrase -> (Ptr PassPhrase -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. newPassPhrase -> (Ptr p -> IO a) -> IO a
withByteArray newPassPhrase
newPass ((Ptr PassPhrase -> IO ()) -> IO ())
-> (Ptr PassPhrase -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PassPhrase
npass ->
PublicKey -> (Ptr EncryptedKey -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. PublicKey -> (Ptr p -> IO a) -> IO a
withByteArray PublicKey
okey ((Ptr EncryptedKey -> IO ()) -> IO ())
-> (Ptr EncryptedKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
oldkey ->
Ptr EncryptedKey
-> Ptr PassPhrase
-> DerivationIndex
-> Ptr PassPhrase
-> DerivationIndex
-> Ptr EncryptedKey
-> IO ()
wallet_encrypted_change_pass Ptr EncryptedKey
oldkey
Ptr PassPhrase
opass (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ oldPassPhrase -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length oldPassPhrase
oldPass)
Ptr PassPhrase
npass (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ newPassPhrase -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length newPassPhrase
newPass)
Ptr EncryptedKey
ekey
encryptedSign :: (ByteArrayAccess passphrase, ByteArrayAccess msg)
=> EncryptedKey
-> passphrase
-> msg
-> Signature
encryptedSign :: forall passphrase msg.
(ByteArrayAccess passphrase, ByteArrayAccess msg) =>
EncryptedKey -> passphrase -> msg -> Signature
encryptedSign (EncryptedKey PublicKey
ekey) passphrase
pass msg
msg =
PublicKey -> Signature
Signature (PublicKey -> Signature) -> PublicKey -> Signature
forall a b. (a -> b) -> a -> b
$ Int -> (Ptr Signature -> IO ()) -> PublicKey
forall a p. ByteArray a => Int -> (Ptr p -> IO ()) -> a
B.allocAndFreeze Int
signatureSize ((Ptr Signature -> IO ()) -> PublicKey)
-> (Ptr Signature -> IO ()) -> PublicKey
forall a b. (a -> b) -> a -> b
$ \Ptr Signature
sig ->
PublicKey -> (Ptr EncryptedKey -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. PublicKey -> (Ptr p -> IO a) -> IO a
withByteArray PublicKey
ekey ((Ptr EncryptedKey -> IO ()) -> IO ())
-> (Ptr EncryptedKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
k ->
passphrase -> (Ptr PassPhrase -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. passphrase -> (Ptr p -> IO a) -> IO a
withByteArray passphrase
pass ((Ptr PassPhrase -> IO ()) -> IO ())
-> (Ptr PassPhrase -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PassPhrase
p ->
msg -> (Ptr Word8 -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. msg -> (Ptr p -> IO a) -> IO a
withByteArray msg
msg ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
m ->
Ptr EncryptedKey
-> Ptr PassPhrase
-> DerivationIndex
-> Ptr Word8
-> DerivationIndex
-> Ptr Signature
-> IO ()
wallet_encrypted_sign Ptr EncryptedKey
k Ptr PassPhrase
p (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ passphrase -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length passphrase
pass) Ptr Word8
m (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ msg -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length msg
msg) Ptr Signature
sig
encryptedDerivePrivate :: (ByteArrayAccess passphrase)
=> DerivationScheme
-> EncryptedKey
-> passphrase
-> DerivationIndex
-> EncryptedKey
encryptedDerivePrivate :: forall passphrase.
ByteArrayAccess passphrase =>
DerivationScheme
-> EncryptedKey -> passphrase -> DerivationIndex -> EncryptedKey
encryptedDerivePrivate DerivationScheme
dscheme (EncryptedKey PublicKey
parent) passphrase
pass DerivationIndex
childIndex =
PublicKey -> EncryptedKey
EncryptedKey (PublicKey -> EncryptedKey) -> PublicKey -> EncryptedKey
forall a b. (a -> b) -> a -> b
$ Int -> (Ptr EncryptedKey -> IO ()) -> PublicKey
forall a p. ByteArray a => Int -> (Ptr p -> IO ()) -> a
B.allocAndFreeze Int
totalKeySize ((Ptr EncryptedKey -> IO ()) -> PublicKey)
-> (Ptr EncryptedKey -> IO ()) -> PublicKey
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
ekey ->
passphrase -> (Ptr PassPhrase -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. passphrase -> (Ptr p -> IO a) -> IO a
withByteArray passphrase
pass ((Ptr PassPhrase -> IO ()) -> IO ())
-> (Ptr PassPhrase -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PassPhrase
ppass ->
PublicKey -> (Ptr EncryptedKey -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. PublicKey -> (Ptr p -> IO a) -> IO a
withByteArray PublicKey
parent ((Ptr EncryptedKey -> IO ()) -> IO ())
-> (Ptr EncryptedKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EncryptedKey
pparent ->
Ptr EncryptedKey
-> Ptr PassPhrase
-> DerivationIndex
-> DerivationIndex
-> Ptr EncryptedKey
-> CDerivationScheme
-> IO ()
wallet_encrypted_derive_private Ptr EncryptedKey
pparent Ptr PassPhrase
ppass (Int -> DerivationIndex
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> DerivationIndex) -> Int -> DerivationIndex
forall a b. (a -> b) -> a -> b
$ passphrase -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length passphrase
pass) DerivationIndex
childIndex Ptr EncryptedKey
ekey (DerivationScheme -> CDerivationScheme
dschemeToC DerivationScheme
dscheme)
encryptedDerivePublic :: DerivationScheme
-> (PublicKey, ChainCode)
-> DerivationIndex
-> (PublicKey, ChainCode)
encryptedDerivePublic :: DerivationScheme
-> (PublicKey, PublicKey)
-> DerivationIndex
-> (PublicKey, PublicKey)
encryptedDerivePublic DerivationScheme
dscheme (PublicKey
pub, PublicKey
cc) DerivationIndex
childIndex
| DerivationIndex
childIndex DerivationIndex -> DerivationIndex -> Bool
forall a. Ord a => a -> a -> Bool
>= DerivationIndex
0x80000000 = [Char] -> (PublicKey, PublicKey)
forall a. HasCallStack => [Char] -> a
error [Char]
"cannot derive hardened in derive public"
| Bool
otherwise = IO (PublicKey, PublicKey) -> (PublicKey, PublicKey)
forall a. IO a -> a
unsafePerformIO (IO (PublicKey, PublicKey) -> (PublicKey, PublicKey))
-> IO (PublicKey, PublicKey) -> (PublicKey, PublicKey)
forall a b. (a -> b) -> a -> b
$ do
(PublicKey
newCC, PublicKey
newPub) <-
Int -> (Ptr PublicKey -> IO PublicKey) -> IO (PublicKey, PublicKey)
forall ba p a. ByteArray ba => Int -> (Ptr p -> IO a) -> IO (a, ba)
forall p a. Int -> (Ptr p -> IO a) -> IO (a, PublicKey)
B.allocRet Int
publicKeySize ((Ptr PublicKey -> IO PublicKey) -> IO (PublicKey, PublicKey))
-> (Ptr PublicKey -> IO PublicKey) -> IO (PublicKey, PublicKey)
forall a b. (a -> b) -> a -> b
$ \Ptr PublicKey
outPub ->
Int -> (Ptr PublicKey -> IO ()) -> IO PublicKey
forall ba p. ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba
B.alloc Int
ccSize ((Ptr PublicKey -> IO ()) -> IO PublicKey)
-> (Ptr PublicKey -> IO ()) -> IO PublicKey
forall a b. (a -> b) -> a -> b
$ \Ptr PublicKey
outCc ->
PublicKey -> (Ptr PublicKey -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. PublicKey -> (Ptr p -> IO a) -> IO a
withByteArray PublicKey
pub ((Ptr PublicKey -> IO ()) -> IO ())
-> (Ptr PublicKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PublicKey
ppub ->
PublicKey -> (Ptr PublicKey -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. PublicKey -> (Ptr p -> IO a) -> IO a
withByteArray PublicKey
cc ((Ptr PublicKey -> IO ()) -> IO ())
-> (Ptr PublicKey -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PublicKey
pcc -> do
CDerivationScheme
r <- Ptr PublicKey
-> Ptr PublicKey
-> DerivationIndex
-> Ptr PublicKey
-> Ptr PublicKey
-> CDerivationScheme
-> IO CDerivationScheme
wallet_encrypted_derive_public Ptr PublicKey
ppub Ptr PublicKey
pcc DerivationIndex
childIndex Ptr PublicKey
outPub Ptr PublicKey
outCc (DerivationScheme -> CDerivationScheme
dschemeToC DerivationScheme
dscheme)
if CDerivationScheme
r CDerivationScheme -> CDerivationScheme -> Bool
forall a. Eq a => a -> a -> Bool
/= CDerivationScheme
0 then [Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"encrypted derive public assumption about index failed" else () -> IO ()
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return ()
(PublicKey, PublicKey) -> IO (PublicKey, PublicKey)
forall a. a -> IO a
forall (m :: Type -> Type) a. Monad m => a -> m a
return (PublicKey
newPub, PublicKey
newCC)
encryptedPublic :: EncryptedKey -> ByteString
encryptedPublic :: EncryptedKey -> PublicKey
encryptedPublic (EncryptedKey PublicKey
ekey) = Int -> Int -> PublicKey -> PublicKey
forall c. ByteArray c => Int -> Int -> c -> c
sub Int
publicKeyOffset Int
publicKeySize PublicKey
ekey
encryptedChainCode :: EncryptedKey -> ByteString
encryptedChainCode :: EncryptedKey -> PublicKey
encryptedChainCode (EncryptedKey PublicKey
ekey) = Int -> Int -> PublicKey -> PublicKey
forall c. ByteArray c => Int -> Int -> c -> c
sub Int
ccOffset Int
ccSize PublicKey
ekey
sub :: B.ByteArray c => Int -> Int -> c -> c
sub :: forall c. ByteArray c => Int -> Int -> c -> c
sub Int
ofs Int
sz = Int -> c -> c
forall bs. ByteArray bs => Int -> bs -> bs
B.take Int
sz (c -> c) -> (c -> c) -> c -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> c -> c
forall bs. ByteArray bs => Int -> bs -> bs
B.drop Int
ofs
type CDerivationScheme = CInt
dschemeToC :: DerivationScheme -> CDerivationScheme
dschemeToC :: DerivationScheme -> CDerivationScheme
dschemeToC DerivationScheme
DerivationScheme1 = CDerivationScheme
1
dschemeToC DerivationScheme
DerivationScheme2 = CDerivationScheme
2
foreign import ccall "wallet_encrypted_from_secret"
wallet_encrypted_from_secret :: Ptr PassPhrase -> Word32
-> Ptr Word8
-> Ptr Word8
-> Ptr EncryptedKey
-> IO CInt
foreign import ccall "wallet_encrypted_new_from_mkg"
wallet_encrypted_new_from_mkg :: Ptr PassPhrase -> Word32
-> Ptr Word8
-> Ptr EncryptedKey
-> IO ()
foreign import ccall "wallet_encrypted_sign"
wallet_encrypted_sign :: Ptr EncryptedKey
-> Ptr PassPhrase -> Word32
-> Ptr Word8 -> Word32
-> Ptr Signature
-> IO ()
foreign import ccall "wallet_encrypted_derive_private"
wallet_encrypted_derive_private :: Ptr EncryptedKey
-> Ptr PassPhrase -> Word32
-> DerivationIndex
-> Ptr EncryptedKey
-> CDerivationScheme
-> IO ()
foreign import ccall "wallet_encrypted_derive_public"
wallet_encrypted_derive_public :: Ptr PublicKey
-> Ptr ChainCode
-> DerivationIndex
-> Ptr PublicKey
-> Ptr ChainCode
-> CDerivationScheme
-> IO CInt
foreign import ccall "wallet_encrypted_change_pass"
wallet_encrypted_change_pass :: Ptr EncryptedKey
-> Ptr PassPhrase -> Word32
-> Ptr PassPhrase -> Word32
-> Ptr EncryptedKey
-> IO ()