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

Crypto.Encoding.BIP39

Synopsis

Entropy

data Entropy (n :: Nat) Source #

BIP39's entropy is a byte array of a given size (in bits, see ValidEntropySize for the valid size).

To it is associated

Instances

Instances details
Show (Entropy n) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

showsPrec :: Int -> Entropy n -> ShowS #

show :: Entropy n -> String #

showList :: [Entropy n] -> ShowS #

NormalForm (Entropy n) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

toNormalForm :: Entropy n -> () #

Arbitrary (Entropy 96) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

arbitrary :: Gen (Entropy 96) #

Arbitrary (Entropy 128) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

arbitrary :: Gen (Entropy 128) #

Arbitrary (Entropy 160) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

arbitrary :: Gen (Entropy 160) #

Arbitrary (Entropy 192) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

arbitrary :: Gen (Entropy 192) #

Arbitrary (Entropy 224) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

arbitrary :: Gen (Entropy 224) #

Arbitrary (Entropy 256) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

arbitrary :: Gen (Entropy 256) #

Eq (Entropy n) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

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

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

type ValidEntropySize (n :: Nat) = (KnownNat n, NatWithinBound Int n, Elem n '[96, 128, 160, 192, 224, 256]) Source #

Type Constraint Alias to check a given Nat is valid for an entropy size

i.e. it must be one of the following: 96, 128, 160, 192, 224, 256.

data Checksum (bits :: Nat) Source #

this is the Checksum of a given Entropy

the Nat type parameter represent the size, in bits, of this checksum.

Instances

Instances details
Show (Checksum bits) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

showsPrec :: Int -> Checksum bits -> ShowS #

show :: Checksum bits -> String #

showList :: [Checksum bits] -> ShowS #

NormalForm (Checksum bits) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

toNormalForm :: Checksum bits -> () #

Eq (Checksum bits) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

(==) :: Checksum bits -> Checksum bits -> Bool #

(/=) :: Checksum bits -> Checksum bits -> Bool #

type ValidChecksumSize (ent :: Nat) (csz :: Nat) = (KnownNat csz, NatWithinBound Int csz, Elem csz '[3, 4, 5, 6, 7, 8], CheckSumBits ent ~ csz) Source #

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

Number of Words related to a specific entropy size in bits

Equations

MnemonicWords 96 = 9 
MnemonicWords 128 = 12 
MnemonicWords 160 = 15 
MnemonicWords 192 = 18 
MnemonicWords 224 = 21 
MnemonicWords 256 = 24 

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

Corresponding entropy size in bits for a given number of words

Equations

EntropySize 9 = 96 
EntropySize 12 = 128 
EntropySize 15 = 160 
EntropySize 18 = 192 
EntropySize 21 = 224 
EntropySize 24 = 256 

toEntropy :: forall n csz ba. (ValidEntropySize n, ValidChecksumSize n csz, ByteArrayAccess ba) => ba -> Either (EntropyError csz) (Entropy n) Source #

Create a specific entropy type of known size from a raw bytestring

entropyRaw :: Entropy n -> ByteString Source #

Get the raw binary associated with the entropy

entropyChecksum :: Entropy n -> Checksum (CheckSumBits n) Source #

Get the checksum of the Entropy

entropyToWords :: forall n csz mw. ConsistentEntropy n mw csz => Entropy n -> MnemonicSentence mw Source #

Given an entropy of size n, Create a list

wordsToEntropy :: forall ent csz mw. ConsistentEntropy ent mw csz => MnemonicSentence mw -> Either (EntropyError csz) (Entropy ent) Source #

retrieve the initial entropy from a given MnemonicSentence

This function validate the retrieved Entropy is valid, i.e. that the checksum is correct. This means you should not create a new Entropy from a MnemonicSentence, instead, you should use a Random Number Generator to create a new Entropy.

Seed

data Seed Source #

Instances

Instances details
IsString Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

fromString :: String -> Seed #

Monoid Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

mempty :: Seed #

mappend :: Seed -> Seed -> Seed #

mconcat :: [Seed] -> Seed #

Semigroup Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

(<>) :: Seed -> Seed -> Seed #

sconcat :: NonEmpty Seed -> Seed #

stimes :: Integral b => b -> Seed -> Seed #

Show Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

showsPrec :: Int -> Seed -> ShowS #

show :: Seed -> String #

showList :: [Seed] -> ShowS #

Eq Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

(==) :: Seed -> Seed -> Bool #

(/=) :: Seed -> Seed -> Bool #

Ord Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

compare :: Seed -> Seed -> Ordering #

(<) :: Seed -> Seed -> Bool #

(<=) :: Seed -> Seed -> Bool #

(>) :: Seed -> Seed -> Bool #

(>=) :: Seed -> Seed -> Bool #

max :: Seed -> Seed -> Seed #

min :: Seed -> Seed -> Seed #

ByteArray Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Seed) #

ByteArrayAccess Seed Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

length :: Seed -> Int #

withByteArray :: Seed -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Seed -> Ptr p -> IO () #

sentenceToSeed Source #

Arguments

:: ValidMnemonicSentence mw 
=> MnemonicSentence mw

MmenomicPhrase of mw words

-> Dictionary

Dictionary' of words/indexes

-> Passphrase

Passphrase used to generate

-> Seed 

Create a seed from MmemonicSentence and Passphrase using the BIP39 algorithm.

phraseToSeed Source #

Arguments

:: ValidMnemonicSentence mw 
=> MnemonicPhrase mw

MmenomicPhrase of mw words

-> Dictionary

Dictionary' of words/indexes

-> Passphrase

Passphrase used to generate

-> Seed 

Create a seed from MmemonicPhrase and Passphrase using the BIP39 algorithm.

Mnemonic Sentence

data MnemonicSentence (mw :: Nat) Source #

Mnemonic Sentence is a list of WordIndex.

This is the generic representation of a mnemonic phrase that can be used for transalating to a different dictionary (example: English to Japanese).

This is mainly used to convert from/to the Entropy and for cardanoSlSeed

Instances

Instances details
ValidMnemonicSentence mw => IsList (MnemonicSentence mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Associated Types

type Item (MnemonicSentence mw) #

Show (MnemonicSentence mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

NormalForm (MnemonicSentence mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

toNormalForm :: MnemonicSentence mw -> () #

Eq (MnemonicSentence mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Ord (MnemonicSentence mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

type Item (MnemonicSentence mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

data MnemonicPhrase (mw :: Nat) Source #

Human readable representation of a MnemonicSentence

Instances

Instances details
ValidMnemonicSentence mw => IsList (MnemonicPhrase mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Associated Types

type Item (MnemonicPhrase mw) #

Show (MnemonicPhrase mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

NormalForm (MnemonicPhrase mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Methods

toNormalForm :: MnemonicPhrase mw -> () #

Eq (MnemonicPhrase mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

Ord (MnemonicPhrase mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

type Item (MnemonicPhrase mw) Source # 
Instance details

Defined in Crypto.Encoding.BIP39

type ValidMnemonicSentence (mw :: Nat) = (KnownNat mw, NatWithinBound Int mw, Elem mw '[9, 12, 15, 18, 21, 24]) Source #

Type Constraint to validate the given Nat is valid for the supported MnemonicSentence

checkMnemonicPhrase :: forall mw. ValidMnemonicSentence mw => Dictionary -> MnemonicPhrase mw -> Bool Source #

check a given MnemonicPhrase is valid for the given Dictionary

mnemonicPhraseToMnemonicSentence :: forall mw. ValidMnemonicSentence mw => Dictionary -> MnemonicPhrase mw -> Either DictionaryError (MnemonicSentence mw) Source #

convert the given MnemonicPhrase to a generic MnemonicSentence with the given Dictionary.

This function assumes the Dictionary and the MnemonicPhrase are compatible (see checkMnemonicPhrase).

mnemonicSentenceToMnemonicPhrase :: forall mw. ValidMnemonicSentence mw => Dictionary -> MnemonicSentence mw -> MnemonicPhrase mw Source #

convert the given generic MnemonicSentence to a human readable MnemonicPhrase targetting the language of the given Dictionary.

translateTo Source #

Arguments

:: forall mw. ValidMnemonicSentence mw 
=> Dictionary

source dictionary

-> Dictionary

destination dictionary

-> MnemonicPhrase mw 
-> Either DictionaryError (MnemonicPhrase mw) 

translate the given MnemonicPhrase from one dictionary into another.

This function assumes the source dictionary is compatible with the given MnemonicPhrase (see checkMnemonicPhrase)

Dictionary

data Dictionary Source #

this discribe the property of the Dictionary and will alllow to convert from a mnemonic phrase to MnemonicSentence

This is especially needed to build the BIP39 Seed

Constructors

Dictionary 

Fields

data WordIndex Source #

Index of the mnemonic word in the Dictionary

WordIndex are within range of [0..2047]

Instances

Instances details
Bounded WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

Enum WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

Show WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

NormalForm WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

Methods

toNormalForm :: WordIndex -> () #

Eq WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

Ord WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

TryFrom Int WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

Methods

tryFrom :: Int -> Maybe WordIndex #

TryFrom (Offset String) WordIndex Source # 
Instance details

Defined in Crypto.Encoding.BIP39.Dictionary

helpers

type ConsistentEntropy ent mw csz = (ValidEntropySize ent, ValidChecksumSize ent csz, ValidMnemonicSentence mw, MnemonicWords ent ~ mw) Source #

Type Constraint Alias to check the entropy size, the number of mnemonic words and the checksum size is consistent. i.e. that the following is true:

| entropysize | checksumsize | entropysize + checksumsize | mnemonicsize | +---------------+--------------+----------------------------+--------------+ | 96 | 3 | 99 | 9 | | 128 | 4 | 132 | 12 | | 160 | 5 | 165 | 15 | | 192 | 6 | 198 | 18 | | 224 | 7 | 231 | 21 | | 256 | 8 | 264 | 24 |

This type constraint alias also perform all the GHC's cumbersome type level literal handling.

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

Number of bits of checksum related to a specific entropy size in bits

Equations

CheckSumBits 96 = 3 
CheckSumBits 128 = 4 
CheckSumBits 160 = 5 
CheckSumBits 192 = 6 
CheckSumBits 224 = 7 
CheckSumBits 256 = 8 

type family Elem (e :: Nat) (l :: [Nat]) :: Constraint where ... Source #

convenient type level constraint to validate a given Nat e is an elemnt of the list of Nat l.

Equations

Elem e '[] = TypeError (('Text "offset: field " ':<>: 'ShowType e) ':<>: 'Text " not elements of valids values") 
Elem e (e ': _) = () 
Elem e (_ ': xs) = Elem e xs 

Errors

data EntropyError csz Source #

Instances

Instances details
Show (EntropyError csz) Source # 
Instance details

Defined in Crypto.Encoding.BIP39