Maintainer | vincent@typed.io |
---|---|
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Cardano.Crypto.Wallet
Description
This provides similar functionality to BIP32 but using Ed25519 arithmetic instead of P256K1 arithmethic.
Key can be hierarchically derived from private key in two fashions: Hardened or Normal.
In the hardened scheme, the child secret key is not linearly derived, so that the child public key has no way to be efficiently computed from the parent public key.
The normal scheme allows anyone to derive public keys from public key.
Synopsis
- newtype ChainCode = ChainCode ByteString
- data DerivationScheme
- type DerivationIndex = Word32
- pattern LatestScheme :: DerivationScheme
- data XPrv
- data XPub = XPub {}
- data XSignature
- generate :: (ByteArrayAccess passPhrase, ByteArrayAccess seed) => seed -> passPhrase -> XPrv
- generateNew :: (ByteArrayAccess keyPassPhrase, ByteArrayAccess generationPassPhrase, ByteArrayAccess seed) => seed -> generationPassPhrase -> keyPassPhrase -> XPrv
- xprv :: ByteArrayAccess bin => bin -> Either String XPrv
- xpub :: ByteString -> Either String XPub
- xsignature :: ByteString -> Either String XSignature
- unXPrv :: XPrv -> ByteString
- unXPub :: XPub -> ByteString
- unXSignature :: XSignature -> ByteString
- toXPub :: HasCallStack => XPrv -> XPub
- xPubGetPublicKey :: XPub -> PublicKey
- xPrvChangePass :: (ByteArrayAccess oldPassPhrase, ByteArrayAccess newPassPhrase) => oldPassPhrase -> newPassPhrase -> XPrv -> XPrv
- deriveXPrv :: ByteArrayAccess passPhrase => DerivationScheme -> passPhrase -> XPrv -> Word32 -> XPrv
- deriveXPub :: DerivationScheme -> XPub -> Word32 -> Maybe XPub
- sign :: (ByteArrayAccess passPhrase, ByteArrayAccess msg) => passPhrase -> XPrv -> msg -> XSignature
- verify :: ByteArrayAccess msg => XPub -> msg -> XSignature -> Bool
Documentation
Constructors
ChainCode ByteString |
Instances
Show ChainCode Source # | |
NFData ChainCode Source # | |
Defined in Cardano.Crypto.Wallet.Types | |
Eq ChainCode Source # | |
Ord ChainCode Source # | |
Hashable ChainCode Source # | |
Defined in Cardano.Crypto.Wallet.Types | |
ByteArrayAccess ChainCode Source # | |
data DerivationScheme Source #
Constructors
DerivationScheme1 | |
DerivationScheme2 |
Instances
type DerivationIndex = Word32 Source #
pattern LatestScheme :: DerivationScheme Source #
Extended Private & Public types
Constructors
XPub | |
Fields |
Instances
Generic XPub Source # | |
Show XPub Source # | |
NFData XPub Source # | |
Defined in Cardano.Crypto.Wallet | |
Eq XPub Source # | |
Ord XPub Source # | |
Hashable XPub Source # | |
Defined in Cardano.Crypto.Wallet | |
type Rep XPub Source # | |
Defined in Cardano.Crypto.Wallet type Rep XPub = D1 ('MetaData "XPub" "Cardano.Crypto.Wallet" "cardano-crypto-1.3.0-86AJXuhOxHIyvBNHGbU6a" 'False) (C1 ('MetaCons "XPub" 'PrefixI 'True) (S1 ('MetaSel ('Just "xpubPublicKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "xpubChaincode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainCode))) |
data XSignature Source #
Instances
Show XSignature Source # | |
Defined in Cardano.Crypto.Wallet Methods showsPrec :: Int -> XSignature -> ShowS # show :: XSignature -> String # showList :: [XSignature] -> ShowS # | |
NFData XSignature Source # | |
Defined in Cardano.Crypto.Wallet Methods rnf :: XSignature -> () # | |
Eq XSignature Source # | |
Defined in Cardano.Crypto.Wallet | |
Ord XSignature Source # | |
Defined in Cardano.Crypto.Wallet Methods compare :: XSignature -> XSignature -> Ordering # (<) :: XSignature -> XSignature -> Bool # (<=) :: XSignature -> XSignature -> Bool # (>) :: XSignature -> XSignature -> Bool # (>=) :: XSignature -> XSignature -> Bool # max :: XSignature -> XSignature -> XSignature # min :: XSignature -> XSignature -> XSignature # | |
Hashable XSignature Source # | |
Defined in Cardano.Crypto.Wallet | |
ByteArrayAccess XSignature Source # | |
Defined in Cardano.Crypto.Wallet Methods length :: XSignature -> Int # withByteArray :: XSignature -> (Ptr p -> IO a) -> IO a # copyByteArrayToPtr :: XSignature -> Ptr p -> IO () # |
generate :: (ByteArrayAccess passPhrase, ByteArrayAccess seed) => seed -> passPhrase -> XPrv Source #
Generate a new XPrv
The seed needs to be at least 32 bytes, otherwise an asynchronous error is thrown
Arguments
:: (ByteArrayAccess keyPassPhrase, ByteArrayAccess generationPassPhrase, ByteArrayAccess seed) | |
=> seed | Raw entropy used as source of randomness for this algorithm |
-> generationPassPhrase | User chosen passphrase for the generation phase |
-> keyPassPhrase | Symmetric encryption key passphrase used for the in-memory security |
-> XPrv |
Generate a new XPrv from an entropy seed
The seed should be at least 16 bytes, although it is not enforced
The passphrase encrypt the secret key in memory
unXPrv :: XPrv -> ByteString Source #
unXPub :: XPub -> ByteString Source #
unXSignature :: XSignature -> ByteString Source #
xPubGetPublicKey :: XPub -> PublicKey Source #
Return the Ed25519 public key associated with a XPub context
Arguments
:: (ByteArrayAccess oldPassPhrase, ByteArrayAccess newPassPhrase) | |
=> oldPassPhrase | passphrase to decrypt the current encrypted key |
-> newPassPhrase | new passphrase to use for the new encrypted key |
-> XPrv | |
-> XPrv |
Derivation function
deriveXPrv :: ByteArrayAccess passPhrase => DerivationScheme -> passPhrase -> XPrv -> Word32 -> XPrv Source #
Derive a child extended private key from an extended private key
deriveXPub :: DerivationScheme -> XPub -> Word32 -> Maybe XPub Source #
Derive a child extended public key from an extended public key
Signature & Verification from extended types
sign :: (ByteArrayAccess passPhrase, ByteArrayAccess msg) => passPhrase -> XPrv -> msg -> XSignature Source #
verify :: ByteArrayAccess msg => XPub -> msg -> XSignature -> Bool Source #