Skip to content

Commit

Permalink
bip39-seed: Decode from hex if needed. More tests.
Browse files Browse the repository at this point in the history
  • Loading branch information
np committed Jan 16, 2015
1 parent add76bc commit 0b00d21
Show file tree
Hide file tree
Showing 8 changed files with 96 additions and 3 deletions.
5 changes: 4 additions & 1 deletion Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Utils where

import Control.Applicative
import Data.Binary
import Data.Char (isSpace,isDigit,toLower)
import Data.Char (isSpace,isDigit,toLower,isHexDigit)
import Data.Maybe
import Data.Monoid
import Data.String
Expand Down Expand Up @@ -43,6 +43,9 @@ instance Hex LBS.ByteString where
decodeHex msg = decodeHex msg . toStrictBS
encodeHex = toLazyBS . encodeHex

isHex :: String -> Bool
isHex = all (\ c -> isHexDigit c || isSpace c)

putLn :: (IsString s, Monoid s) => s -> s
putLn = (<> "\n")

Expand Down
6 changes: 4 additions & 2 deletions hx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -295,13 +295,15 @@ hx_hd_decode :: BS -> BS
hx_hd_decode = xKeyDetails . xKeyImportE

hx_bip39_mnemonic :: Hex s => s -> BS
hx_bip39_mnemonic = either error B8.pack . toMnemonic . decodeHex "seed"
hx_bip39_mnemonic = either error B8.pack . toMnemonic . decodeHex "mnemonic-as-hex"

hx_bip39_hex :: Hex s => BS -> s
hx_bip39_hex = encodeHex . either error id . fromMnemonic . B8.unpack

hx_bip39_seed :: Hex s => {-passphrase-}BS -> {-mnemonic-}BS -> s
hx_bip39_seed pf = encodeHex . either error id . mnemonicToSeed (B8.unpack pf) . B8.unpack
hx_bip39_seed pf = encodeHex . either error id . mnemonicToSeed (B8.unpack pf) . f . B8.unpack
where f s | isHex s = either (const s) id (toMnemonic (decodeHex "seed" s))
| otherwise = s

hx_btc, hx_satoshi :: BS -> BS
hx_btc = B8.pack . formatScientific Fixed (Just 8) . (/ one_btc_in_satoshi) . readBS
Expand Down
42 changes: 42 additions & 0 deletions tests/bip39-seed-from-hex.t/TESTRECIPE
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
#!/bin/bash

testname=bip39-seed-from-hex.t
command=hx
args=( bip39-seed )
exit_code=0
stdin_file=stdin
stdout_file=stdout
stderr_file=/dev/null
sources=( )
products=( )

# Environment variables:
env_vars=( )

setup(){
: Perform here actions to be run before the tested program
}

munge(){
: Munge here the results of the tested program to ease the check
}

check(){
check_exit_code &&
check_stderr &&
check_stdout &&
check_products &&
: Perform here extra checks on the tested program
}

explain(){
explain_exit_code
explain_stdout
explain_stderr
explain_products
: Explain here more potential differences
}

teardown(){
: Undo here the actions of setup
}
1 change: 1 addition & 0 deletions tests/bip39-seed-from-hex.t/stdin
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
636f727265637420686f727365206261747465727920737461706c65
1 change: 1 addition & 0 deletions tests/bip39-seed-from-hex.t/stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
1929625a9cb3ff0fc1a2bc5288807730469969278dc9629926a862cf3932bd888cb0d621f818ee7bee359281e9aa08f35deaa0dd559be5041bbc4c64ff57d7c6
42 changes: 42 additions & 0 deletions tests/bip39-seed.t/TESTRECIPE
Original file line number Diff line number Diff line change
@@ -0,0 +1,42 @@
#!/bin/bash

testname=bip39-seed.t
command=hx
args=( bip39-seed )
exit_code=0
stdin_file=stdin
stdout_file=stdout
stderr_file=/dev/null
sources=( )
products=( )

# Environment variables:
env_vars=( )

setup(){
: Perform here actions to be run before the tested program
}

munge(){
: Munge here the results of the tested program to ease the check
}

check(){
check_exit_code &&
check_stderr &&
check_stdout &&
check_products &&
: Perform here extra checks on the tested program
}

explain(){
explain_exit_code
explain_stdout
explain_stderr
explain_products
: Explain here more potential differences
}

teardown(){
: Undo here the actions of setup
}
1 change: 1 addition & 0 deletions tests/bip39-seed.t/stdin
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
gloom knee orient skull dance awake payment unusual inflict cinnamon blush seed elder crawl size catch inflict perfect foster sugar fox
1 change: 1 addition & 0 deletions tests/bip39-seed.t/stdout
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
1929625a9cb3ff0fc1a2bc5288807730469969278dc9629926a862cf3932bd888cb0d621f818ee7bee359281e9aa08f35deaa0dd559be5041bbc4c64ff57d7c6

0 comments on commit 0b00d21

Please sign in to comment.