cardano-crypto-1.3.0: Cryptography primitives for cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.ECC.Ed25519BIP32

Synopsis

Documentation

type MasterSecret = FBits 256 Source #

A Master secret is a 256 bits random quantity

type ChildKey (didxs :: DerivationHier) = Key Source #

A child key is similar to the key in structure except it has an additional annotation representing the indexes for the hierarchy derivation indexes from a base Key (usually the root key)

type Key = (FBits 256, FBits 256, ChainCode) Source #

A key is a 512 bit random value and a chaincode

Left half need to have: * Lowest 3 bits clear * Highest bit clear * Second highest bit set * Third highest bit clear

Right half doesn't have any particular structure.

type Public = (PointCompressed, ChainCode) Source #

A public part of a key

type PointCompressed = FBits 256 Source #

A point is 1 bit of x sign and 255 bit of y coordinate (y's 256th bit is always 0)

newtype ChainCode Source #

A 256 bits chain code

Constructors

ChainCode 

Fields

Instances

Instances details
Eq ChainCode Source # 
Instance details

Defined in Crypto.ECC.Ed25519BIP32

GetDerivationMaterial 'Hard Key Source # 
Instance details

Defined in Crypto.ECC.Ed25519BIP32

GetDerivationMaterial 'Soft Key Source # 
Instance details

Defined in Crypto.ECC.Ed25519BIP32

newtype Hash n Source #

A n bits Digest

Constructors

Hash 

Fields

Instances

Instances details
Eq (Hash n) Source # 
Instance details

Defined in Crypto.ECC.Ed25519BIP32

Methods

(==) :: Hash n -> Hash n -> Bool #

(/=) :: Hash n -> Hash n -> Bool #

type Tag = Bytes 1 Source #

A Serialized tag used during HMAC

newtype SerializedIndex Source #

Serialized Index

Constructors

SerializedIndex (Bytes 4) 

Instances

Instances details
Eq SerializedIndex Source # 
Instance details

Defined in Crypto.ECC.Ed25519BIP32

data DerivationType Source #

Constructors

Hard 
Soft 

data DerivationIndex (k :: DerivationType) (n :: Nat) Source #

Constructors

DerivationIndex 

type MaxHardIndex = 4294967295 Source #

type MinHardIndex = 2147483648 Source #

leftHalfValid :: FBits 256 -> Bool Source #

Check if the left half is valid

type family BitsToHashScheme (n :: Nat) where ... Source #

type ValidTag tag = (0 <= tag, tag <= 3) Source #

fcp :: forall tag idx deriveType deriveMaterial. (KnownNat (DerivationTag deriveType deriveMaterial), KnownNat idx, DerivationTag deriveType deriveMaterial ~ tag, ValidDerivationIndex idx ~ 'True, ValidDerivationIndexForType deriveType idx ~ 'True) => Proxy deriveMaterial -> Proxy deriveType -> Proxy idx -> ChainCode -> DerivationIndex deriveType idx -> [Word8] -> HMAC_SHA512 Source #

Compute the HMAC-SHA512 using the ChainCode as the key

hmacSHA512 :: Bytes keyLength -> Bytes input -> HMAC_SHA512 Source #

step2 :: Bytes 64 -> (FBits 256, FBits 256) Source #

Given Z, return 8*ZL(28Bytes) and ZR

indexSerialized :: forall idx. (KnownNat idx, ValidDerivationIndex idx ~ 'True) => Proxy idx -> SerializedIndex Source #

Serialized index