Skip to content

Commit 211bc94

Browse files
committed
[LTB-7] Write unit tests for all decode cases
1 parent 5e7ae0b commit 211bc94

File tree

3 files changed

+147
-3
lines changed

3 files changed

+147
-3
lines changed

code/crypto/lib/Loot/Crypto/Bech32.hs

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,16 @@
11
module Loot.Crypto.Bech32
2-
(
3-
HumanReadablePart
2+
( DecodeError (..)
3+
, EncodeError (..)
4+
, HumanReadablePart
45
, encode
56
, decode
67
)
78
where
89

910
import Universum
1011

11-
import Codec.Binary.Bech32 (DecodeError, EncodeError, bech32Decode, bech32Encode, fromWord5, word5)
12+
import Codec.Binary.Bech32 (DecodeError (..), EncodeError (..), bech32Decode, bech32Encode,
13+
fromWord5, word5)
1214

1315
import qualified Data.ByteString as BS
1416

code/crypto/package.yaml

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,3 +16,6 @@ tests:
1616
dependencies:
1717
- tasty
1818
- tasty-discover
19+
- tasty-hunit
20+
21+
- loot-crypto
Lines changed: 139 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,139 @@
1+
module Test.Loot.Crypto.Bech32 where
2+
3+
import Universum
4+
5+
import Test.Tasty
6+
import Test.Tasty.HUnit
7+
8+
import qualified Loot.Crypto.Bech32 as B32
9+
10+
--------------------------------------------
11+
---- Test data
12+
--------------------------------------------
13+
14+
validB32Strings :: [String]
15+
validB32Strings =
16+
[
17+
"A12UEL5L"
18+
, "a12uel5l"
19+
, "an83characterlonghumanreadablepartthatcontainsthenumber1andtheexcludedcharactersbio1tt5tgs"
20+
, "abcdef1qpzry9x8gf2tvdw0s3jn54khce6mua7lmqqqxw"
21+
, "11qqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqc8247j"
22+
, "split1checkupstagehandshakeupstreamerranterredcaperred2y9e3w"
23+
]
24+
25+
b32WithInvalidHRP :: [String]
26+
b32WithInvalidHRP =
27+
[
28+
"1qzzfhee"
29+
, "10a06t8"
30+
, "1pzry9x0s0muk"
31+
, "pzry9x0s0muk"
32+
]
33+
34+
b32WithExceededLength :: [String]
35+
b32WithExceededLength =
36+
[
37+
"an84characterslonghumanreadablepartthatcontainsthenumber1andtheexcludedcharactersbio1569pvx"
38+
]
39+
40+
b32WithInvalidChecksum :: [String]
41+
b32WithInvalidChecksum =
42+
[
43+
"A1G7SGD8"
44+
, "a1fuel5l"
45+
, "an83characterlonghumanreadablepartthatcontainsthenumber1fndtheexcludedcharactersbio1tt5tgs"
46+
, "abcdef1fpzry9x8gf2tvdw0s3jn54khce6mua7lmqqqxw"
47+
, "11fqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqc8247j"
48+
, "split1fheckupstagehandshakeupstreamerranterredcaperred2y9e3w"
49+
]
50+
51+
b32WithInvalidCharsetMap :: [String]
52+
b32WithInvalidCharsetMap =
53+
[
54+
"a1bbel5l"
55+
, "a1ibel5l"
56+
, "a1obel5l"
57+
]
58+
59+
b32WithCaseInconsistency :: [String]
60+
b32WithCaseInconsistency =
61+
[
62+
"A12UeL5L"
63+
, "a12uFl5l"
64+
, "An83characterlonghumanreadablepartthatcontainsthenumber1andtheexcludedcharactersbio1tt5tgs"
65+
, "Abcdef1qpzry9x8gf2tvdw0s3jn54khce6mua7lmqqqxw"
66+
, "11Qqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqqc8247j"
67+
, "Split1checkupstagehandshakeupstreamerranterredcaperred2y9e3w"
68+
]
69+
70+
b32WithTooShortDataPart :: [String]
71+
b32WithTooShortDataPart =
72+
[
73+
74+
"a1f"
75+
, "a1ff"
76+
, "a1fff"
77+
, "a1ffff"
78+
, "a1fffff"
79+
]
80+
81+
--------------------------------------------
82+
--------------------------------------------
83+
--------------------------------------------
84+
85+
-----------------------
86+
-- Decoding
87+
-----------------------
88+
89+
90+
unit_validB32Strings :: Assertion
91+
unit_validB32Strings = assertDecodeSuccess validB32Strings
92+
93+
unit_invalidHRP :: Assertion
94+
unit_invalidHRP = assertDecodeError B32.InvalidHRP comment b32WithInvalidHRP
95+
where comment = "has invlaid human readable part."
96+
97+
unit_exceededLength :: Assertion
98+
unit_exceededLength = assertDecodeError B32.Bech32StringLengthExceeded comment b32WithExceededLength
99+
where comment = "has exceeded length"
100+
101+
unit_invalidChecksums :: Assertion
102+
unit_invalidChecksums = assertDecodeError B32.ChecksumVerificationFail comment b32WithInvalidChecksum
103+
where comment = "has invalid checksum"
104+
105+
unit_invalidCharsetMap :: Assertion
106+
unit_invalidCharsetMap = assertDecodeError B32.InvalidCharsetMap comment b32WithInvalidCharsetMap
107+
where comment = "has invalid charset map"
108+
109+
unit_caseInconsistency :: Assertion
110+
unit_caseInconsistency = assertDecodeError B32.CaseInconsistency comment b32WithCaseInconsistency
111+
where comment = "has case inconsitency"
112+
113+
unit_tooShortDataPart :: Assertion
114+
unit_tooShortDataPart = assertDecodeError B32.TooShortDataPart comment b32WithTooShortDataPart
115+
where comment = "has too short data part"
116+
-----------------------
117+
-- Helpers
118+
-----------------------
119+
120+
assertDecodeSuccess :: [String] -> Assertion
121+
assertDecodeSuccess = assertDecode isRight
122+
"Is valid and should be decoded successfully."
123+
124+
assertDecodeError :: B32.DecodeError -> String -> [String] -> Assertion
125+
assertDecodeError err comment = assertDecode (isError err) (comment ++ " and therefore is invalid.")
126+
127+
assertDecode :: (Either B32.DecodeError (B32.HumanReadablePart, ByteString) -> Bool)
128+
-> String
129+
-> [String]
130+
-> Assertion
131+
assertDecode pred comment inp = forM_ inp validadteDecoding
132+
where
133+
validadteDecoding b32str = assert' . pred . B32.decode $ b32str
134+
where
135+
assert' = assertBool $ (show b32str)++" "++comment
136+
137+
isError :: Eq a => a -> Either a b -> Bool
138+
isError e' (Left e) = e == e'
139+
isError _ _ = False

0 commit comments

Comments
 (0)