| Copyright | 2020 Input Output (Hong Kong) Ltd. 2021-2022 Input Output Global Inc. (IOG) 2023-2025 Intersect |
|---|---|
| License | Apache-2.0 |
| Safe Haskell | None |
| Language | Haskell2010 |
Cardano.Mnemonic
Description
Synopsis
- data SomeMnemonic where
- SomeMnemonic :: forall (mw :: Nat). KnownNat mw => Mnemonic mw -> SomeMnemonic
- class MkSomeMnemonic (sz :: [Nat]) where
- mkSomeMnemonic :: [Text] -> Either (MkSomeMnemonicError sz) SomeMnemonic
- newtype MkSomeMnemonicError (sz :: [Nat]) = MkSomeMnemonicError {}
- someMnemonicToBytes :: SomeMnemonic -> ScrubbedBytes
- class NatVals (ns :: [Nat]) where
- data Mnemonic (mw :: Nat)
- mkMnemonicWithDict :: forall (mw :: Nat) (ent :: Nat) (csz :: Nat). (ConsistentEntropy ent mw csz, EntropySize mw ~ ent) => [Text] -> Dictionary -> Either (MkMnemonicError csz) (Mnemonic mw)
- mkMnemonic :: forall (mw :: Nat) (ent :: Nat) (csz :: Nat). (ConsistentEntropy ent mw csz, EntropySize mw ~ ent) => [Text] -> Either (MkMnemonicError csz) (Mnemonic mw)
- data MkMnemonicError (csz :: Nat)
- mnemonicToTextWithDict :: forall (mw :: Nat). Mnemonic mw -> Dictionary -> [Text]
- mnemonicToText :: forall (mw :: Nat). Mnemonic mw -> [Text]
- mnemonicToEntropy :: Mnemonic mw -> Entropy (EntropySize mw)
- data Entropy (n :: Nat)
- genEntropy :: forall (ent :: Nat) (csz :: Nat). (ValidEntropySize ent, ValidChecksumSize ent csz) => IO (Entropy ent)
- mkEntropy :: forall (ent :: Nat) (csz :: Nat). (ValidEntropySize ent, ValidChecksumSize ent csz) => ScrubbedBytes -> Either (EntropyError csz) (Entropy ent)
- entropyToBytes :: forall (n :: Nat). Entropy n -> ScrubbedBytes
- entropyToMnemonic :: forall (mw :: Nat) (ent :: Nat) (csz :: Nat). (ValidMnemonicSentence mw, ValidEntropySize ent, ValidChecksumSize ent csz, ent ~ EntropySize mw, mw ~ MnemonicWords ent) => Entropy ent -> Mnemonic mw
- data Dictionary
- type ValidEntropySize (n :: Nat) = (KnownNat n, NatWithinBound Int n, Elem n '[96, 128, 160, 192, 224, 256])
- type ValidMnemonicSentence (mw :: Nat) = (KnownNat mw, NatWithinBound Int mw, Elem mw '[9, 12, 15, 18, 21, 24])
- type ConsistentEntropy (ent :: Nat) (mw :: Nat) (csz :: Nat) = (ValidEntropySize ent, ValidChecksumSize ent csz, ValidMnemonicSentence mw, MnemonicWords ent ~ mw)
- type family CheckSumBits (n :: Nat) :: Nat where ...
- type family EntropySize (n :: Nat) :: Nat where ...
- type family MnemonicWords (n :: Nat) :: Nat where ...
- newtype MnemonicException (csz :: Nat) = UnexpectedEntropyError (EntropyError csz)
Introduction
We call Entropy an arbitrary sequence of bytes that has been generated
through high quality randomness methods. The allowed size of an
Entropy is 96-256 bits and is necessarily a multiple of 32 bits (4
bytes).
Mnemonic is an Entropy with an appended checksum calculated by
taking the first ent / 32 bits of the SHA256 hash of it, where ent
designates the Entropy size in bits.
The concatenated result is split into groups of 11 bits, each encoding a
number from 0 to 2047 serving as an index into a known dictionary:
https://github.com/cardano-foundation/cardano-wallet/tree/master/specifications/mnemonic/english.txt
This makes for a human-readable sentence of English words.
| Entropy Size | Checksum Size | Sentence Length | Example |
|---|---|---|---|
| 96 bits (12 bytes) | 3 bits | 9 words | test child burst immense armed parrot company walk dog |
| 128 bits (16 bytes) | 4 bits | 12 words | test walk nut penalty hip pave soap entry language right filter choice |
| 160 bits (20 bytes) | 5 bits | 15 words | art forum devote street sure rather head chuckle guard poverty release quote oak craft enemy |
| 192 bits (24 bytes) | 6 bits | 18 words | churn shaft spoon second erode useless thrive burst group seed element sign scrub buffalo jelly grace neck useless |
| 224 bits (28 bytes) | 7 bits | 21 words | draft ability female child jump maid roof hurt below live topple paper exclude ordinary coach churn sunset emerge blame ketchup much |
| 256 bits (32 bytes) | 8 bits | 24 words | excess behave track soul table wear ocean cash stay nature item turtle palm soccer lunch horror start stumble month panic right must lock dress |
SomeMnemonic
data SomeMnemonic where Source #
Ease the manipulation of Mnemonic by encapsulating the type constraints inside a constructor.
This is particularly useful for functions which do not require anything but a valid Mnemonic without any
particular pre-condition on the size of the Mnemonic itself.
Since: 1.0.0
Constructors
| SomeMnemonic :: forall (mw :: Nat). KnownNat mw => Mnemonic mw -> SomeMnemonic |
Instances
| Show SomeMnemonic Source # | |
Defined in Cardano.Mnemonic Methods showsPrec :: Int -> SomeMnemonic -> ShowS # show :: SomeMnemonic -> String # showList :: [SomeMnemonic] -> ShowS # | |
| NFData SomeMnemonic Source # | |
Defined in Cardano.Mnemonic Methods rnf :: SomeMnemonic -> () # | |
| Eq SomeMnemonic Source # | |
Defined in Cardano.Mnemonic | |
class MkSomeMnemonic (sz :: [Nat]) where Source #
This class enables caller to parse text list of variable length into mnemonic sentences.
Note that the given Nats have to be valid mnemonic sizes, otherwise the
underlying code won't even compile, with not-so-friendly error messages.
Methods
mkSomeMnemonic :: [Text] -> Either (MkSomeMnemonicError sz) SomeMnemonic Source #
Construct a mnemonic from a list of words. This function is particularly useful when the number of words is not necessarily known at runtime. The function is however ambiguous and requires thereby a type application.
Examples:
>>>mkSomeMnemonic @'[ 12 ] [ "test", "child", "burst", "immense", "armed", "parrot", "company", "walk", "dog" ]Left "Invalid number of words: 12 words are expected."
>>>mkSomeMnemonic @'[ 9, 12, 15 ] [ "test", "child", "burst", "immense", "armed", "parrot", "company", "walk", "dog" ]Right (SomeMnemonic ...)
Since: 1.0.0
Instances
| (n ~ EntropySize mw, csz ~ CheckSumBits n, ConsistentEntropy n mw csz) => MkSomeMnemonic '[mw] Source # | |
Defined in Cardano.Mnemonic Methods mkSomeMnemonic :: [Text] -> Either (MkSomeMnemonicError '[mw]) SomeMnemonic Source # | |
| (n ~ EntropySize mw, csz ~ CheckSumBits n, ConsistentEntropy n mw csz, MkSomeMnemonic rest, NatVals rest) => MkSomeMnemonic (mw ': rest) Source # | |
Defined in Cardano.Mnemonic Methods mkSomeMnemonic :: [Text] -> Either (MkSomeMnemonicError (mw ': rest)) SomeMnemonic Source # | |
newtype MkSomeMnemonicError (sz :: [Nat]) Source #
Error reported from trying to create a passphrase from a given mnemonic
Since: 1.0.0
Constructors
| MkSomeMnemonicError | |
Fields | |
Instances
| Show (MkSomeMnemonicError sz) Source # | |
Defined in Cardano.Mnemonic Methods showsPrec :: Int -> MkSomeMnemonicError sz -> ShowS # show :: MkSomeMnemonicError sz -> String # showList :: [MkSomeMnemonicError sz] -> ShowS # | |
| Eq (MkSomeMnemonicError sz) Source # | |
Defined in Cardano.Mnemonic Methods (==) :: MkSomeMnemonicError sz -> MkSomeMnemonicError sz -> Bool # (/=) :: MkSomeMnemonicError sz -> MkSomeMnemonicError sz -> Bool # | |
someMnemonicToBytes :: SomeMnemonic -> ScrubbedBytes Source #
Convert a SomeMnemonic to bytes.
Since: 1.0.1
Mnemonic
data Mnemonic (mw :: Nat) Source #
A opaque Mnemonic type.
mkMnemonicWithDict :: forall (mw :: Nat) (ent :: Nat) (csz :: Nat). (ConsistentEntropy ent mw csz, EntropySize mw ~ ent) => [Text] -> Dictionary -> Either (MkMnemonicError csz) (Mnemonic mw) Source #
Smart-constructor for Mnemonic for arbitrary dictionary. Requires a type application to
disambiguate the mnemonic size.
Example:
>>>mkMnemonicWithDict @15 sentence dictionaryMnemonic {} :: Mnemonic 15
Property:
mkMnemonicWithDict (mnemonicToTextWithDict mnemonic dictionary) dictionary == Right mnemonic
Since: 4.0.1
mkMnemonic :: forall (mw :: Nat) (ent :: Nat) (csz :: Nat). (ConsistentEntropy ent mw csz, EntropySize mw ~ ent) => [Text] -> Either (MkMnemonicError csz) (Mnemonic mw) Source #
Smart-constructor for English Mnemonic. Requires a type application to
disambiguate the mnemonic size.
Example:
>>>mkMnemonic @15 sentenceMnemonic {} :: Mnemonic 15
Property:
mkMnemonic (mnemonicToText mnemonic) == Right mnemonic
Since: 1.0.0
data MkMnemonicError (csz :: Nat) Source #
This wraps errors from Cardano.Encoding.BIP39
Constructors
| ErrMnemonicWords MnemonicWordsError | Wrong number of words in mnemonic. |
| ErrEntropy (EntropyError csz) | Invalid entropy length or checksum. |
| ErrDictionary DictionaryError | Invalid word in mnemonic. |
Instances
| Show (MkMnemonicError csz) Source # | |
Defined in Cardano.Mnemonic Methods showsPrec :: Int -> MkMnemonicError csz -> ShowS # show :: MkMnemonicError csz -> String # showList :: [MkMnemonicError csz] -> ShowS # | |
| NFData (MkMnemonicError csz) Source # | |
Defined in Cardano.Mnemonic Methods rnf :: MkMnemonicError csz -> () # | |
| Eq (MkMnemonicError csz) Source # | |
Defined in Cardano.Mnemonic Methods (==) :: MkMnemonicError csz -> MkMnemonicError csz -> Bool # (/=) :: MkMnemonicError csz -> MkMnemonicError csz -> Bool # | |
mnemonicToTextWithDict :: forall (mw :: Nat). Mnemonic mw -> Dictionary -> [Text] Source #
Convert a Mnemonic to a sentence of a specified dictionary mnemonic words.
Since: 4.0.1
mnemonicToText :: forall (mw :: Nat). Mnemonic mw -> [Text] Source #
Convert a Mnemonic to a sentence of English mnemonic words.
Since: 1.0.0
mnemonicToEntropy :: Mnemonic mw -> Entropy (EntropySize mw) Source #
Entropy
BIP39's entropy is a byte array of a given size (in bits, see
ValidEntropySize for the valid size).
To it is associated
Instances
| Show (Entropy n) | |
| NormalForm (Entropy n) | |
Defined in Crypto.Encoding.BIP39 Methods toNormalForm :: Entropy n -> () # | |
| Arbitrary (Entropy 96) | |
Defined in Crypto.Encoding.BIP39 | |
| Arbitrary (Entropy 128) | |
Defined in Crypto.Encoding.BIP39 | |
| Arbitrary (Entropy 160) | |
Defined in Crypto.Encoding.BIP39 | |
| Arbitrary (Entropy 192) | |
Defined in Crypto.Encoding.BIP39 | |
| Arbitrary (Entropy 224) | |
Defined in Crypto.Encoding.BIP39 | |
| Arbitrary (Entropy 256) | |
Defined in Crypto.Encoding.BIP39 | |
| Eq (Entropy n) | |
genEntropy :: forall (ent :: Nat) (csz :: Nat). (ValidEntropySize ent, ValidChecksumSize ent csz) => IO (Entropy ent) Source #
Generate Entropy of a given size using a cryptographically secure random seed.
Example:
>>>genEntropy @128Entropy {} :: Entropy 128
Since: 1.0.0
mkEntropy :: forall (ent :: Nat) (csz :: Nat). (ValidEntropySize ent, ValidChecksumSize ent csz) => ScrubbedBytes -> Either (EntropyError csz) (Entropy ent) Source #
Smart-constructor for the Entropy. Make sure the ByteString comes from a highly random source or use genEntropy.
Example:
>>>mkEntropy @160 bytesEntropy {} :: Entropy 160
Property:
mkEntropy (entropyToBytes ent) == Right ent
Since: 1.0.0
entropyToBytes :: forall (n :: Nat). Entropy n -> ScrubbedBytes Source #
Convert Entropy to plain bytes.
Since: 1.0.0
entropyToMnemonic :: forall (mw :: Nat) (ent :: Nat) (csz :: Nat). (ValidMnemonicSentence mw, ValidEntropySize ent, ValidChecksumSize ent csz, ent ~ EntropySize mw, mw ~ MnemonicWords ent) => Entropy ent -> Mnemonic mw Source #
Dictionary
data Dictionary #
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
Internals & Re-export from Crypto.Encoding.BIP39
type ValidEntropySize (n :: Nat) = (KnownNat n, NatWithinBound Int n, Elem n '[96, 128, 160, 192, 224, 256]) #
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.
type ValidMnemonicSentence (mw :: Nat) = (KnownNat mw, NatWithinBound Int mw, Elem mw '[9, 12, 15, 18, 21, 24]) #
Type Constraint to validate the given Nat is valid for the supported
MnemonicSentence
type ConsistentEntropy (ent :: Nat) (mw :: Nat) (csz :: Nat) = (ValidEntropySize ent, ValidChecksumSize ent csz, ValidMnemonicSentence mw, MnemonicWords ent ~ mw) #
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 ... #
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 EntropySize (n :: Nat) :: Nat where ... #
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 |
type family MnemonicWords (n :: Nat) :: Nat where ... #
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 |
newtype MnemonicException (csz :: Nat) Source #
This wraps EntropyError of Cardano.Encoding.BIP39
Constructors
| UnexpectedEntropyError (EntropyError csz) | Invalid entropy length or checksum |
Instances
| KnownNat csz => Exception (MnemonicException csz) Source # | |
Defined in Cardano.Mnemonic Methods toException :: MnemonicException csz -> SomeException # fromException :: SomeException -> Maybe (MnemonicException csz) # displayException :: MnemonicException csz -> String # | |
| Show (MnemonicException csz) Source # | |
Defined in Cardano.Mnemonic Methods showsPrec :: Int -> MnemonicException csz -> ShowS # show :: MnemonicException csz -> String # showList :: [MnemonicException csz] -> ShowS # | |
| NFData (MnemonicException csz) Source # | |
Defined in Cardano.Mnemonic Methods rnf :: MnemonicException csz -> () # | |
Troubleshooting
- Natural XX is out of bounds for Int:
This usually occurs when ones is trying to specify an invalid size for an
EntropyorMnemonic. For example:
>>>genEntropy @42error: • Natural CheckSumBits 42 is out of bounds for Int
- This could be the case as well when forgetting to use an adequate type application:
>>>mkEntropy memptyerror: • Natural ent is out of bounds for Int
Orphan instances
| NFData MnemonicWordsError Source # | |
Methods rnf :: MnemonicWordsError -> () # | |
| NFData DictionaryError Source # | |
Methods rnf :: DictionaryError -> () # | |
| Eq MnemonicWordsError Source # | |
Methods (==) :: MnemonicWordsError -> MnemonicWordsError -> Bool # (/=) :: MnemonicWordsError -> MnemonicWordsError -> Bool # | |
| Eq DictionaryError Source # | |
Methods (==) :: DictionaryError -> DictionaryError -> Bool # (/=) :: DictionaryError -> DictionaryError -> Bool # | |
| NFData (EntropyError csz) Source # | |
Methods rnf :: EntropyError csz -> () # | |
| Eq (EntropyError czs) Source # | |
Methods (==) :: EntropyError czs -> EntropyError czs -> Bool # (/=) :: EntropyError czs -> EntropyError czs -> Bool # | |