{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_HADDOCK prune #-}
module Cardano.Address.Style.Byron
(
Byron
, DerivationPath
, payloadPassphrase
, derivationPath
, getKey
, genMasterKeyFromXPrv
, genMasterKeyFromMnemonic
, deriveAccountPrivateKey
, deriveAddressPrivateKey
, AddressInfo (..)
, eitherInspectAddress
, inspectAddress
, inspectByronAddress
, paymentAddress
, ErrInspectAddress (..)
, prettyErrInspectAddress
, byronMainnet
, byronStaging
, byronTestnet
, byronPreprod
, byronPreview
, liftXPrv
, liftXPub
, minSeedLengthBytes
) where
import Prelude
import Cardano.Address
( Address
, AddressDiscrimination (..)
, HasNetworkDiscriminant (..)
, NetworkTag (..)
, unAddress
, unsafeMkAddress
)
import Cardano.Address.Derivation
( Depth (..)
, DerivationScheme (DerivationScheme1)
, DerivationType (..)
, Index (..)
, XPrv
, XPub
, deriveXPrv
, generate
, toXPub
, xpubToBytes
)
import Cardano.Address.Internal
( DeserialiseFailure, WithErrorMessage (..) )
import Cardano.Mnemonic
( SomeMnemonic (..), entropyToBytes, mnemonicToEntropy )
import Codec.Binary.Encoding
( AbstractEncoding (..), encode )
import Control.DeepSeq
( NFData )
import Control.Exception
( Exception, displayException )
import Control.Exception.Base
( assert )
import Control.Monad.Catch
( MonadThrow, throwM )
import Crypto.Hash
( hash )
import Crypto.Hash.Algorithms
( Blake2b_256, SHA512 (..) )
import Data.Aeson
( ToJSON (..), (.=) )
import Data.Bifunctor
( bimap, first )
import Data.ByteArray
( ScrubbedBytes )
import Data.ByteString
( ByteString )
import Data.Kind
( Type )
import Data.List
( find )
import Data.Word
( Word32, Word8 )
import GHC.Generics
( Generic )
import qualified Cardano.Address as Internal
import qualified Cardano.Address.Derivation as Internal
import qualified Cardano.Codec.Cbor as CBOR
import qualified Codec.CBOR.Decoding as CBOR
import qualified Crypto.KDF.PBKDF2 as PBKDF2
import qualified Data.Aeson as Json
import qualified Data.ByteArray as BA
import qualified Data.Text.Encoding as T
data Byron (depth :: Depth) key = Byron
{ forall (depth :: Depth) key. Byron depth key -> key
getKey :: key
, forall (depth :: Depth) key.
Byron depth key -> DerivationPath depth
derivationPath :: DerivationPath depth
, forall (depth :: Depth) key. Byron depth key -> ScrubbedBytes
payloadPassphrase :: ScrubbedBytes
} deriving stock ((forall x. Byron depth key -> Rep (Byron depth key) x)
-> (forall x. Rep (Byron depth key) x -> Byron depth key)
-> Generic (Byron depth key)
forall x. Rep (Byron depth key) x -> Byron depth key
forall x. Byron depth key -> Rep (Byron depth key) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (depth :: Depth) key x.
Rep (Byron depth key) x -> Byron depth key
forall (depth :: Depth) key x.
Byron depth key -> Rep (Byron depth key) x
$cfrom :: forall (depth :: Depth) key x.
Byron depth key -> Rep (Byron depth key) x
from :: forall x. Byron depth key -> Rep (Byron depth key) x
$cto :: forall (depth :: Depth) key x.
Rep (Byron depth key) x -> Byron depth key
to :: forall x. Rep (Byron depth key) x -> Byron depth key
Generic)
{-# DEPRECATED Byron "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
{-# DEPRECATED getKey "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
{-# DEPRECATED derivationPath "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
{-# DEPRECATED payloadPassphrase "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
instance (NFData key, NFData (DerivationPath depth)) => NFData (Byron depth key)
deriving instance (Show key, Show (DerivationPath depth)) => Show (Byron depth key)
deriving instance (Eq key, Eq (DerivationPath depth)) => Eq (Byron depth key)
deriving instance (Functor (Byron depth))
type family DerivationPath (depth :: Depth) :: Type where
DerivationPath 'RootK =
()
DerivationPath 'AccountK =
Index 'WholeDomain 'AccountK
DerivationPath 'PaymentK =
(Index 'WholeDomain 'AccountK, Index 'WholeDomain 'PaymentK)
{-# DEPRECATED DerivationPath "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
instance Internal.GenMasterKey Byron where
type SecondFactor Byron = ()
genMasterKeyFromXPrv :: XPrv -> Byron 'RootK XPrv
genMasterKeyFromXPrv XPrv
xprv =
XPub -> DerivationPath 'RootK -> XPrv -> Byron 'RootK XPrv
forall (depth :: Depth).
XPub -> DerivationPath depth -> XPrv -> Byron depth XPrv
liftXPrv (HasCallStack => XPrv -> XPub
XPrv -> XPub
toXPub XPrv
xprv) () XPrv
xprv
genMasterKeyFromMnemonic :: SomeMnemonic -> SecondFactor Byron -> Byron 'RootK XPrv
genMasterKeyFromMnemonic (SomeMnemonic Mnemonic mw
mw) () =
XPub -> DerivationPath 'RootK -> XPrv -> Byron 'RootK XPrv
forall (depth :: Depth).
XPub -> DerivationPath depth -> XPrv -> Byron depth XPrv
liftXPrv (HasCallStack => XPrv -> XPub
XPrv -> XPub
toXPub XPrv
xprv) () XPrv
xprv
where
xprv :: XPrv
xprv = ScrubbedBytes -> XPrv
forall seed. ByteArrayAccess seed => seed -> XPrv
generate (ScrubbedBytes -> ScrubbedBytes
hashSeed ScrubbedBytes
seedValidated)
seed :: ScrubbedBytes
seed = Entropy (EntropySize mw) -> ScrubbedBytes
forall (n :: Nat). Entropy n -> ScrubbedBytes
entropyToBytes (Entropy (EntropySize mw) -> ScrubbedBytes)
-> Entropy (EntropySize mw) -> ScrubbedBytes
forall a b. (a -> b) -> a -> b
$ Mnemonic mw -> Entropy (EntropySize mw)
forall (mw :: Nat). Mnemonic mw -> Entropy (EntropySize mw)
mnemonicToEntropy Mnemonic mw
mw
seedValidated :: ScrubbedBytes
seedValidated = Bool -> ScrubbedBytes -> ScrubbedBytes
forall a. HasCallStack => Bool -> a -> a
assert
(ScrubbedBytes -> Int
forall ba. ByteArrayAccess ba => ba -> Int
BA.length ScrubbedBytes
seed Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
minSeedLengthBytes Bool -> Bool -> Bool
&& ScrubbedBytes -> Int
forall ba. ByteArrayAccess ba => ba -> Int
BA.length ScrubbedBytes
seed Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
255)
ScrubbedBytes
seed
instance Internal.HardDerivation Byron where
type AddressIndexDerivationType Byron = 'WholeDomain
type AccountIndexDerivationType Byron = 'WholeDomain
type WithRole Byron = ()
deriveAccountPrivateKey :: Byron 'RootK XPrv
-> Index (AccountIndexDerivationType Byron) 'AccountK
-> Byron 'AccountK XPrv
deriveAccountPrivateKey Byron 'RootK XPrv
rootXPrv Index (AccountIndexDerivationType Byron) 'AccountK
accIx = Byron
{ $sel:getKey:Byron :: XPrv
getKey = DerivationScheme -> XPrv -> Index 'WholeDomain 'AccountK -> XPrv
forall (derivationType :: DerivationType) (depth :: Depth).
DerivationScheme -> XPrv -> Index derivationType depth -> XPrv
deriveXPrv DerivationScheme
DerivationScheme1 (Byron 'RootK XPrv -> XPrv
forall (depth :: Depth) key. Byron depth key -> key
getKey Byron 'RootK XPrv
rootXPrv) Index (AccountIndexDerivationType Byron) 'AccountK
Index 'WholeDomain 'AccountK
accIx
, $sel:derivationPath:Byron :: DerivationPath 'AccountK
derivationPath = Index (AccountIndexDerivationType Byron) 'AccountK
DerivationPath 'AccountK
accIx
, $sel:payloadPassphrase:Byron :: ScrubbedBytes
payloadPassphrase = Byron 'RootK XPrv -> ScrubbedBytes
forall (depth :: Depth) key. Byron depth key -> ScrubbedBytes
payloadPassphrase Byron 'RootK XPrv
rootXPrv
}
deriveAddressPrivateKey :: Byron 'AccountK XPrv
-> WithRole Byron
-> Index (AddressIndexDerivationType Byron) 'PaymentK
-> Byron 'PaymentK XPrv
deriveAddressPrivateKey Byron 'AccountK XPrv
accXPrv () Index (AddressIndexDerivationType Byron) 'PaymentK
addrIx = Byron
{ $sel:getKey:Byron :: XPrv
getKey = DerivationScheme -> XPrv -> Index 'WholeDomain 'PaymentK -> XPrv
forall (derivationType :: DerivationType) (depth :: Depth).
DerivationScheme -> XPrv -> Index derivationType depth -> XPrv
deriveXPrv DerivationScheme
DerivationScheme1 (Byron 'AccountK XPrv -> XPrv
forall (depth :: Depth) key. Byron depth key -> key
getKey Byron 'AccountK XPrv
accXPrv) Index (AddressIndexDerivationType Byron) 'PaymentK
Index 'WholeDomain 'PaymentK
addrIx
, $sel:derivationPath:Byron :: DerivationPath 'PaymentK
derivationPath = (Byron 'AccountK XPrv -> DerivationPath 'AccountK
forall (depth :: Depth) key.
Byron depth key -> DerivationPath depth
derivationPath Byron 'AccountK XPrv
accXPrv, Index (AddressIndexDerivationType Byron) 'PaymentK
Index 'WholeDomain 'PaymentK
addrIx)
, $sel:payloadPassphrase:Byron :: ScrubbedBytes
payloadPassphrase = Byron 'AccountK XPrv -> ScrubbedBytes
forall (depth :: Depth) key. Byron depth key -> ScrubbedBytes
payloadPassphrase Byron 'AccountK XPrv
accXPrv
}
genMasterKeyFromMnemonic
:: SomeMnemonic
-> Byron 'RootK XPrv
genMasterKeyFromMnemonic :: SomeMnemonic -> Byron 'RootK XPrv
genMasterKeyFromMnemonic =
(SomeMnemonic -> () -> Byron 'RootK XPrv)
-> () -> SomeMnemonic -> Byron 'RootK XPrv
forall a b c. (a -> b -> c) -> b -> a -> c
flip SomeMnemonic -> () -> Byron 'RootK XPrv
SomeMnemonic -> SecondFactor Byron -> Byron 'RootK XPrv
forall (key :: Depth -> * -> *).
GenMasterKey key =>
SomeMnemonic -> SecondFactor key -> key 'RootK XPrv
Internal.genMasterKeyFromMnemonic ()
{-# DEPRECATED genMasterKeyFromMnemonic "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
genMasterKeyFromXPrv
:: XPrv
-> Byron 'RootK XPrv
genMasterKeyFromXPrv :: XPrv -> Byron 'RootK XPrv
genMasterKeyFromXPrv =
XPrv -> Byron 'RootK XPrv
forall (key :: Depth -> * -> *).
GenMasterKey key =>
XPrv -> key 'RootK XPrv
Internal.genMasterKeyFromXPrv
{-# DEPRECATED genMasterKeyFromXPrv "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
deriveAccountPrivateKey
:: Byron 'RootK XPrv
-> Index 'WholeDomain 'AccountK
-> Byron 'AccountK XPrv
deriveAccountPrivateKey :: Byron 'RootK XPrv
-> Index 'WholeDomain 'AccountK -> Byron 'AccountK XPrv
deriveAccountPrivateKey =
Byron 'RootK XPrv
-> Index (AccountIndexDerivationType Byron) 'AccountK
-> Byron 'AccountK XPrv
Byron 'RootK XPrv
-> Index 'WholeDomain 'AccountK -> Byron 'AccountK XPrv
forall (key :: Depth -> * -> *).
HardDerivation key =>
key 'RootK XPrv
-> Index (AccountIndexDerivationType key) 'AccountK
-> key 'AccountK XPrv
Internal.deriveAccountPrivateKey
{-# DEPRECATED deriveAccountPrivateKey "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
deriveAddressPrivateKey
:: Byron 'AccountK XPrv
-> Index 'WholeDomain 'PaymentK
-> Byron 'PaymentK XPrv
deriveAddressPrivateKey :: Byron 'AccountK XPrv
-> Index 'WholeDomain 'PaymentK -> Byron 'PaymentK XPrv
deriveAddressPrivateKey Byron 'AccountK XPrv
acctK =
Byron 'AccountK XPrv
-> WithRole Byron
-> Index (AddressIndexDerivationType Byron) 'PaymentK
-> Byron 'PaymentK XPrv
forall (key :: Depth -> * -> *).
HardDerivation key =>
key 'AccountK XPrv
-> WithRole key
-> Index (AddressIndexDerivationType key) 'PaymentK
-> key 'PaymentK XPrv
Internal.deriveAddressPrivateKey Byron 'AccountK XPrv
acctK ()
{-# DEPRECATED deriveAddressPrivateKey "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
data ErrInspectAddress
= MissingExpectedDerivationPath
| DeserialiseError DeserialiseFailure
| FailedToDecryptPath
deriving ((forall x. ErrInspectAddress -> Rep ErrInspectAddress x)
-> (forall x. Rep ErrInspectAddress x -> ErrInspectAddress)
-> Generic ErrInspectAddress
forall x. Rep ErrInspectAddress x -> ErrInspectAddress
forall x. ErrInspectAddress -> Rep ErrInspectAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ErrInspectAddress -> Rep ErrInspectAddress x
from :: forall x. ErrInspectAddress -> Rep ErrInspectAddress x
$cto :: forall x. Rep ErrInspectAddress x -> ErrInspectAddress
to :: forall x. Rep ErrInspectAddress x -> ErrInspectAddress
Generic, Int -> ErrInspectAddress -> ShowS
[ErrInspectAddress] -> ShowS
ErrInspectAddress -> String
(Int -> ErrInspectAddress -> ShowS)
-> (ErrInspectAddress -> String)
-> ([ErrInspectAddress] -> ShowS)
-> Show ErrInspectAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ErrInspectAddress -> ShowS
showsPrec :: Int -> ErrInspectAddress -> ShowS
$cshow :: ErrInspectAddress -> String
show :: ErrInspectAddress -> String
$cshowList :: [ErrInspectAddress] -> ShowS
showList :: [ErrInspectAddress] -> ShowS
Show, ErrInspectAddress -> ErrInspectAddress -> Bool
(ErrInspectAddress -> ErrInspectAddress -> Bool)
-> (ErrInspectAddress -> ErrInspectAddress -> Bool)
-> Eq ErrInspectAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ErrInspectAddress -> ErrInspectAddress -> Bool
== :: ErrInspectAddress -> ErrInspectAddress -> Bool
$c/= :: ErrInspectAddress -> ErrInspectAddress -> Bool
/= :: ErrInspectAddress -> ErrInspectAddress -> Bool
Eq)
deriving [ErrInspectAddress] -> Value
[ErrInspectAddress] -> Encoding
ErrInspectAddress -> Bool
ErrInspectAddress -> Value
ErrInspectAddress -> Encoding
(ErrInspectAddress -> Value)
-> (ErrInspectAddress -> Encoding)
-> ([ErrInspectAddress] -> Value)
-> ([ErrInspectAddress] -> Encoding)
-> (ErrInspectAddress -> Bool)
-> ToJSON ErrInspectAddress
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ErrInspectAddress -> Value
toJSON :: ErrInspectAddress -> Value
$ctoEncoding :: ErrInspectAddress -> Encoding
toEncoding :: ErrInspectAddress -> Encoding
$ctoJSONList :: [ErrInspectAddress] -> Value
toJSONList :: [ErrInspectAddress] -> Value
$ctoEncodingList :: [ErrInspectAddress] -> Encoding
toEncodingList :: [ErrInspectAddress] -> Encoding
$comitField :: ErrInspectAddress -> Bool
omitField :: ErrInspectAddress -> Bool
ToJSON via WithErrorMessage ErrInspectAddress
instance Exception ErrInspectAddress where
displayException :: ErrInspectAddress -> String
displayException = ErrInspectAddress -> String
prettyErrInspectAddress
prettyErrInspectAddress :: ErrInspectAddress -> String
prettyErrInspectAddress :: ErrInspectAddress -> String
prettyErrInspectAddress = \case
ErrInspectAddress
MissingExpectedDerivationPath ->
String
"Missing expected derivation path"
DeserialiseError DeserialiseFailure
e ->
DeserialiseFailure -> String
forall e. Exception e => e -> String
displayException DeserialiseFailure
e
ErrInspectAddress
FailedToDecryptPath ->
String
"Failed to decrypt derivation path"
inspectByronAddress :: forall m. MonadThrow m => Maybe XPub -> Address -> m Json.Value
inspectByronAddress :: forall (m :: * -> *).
MonadThrow m =>
Maybe XPub -> Address -> m Value
inspectByronAddress = Maybe XPub -> Address -> m Value
forall (m :: * -> *).
MonadThrow m =>
Maybe XPub -> Address -> m Value
inspectAddress
{-# DEPRECATED inspectByronAddress "use qualified 'inspectAddress' instead." #-}
inspectAddress :: forall m. MonadThrow m => Maybe XPub -> Address -> m Json.Value
inspectAddress :: forall (m :: * -> *).
MonadThrow m =>
Maybe XPub -> Address -> m Value
inspectAddress Maybe XPub
mRootPub Address
addr = (ErrInspectAddress -> m Value)
-> (AddressInfo -> m Value)
-> Either ErrInspectAddress AddressInfo
-> m Value
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ErrInspectAddress -> m Value
forall e a. (HasCallStack, Exception e) => e -> m a
forall (m :: * -> *) e a.
(MonadThrow m, HasCallStack, Exception e) =>
e -> m a
throwM (Value -> m Value
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value -> m Value)
-> (AddressInfo -> Value) -> AddressInfo -> m Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AddressInfo -> Value
forall a. ToJSON a => a -> Value
toJSON) (Either ErrInspectAddress AddressInfo -> m Value)
-> Either ErrInspectAddress AddressInfo -> m Value
forall a b. (a -> b) -> a -> b
$
Maybe XPub -> Address -> Either ErrInspectAddress AddressInfo
eitherInspectAddress Maybe XPub
mRootPub Address
addr
eitherInspectAddress :: Maybe XPub -> Address -> Either ErrInspectAddress AddressInfo
eitherInspectAddress :: Maybe XPub -> Address -> Either ErrInspectAddress AddressInfo
eitherInspectAddress Maybe XPub
mRootPub Address
addr = do
ByteString
payload <- (DeserialiseFailure -> ErrInspectAddress)
-> Either DeserialiseFailure ByteString
-> Either ErrInspectAddress ByteString
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first DeserialiseFailure -> ErrInspectAddress
DeserialiseError (Either DeserialiseFailure ByteString
-> Either ErrInspectAddress ByteString)
-> Either DeserialiseFailure ByteString
-> Either ErrInspectAddress ByteString
forall a b. (a -> b) -> a -> b
$
(forall s. Decoder s ByteString)
-> ByteString -> Either DeserialiseFailure ByteString
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure a
CBOR.deserialiseCbor Decoder s ByteString
forall s. Decoder s ByteString
CBOR.decodeAddressPayload ByteString
bytes
(ByteString
root, [(Word8, ByteString)]
attrs) <- (DeserialiseFailure -> ErrInspectAddress)
-> Either DeserialiseFailure (ByteString, [(Word8, ByteString)])
-> Either ErrInspectAddress (ByteString, [(Word8, ByteString)])
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first DeserialiseFailure -> ErrInspectAddress
DeserialiseError (Either DeserialiseFailure (ByteString, [(Word8, ByteString)])
-> Either ErrInspectAddress (ByteString, [(Word8, ByteString)]))
-> Either DeserialiseFailure (ByteString, [(Word8, ByteString)])
-> Either ErrInspectAddress (ByteString, [(Word8, ByteString)])
forall a b. (a -> b) -> a -> b
$
(forall s. Decoder s (ByteString, [(Word8, ByteString)]))
-> ByteString
-> Either DeserialiseFailure (ByteString, [(Word8, ByteString)])
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure a
CBOR.deserialiseCbor Decoder s (ByteString, [(Word8, ByteString)])
forall s. Decoder s (ByteString, [(Word8, ByteString)])
decodePayload ByteString
payload
PayloadInfo
path <- do
(Word8, ByteString)
attr <- Either ErrInspectAddress (Word8, ByteString)
-> ((Word8, ByteString)
-> Either ErrInspectAddress (Word8, ByteString))
-> Maybe (Word8, ByteString)
-> Either ErrInspectAddress (Word8, ByteString)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (ErrInspectAddress -> Either ErrInspectAddress (Word8, ByteString)
forall a b. a -> Either a b
Left ErrInspectAddress
MissingExpectedDerivationPath) (Word8, ByteString) -> Either ErrInspectAddress (Word8, ByteString)
forall a b. b -> Either a b
Right (Maybe (Word8, ByteString)
-> Either ErrInspectAddress (Word8, ByteString))
-> Maybe (Word8, ByteString)
-> Either ErrInspectAddress (Word8, ByteString)
forall a b. (a -> b) -> a -> b
$
((Word8, ByteString) -> Bool)
-> [(Word8, ByteString)] -> Maybe (Word8, ByteString)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
1) (Word8 -> Bool)
-> ((Word8, ByteString) -> Word8) -> (Word8, ByteString) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8, ByteString) -> Word8
forall a b. (a, b) -> a
fst) [(Word8, ByteString)]
attrs
case Maybe XPub
mRootPub of
Maybe XPub
Nothing -> PayloadInfo -> Either ErrInspectAddress PayloadInfo
forall a b. b -> Either a b
Right (PayloadInfo -> Either ErrInspectAddress PayloadInfo)
-> PayloadInfo -> Either ErrInspectAddress PayloadInfo
forall a b. (a -> b) -> a -> b
$ ByteString -> PayloadInfo
EncryptedDerivationPath (ByteString -> PayloadInfo) -> ByteString -> PayloadInfo
forall a b. (a -> b) -> a -> b
$ (Word8, ByteString) -> ByteString
forall a b. (a, b) -> b
snd (Word8, ByteString)
attr
Just XPub
rootPub -> (Word8, ByteString) -> XPub -> Either ErrInspectAddress PayloadInfo
decryptPath (Word8, ByteString)
attr XPub
rootPub
Maybe NetworkTag
ntwrk <- (DeserialiseFailure -> ErrInspectAddress)
-> (Maybe Word32 -> Maybe NetworkTag)
-> Either DeserialiseFailure (Maybe Word32)
-> Either ErrInspectAddress (Maybe NetworkTag)
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap DeserialiseFailure -> ErrInspectAddress
DeserialiseError ((Word32 -> NetworkTag) -> Maybe Word32 -> Maybe NetworkTag
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> NetworkTag
NetworkTag) (Either DeserialiseFailure (Maybe Word32)
-> Either ErrInspectAddress (Maybe NetworkTag))
-> Either DeserialiseFailure (Maybe Word32)
-> Either ErrInspectAddress (Maybe NetworkTag)
forall a b. (a -> b) -> a -> b
$
(forall s. Decoder s (Maybe Word32))
-> ByteString -> Either DeserialiseFailure (Maybe Word32)
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure a
CBOR.deserialiseCbor Decoder s (Maybe Word32)
forall s. Decoder s (Maybe Word32)
CBOR.decodeProtocolMagicAttr ByteString
payload
AddressInfo -> Either ErrInspectAddress AddressInfo
forall a. a -> Either ErrInspectAddress a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AddressInfo
{ $sel:infoAddressRoot:AddressInfo :: ByteString
infoAddressRoot = ByteString
root
, $sel:infoPayload:AddressInfo :: PayloadInfo
infoPayload = PayloadInfo
path
, $sel:infoNetworkTag:AddressInfo :: Maybe NetworkTag
infoNetworkTag = Maybe NetworkTag
ntwrk
}
where
bytes :: ByteString
bytes :: ByteString
bytes = Address -> ByteString
unAddress Address
addr
decodePayload :: forall s. CBOR.Decoder s (ByteString, [(Word8, ByteString)])
decodePayload :: forall s. Decoder s (ByteString, [(Word8, ByteString)])
decodePayload = do
()
_ <- Int -> Decoder s ()
forall s. Int -> Decoder s ()
CBOR.decodeListLenCanonicalOf Int
3
ByteString
root <- Decoder s ByteString
forall s. Decoder s ByteString
CBOR.decodeBytes
(ByteString
root,) ([(Word8, ByteString)] -> (ByteString, [(Word8, ByteString)]))
-> Decoder s [(Word8, ByteString)]
-> Decoder s (ByteString, [(Word8, ByteString)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s [(Word8, ByteString)]
forall s. Decoder s [(Word8, ByteString)]
CBOR.decodeAllAttributes
decryptPath :: (Word8, ByteString) -> XPub -> Either ErrInspectAddress PayloadInfo
decryptPath :: (Word8, ByteString) -> XPub -> Either ErrInspectAddress PayloadInfo
decryptPath (Word8, ByteString)
attr XPub
rootPub = do
let pwd :: ScrubbedBytes
pwd = XPub -> ScrubbedBytes
hdPassphrase XPub
rootPub
Maybe (Word32, Word32)
path <- (DeserialiseFailure -> ErrInspectAddress)
-> Either DeserialiseFailure (Maybe (Word32, Word32))
-> Either ErrInspectAddress (Maybe (Word32, Word32))
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (ErrInspectAddress -> DeserialiseFailure -> ErrInspectAddress
forall a b. a -> b -> a
const ErrInspectAddress
FailedToDecryptPath) (Either DeserialiseFailure (Maybe (Word32, Word32))
-> Either ErrInspectAddress (Maybe (Word32, Word32)))
-> Either DeserialiseFailure (Maybe (Word32, Word32))
-> Either ErrInspectAddress (Maybe (Word32, Word32))
forall a b. (a -> b) -> a -> b
$
(forall s. Decoder s (Maybe (Word32, Word32)))
-> ByteString -> Either DeserialiseFailure (Maybe (Word32, Word32))
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure a
CBOR.deserialiseCbor (ScrubbedBytes
-> [(Word8, ByteString)] -> Decoder s (Maybe (Word32, Word32))
forall s.
ScrubbedBytes
-> [(Word8, ByteString)] -> Decoder s (Maybe (Word32, Word32))
CBOR.decodeDerivationPathAttr ScrubbedBytes
pwd [(Word8, ByteString)
attr]) ByteString
forall a. Monoid a => a
mempty
case Maybe (Word32, Word32)
path of
Maybe (Word32, Word32)
Nothing -> ErrInspectAddress -> Either ErrInspectAddress PayloadInfo
forall a b. a -> Either a b
Left ErrInspectAddress
FailedToDecryptPath
Just (Word32
accountIndex, Word32
addressIndex) -> PayloadInfo -> Either ErrInspectAddress PayloadInfo
forall a b. b -> Either a b
Right PayloadDerivationPath{Word32
accountIndex :: Word32
addressIndex :: Word32
$sel:accountIndex:PayloadDerivationPath :: Word32
$sel:addressIndex:PayloadDerivationPath :: Word32
..}
data AddressInfo = AddressInfo
{ AddressInfo -> ByteString
infoAddressRoot :: !ByteString
, AddressInfo -> PayloadInfo
infoPayload :: !PayloadInfo
, AddressInfo -> Maybe NetworkTag
infoNetworkTag :: !(Maybe NetworkTag)
} deriving ((forall x. AddressInfo -> Rep AddressInfo x)
-> (forall x. Rep AddressInfo x -> AddressInfo)
-> Generic AddressInfo
forall x. Rep AddressInfo x -> AddressInfo
forall x. AddressInfo -> Rep AddressInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AddressInfo -> Rep AddressInfo x
from :: forall x. AddressInfo -> Rep AddressInfo x
$cto :: forall x. Rep AddressInfo x -> AddressInfo
to :: forall x. Rep AddressInfo x -> AddressInfo
Generic, Int -> AddressInfo -> ShowS
[AddressInfo] -> ShowS
AddressInfo -> String
(Int -> AddressInfo -> ShowS)
-> (AddressInfo -> String)
-> ([AddressInfo] -> ShowS)
-> Show AddressInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AddressInfo -> ShowS
showsPrec :: Int -> AddressInfo -> ShowS
$cshow :: AddressInfo -> String
show :: AddressInfo -> String
$cshowList :: [AddressInfo] -> ShowS
showList :: [AddressInfo] -> ShowS
Show, AddressInfo -> AddressInfo -> Bool
(AddressInfo -> AddressInfo -> Bool)
-> (AddressInfo -> AddressInfo -> Bool) -> Eq AddressInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AddressInfo -> AddressInfo -> Bool
== :: AddressInfo -> AddressInfo -> Bool
$c/= :: AddressInfo -> AddressInfo -> Bool
/= :: AddressInfo -> AddressInfo -> Bool
Eq)
data PayloadInfo
= PayloadDerivationPath
{ PayloadInfo -> Word32
accountIndex :: !Word32
, PayloadInfo -> Word32
addressIndex :: !Word32
}
| EncryptedDerivationPath
{ PayloadInfo -> ByteString
encryptedDerivationPath :: !ByteString
}
deriving ((forall x. PayloadInfo -> Rep PayloadInfo x)
-> (forall x. Rep PayloadInfo x -> PayloadInfo)
-> Generic PayloadInfo
forall x. Rep PayloadInfo x -> PayloadInfo
forall x. PayloadInfo -> Rep PayloadInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PayloadInfo -> Rep PayloadInfo x
from :: forall x. PayloadInfo -> Rep PayloadInfo x
$cto :: forall x. Rep PayloadInfo x -> PayloadInfo
to :: forall x. Rep PayloadInfo x -> PayloadInfo
Generic, Int -> PayloadInfo -> ShowS
[PayloadInfo] -> ShowS
PayloadInfo -> String
(Int -> PayloadInfo -> ShowS)
-> (PayloadInfo -> String)
-> ([PayloadInfo] -> ShowS)
-> Show PayloadInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PayloadInfo -> ShowS
showsPrec :: Int -> PayloadInfo -> ShowS
$cshow :: PayloadInfo -> String
show :: PayloadInfo -> String
$cshowList :: [PayloadInfo] -> ShowS
showList :: [PayloadInfo] -> ShowS
Show, PayloadInfo -> PayloadInfo -> Bool
(PayloadInfo -> PayloadInfo -> Bool)
-> (PayloadInfo -> PayloadInfo -> Bool) -> Eq PayloadInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PayloadInfo -> PayloadInfo -> Bool
== :: PayloadInfo -> PayloadInfo -> Bool
$c/= :: PayloadInfo -> PayloadInfo -> Bool
/= :: PayloadInfo -> PayloadInfo -> Bool
Eq)
instance ToJSON AddressInfo where
toJSON :: AddressInfo -> Value
toJSON AddressInfo{Maybe NetworkTag
ByteString
PayloadInfo
$sel:infoAddressRoot:AddressInfo :: AddressInfo -> ByteString
$sel:infoPayload:AddressInfo :: AddressInfo -> PayloadInfo
$sel:infoNetworkTag:AddressInfo :: AddressInfo -> Maybe NetworkTag
infoAddressRoot :: ByteString
infoPayload :: PayloadInfo
infoNetworkTag :: Maybe NetworkTag
..} = [Pair] -> Value
Json.object
[ Key
"address_root" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ByteString -> Text
T.decodeUtf8 (Encoding -> ByteString -> ByteString
encode Encoding
forall a. AbstractEncoding a
EBase16 ByteString
infoAddressRoot)
, Key
"derivation_path" Key -> PayloadInfo -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= PayloadInfo
infoPayload
, Key
"network_tag" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Value -> (NetworkTag -> Value) -> Maybe NetworkTag -> Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Value
Json.Null NetworkTag -> Value
forall a. ToJSON a => a -> Value
toJSON Maybe NetworkTag
infoNetworkTag
, Key
"address_type" Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON @Word8 Word8
8
]
instance ToJSON PayloadInfo where
toJSON :: PayloadInfo -> Value
toJSON PayloadDerivationPath{Word32
$sel:accountIndex:PayloadDerivationPath :: PayloadInfo -> Word32
$sel:addressIndex:PayloadDerivationPath :: PayloadInfo -> Word32
accountIndex :: Word32
addressIndex :: Word32
..} = [Pair] -> Value
Json.object
[ Key
"account_index" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Word32 -> String
prettyIndex Word32
accountIndex
, Key
"address_index" Key -> String -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Word32 -> String
prettyIndex Word32
addressIndex
]
where
prettyIndex :: Word32 -> String
prettyIndex :: Word32 -> String
prettyIndex Word32
ix
| Word32
ix Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word32
firstHardened = Word32 -> String
forall a. Show a => a -> String
show (Word32
ix Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
- Word32
firstHardened) String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"H"
| Bool
otherwise = Word32 -> String
forall a. Show a => a -> String
show Word32
ix
where
firstHardened :: Word32
firstHardened = Word32
0x80000000
toJSON EncryptedDerivationPath{ByteString
$sel:encryptedDerivationPath:PayloadDerivationPath :: PayloadInfo -> ByteString
encryptedDerivationPath :: ByteString
..} = Text -> Value
Json.String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$
ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ Encoding -> ByteString -> ByteString
encode Encoding
forall a. AbstractEncoding a
EBase16 ByteString
encryptedDerivationPath
instance Internal.PaymentAddress Byron where
paymentAddress :: NetworkDiscriminant Byron -> Byron 'PaymentK XPub -> Address
paymentAddress NetworkDiscriminant Byron
discrimination Byron 'PaymentK XPub
k = ByteString -> Address
unsafeMkAddress
(ByteString -> Address) -> ByteString -> Address
forall a b. (a -> b) -> a -> b
$ Encoding -> ByteString
CBOR.toStrictByteString
(Encoding -> ByteString) -> Encoding -> ByteString
forall a b. (a -> b) -> a -> b
$ XPub -> [Encoding] -> Encoding
CBOR.encodeAddress (Byron 'PaymentK XPub -> XPub
forall (depth :: Depth) key. Byron depth key -> key
getKey Byron 'PaymentK XPub
k) [Encoding]
attrs
where
(Word32
acctIx, Word32
addrIx) = (Index 'WholeDomain 'AccountK -> Word32)
-> (Index 'WholeDomain 'PaymentK -> Word32)
-> (Index 'WholeDomain 'AccountK, Index 'WholeDomain 'PaymentK)
-> (Word32, Word32)
forall a b c d. (a -> b) -> (c -> d) -> (a, c) -> (b, d)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Index 'WholeDomain 'AccountK -> Word32
forall (derivationType :: DerivationType) (depth :: Depth).
Index derivationType depth -> Word32
indexToWord32 Index 'WholeDomain 'PaymentK -> Word32
forall (derivationType :: DerivationType) (depth :: Depth).
Index derivationType depth -> Word32
indexToWord32 ((Index 'WholeDomain 'AccountK, Index 'WholeDomain 'PaymentK)
-> (Word32, Word32))
-> (Index 'WholeDomain 'AccountK, Index 'WholeDomain 'PaymentK)
-> (Word32, Word32)
forall a b. (a -> b) -> a -> b
$ Byron 'PaymentK XPub -> DerivationPath 'PaymentK
forall (depth :: Depth) key.
Byron depth key -> DerivationPath depth
derivationPath Byron 'PaymentK XPub
k
pwd :: ScrubbedBytes
pwd = Byron 'PaymentK XPub -> ScrubbedBytes
forall (depth :: Depth) key. Byron depth key -> ScrubbedBytes
payloadPassphrase Byron 'PaymentK XPub
k
NetworkTag Word32
magic = forall (key :: Depth -> * -> *).
HasNetworkDiscriminant key =>
NetworkDiscriminant key -> NetworkTag
networkTag @Byron NetworkDiscriminant Byron
discrimination
attrs :: [Encoding]
attrs = case forall (key :: Depth -> * -> *).
HasNetworkDiscriminant key =>
NetworkDiscriminant key -> AddressDiscrimination
addressDiscrimination @Byron NetworkDiscriminant Byron
discrimination of
AddressDiscrimination
RequiresNetworkTag ->
[ ScrubbedBytes -> Word32 -> Word32 -> Encoding
CBOR.encodeDerivationPathAttr ScrubbedBytes
pwd Word32
acctIx Word32
addrIx
, Word32 -> Encoding
CBOR.encodeProtocolMagicAttr Word32
magic
]
AddressDiscrimination
RequiresNoTag ->
[ ScrubbedBytes -> Word32 -> Word32 -> Encoding
CBOR.encodeDerivationPathAttr ScrubbedBytes
pwd Word32
acctIx Word32
addrIx
]
paymentAddress
:: NetworkDiscriminant Byron
-> Byron 'PaymentK XPub
-> Address
paymentAddress :: NetworkDiscriminant Byron -> Byron 'PaymentK XPub -> Address
paymentAddress =
NetworkDiscriminant Byron -> Byron 'PaymentK XPub -> Address
forall (key :: Depth -> * -> *).
PaymentAddress key =>
NetworkDiscriminant key -> key 'PaymentK XPub -> Address
Internal.paymentAddress
instance HasNetworkDiscriminant Byron where
type NetworkDiscriminant Byron = (AddressDiscrimination, NetworkTag)
addressDiscrimination :: NetworkDiscriminant Byron -> AddressDiscrimination
addressDiscrimination = (AddressDiscrimination, NetworkTag) -> AddressDiscrimination
NetworkDiscriminant Byron -> AddressDiscrimination
forall a b. (a, b) -> a
fst
networkTag :: NetworkDiscriminant Byron -> NetworkTag
networkTag = (AddressDiscrimination, NetworkTag) -> NetworkTag
NetworkDiscriminant Byron -> NetworkTag
forall a b. (a, b) -> b
snd
byronMainnet :: NetworkDiscriminant Byron
byronMainnet :: NetworkDiscriminant Byron
byronMainnet = (AddressDiscrimination
RequiresNoTag, Word32 -> NetworkTag
NetworkTag Word32
764824073)
byronStaging :: NetworkDiscriminant Byron
byronStaging :: NetworkDiscriminant Byron
byronStaging = (AddressDiscrimination
RequiresNetworkTag, Word32 -> NetworkTag
NetworkTag Word32
633343913)
byronTestnet :: NetworkDiscriminant Byron
byronTestnet :: NetworkDiscriminant Byron
byronTestnet = (AddressDiscrimination
RequiresNetworkTag, Word32 -> NetworkTag
NetworkTag Word32
1097911063)
byronPreview :: NetworkDiscriminant Byron
byronPreview :: NetworkDiscriminant Byron
byronPreview = (AddressDiscrimination
RequiresNetworkTag, Word32 -> NetworkTag
NetworkTag Word32
2)
byronPreprod :: NetworkDiscriminant Byron
byronPreprod :: NetworkDiscriminant Byron
byronPreprod = (AddressDiscrimination
RequiresNetworkTag, Word32 -> NetworkTag
NetworkTag Word32
1)
liftXPrv
:: XPub
-> DerivationPath depth
-> XPrv
-> Byron depth XPrv
liftXPrv :: forall (depth :: Depth).
XPub -> DerivationPath depth -> XPrv -> Byron depth XPrv
liftXPrv XPub
rootPub DerivationPath depth
derivationPath XPrv
getKey = Byron
{ XPrv
$sel:getKey:Byron :: XPrv
getKey :: XPrv
getKey
, DerivationPath depth
$sel:derivationPath:Byron :: DerivationPath depth
derivationPath :: DerivationPath depth
derivationPath
, $sel:payloadPassphrase:Byron :: ScrubbedBytes
payloadPassphrase = XPub -> ScrubbedBytes
hdPassphrase XPub
rootPub
}
{-# DEPRECATED liftXPrv "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
liftXPub
:: XPub
-> DerivationPath depth
-> XPub
-> Byron depth XPub
liftXPub :: forall (depth :: Depth).
XPub -> DerivationPath depth -> XPub -> Byron depth XPub
liftXPub XPub
rootPub DerivationPath depth
derivationPath XPub
getKey = Byron
{ XPub
$sel:getKey:Byron :: XPub
getKey :: XPub
getKey
, DerivationPath depth
$sel:derivationPath:Byron :: DerivationPath depth
derivationPath :: DerivationPath depth
derivationPath
, $sel:payloadPassphrase:Byron :: ScrubbedBytes
payloadPassphrase = XPub -> ScrubbedBytes
hdPassphrase XPub
rootPub
}
{-# DEPRECATED liftXPub "see 'Cardano.Address.Style.Icarus.Icarus'" #-}
minSeedLengthBytes :: Int
minSeedLengthBytes :: Int
minSeedLengthBytes = Int
16
hashSeed :: ScrubbedBytes -> ScrubbedBytes
hashSeed :: ScrubbedBytes -> ScrubbedBytes
hashSeed = ScrubbedBytes -> ScrubbedBytes
serialize (ScrubbedBytes -> ScrubbedBytes)
-> (ScrubbedBytes -> ScrubbedBytes)
-> ScrubbedBytes
-> ScrubbedBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrubbedBytes -> ScrubbedBytes
blake2b256 (ScrubbedBytes -> ScrubbedBytes)
-> (ScrubbedBytes -> ScrubbedBytes)
-> ScrubbedBytes
-> ScrubbedBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrubbedBytes -> ScrubbedBytes
serialize
where
serialize :: ScrubbedBytes -> ScrubbedBytes
serialize = ByteString -> ScrubbedBytes
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert (ByteString -> ScrubbedBytes)
-> (ScrubbedBytes -> ByteString) -> ScrubbedBytes -> ScrubbedBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
cbor (ByteString -> ByteString)
-> (ScrubbedBytes -> ByteString) -> ScrubbedBytes -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrubbedBytes -> ByteString
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert
cbor :: ByteString -> ByteString
cbor = Encoding -> ByteString
CBOR.toStrictByteString (Encoding -> ByteString)
-> (ByteString -> Encoding) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Encoding
CBOR.encodeBytes
blake2b256 :: ScrubbedBytes -> ScrubbedBytes
blake2b256 :: ScrubbedBytes -> ScrubbedBytes
blake2b256 = Digest Blake2b_256 -> ScrubbedBytes
forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
BA.convert (Digest Blake2b_256 -> ScrubbedBytes)
-> (ScrubbedBytes -> Digest Blake2b_256)
-> ScrubbedBytes
-> ScrubbedBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ba a.
(ByteArrayAccess ba, HashAlgorithm a) =>
ba -> Digest a
hash @ScrubbedBytes @Blake2b_256
hdPassphrase :: XPub -> ScrubbedBytes
hdPassphrase :: XPub -> ScrubbedBytes
hdPassphrase XPub
masterKey =
PRF ByteString
-> Parameters -> ByteString -> ByteString -> ScrubbedBytes
forall password salt ba.
(ByteArrayAccess password, ByteArrayAccess salt, ByteArray ba) =>
PRF password -> Parameters -> password -> salt -> ba
PBKDF2.generate
(SHA512 -> PRF ByteString
forall a password.
(HashAlgorithm a, ByteArrayAccess password) =>
a -> PRF password
PBKDF2.prfHMAC SHA512
SHA512)
(Int -> Int -> Parameters
PBKDF2.Parameters Int
500 Int
32)
(XPub -> ByteString
xpubToBytes XPub
masterKey)
(ByteString
"address-hashing" :: ByteString)