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