Skip to content

Commit ad02fdd

Browse files
authored
Add structured types for bech32 encoding result (#40)
* Add structured types for bech32 encoding result This introduces the `bech32EncodeResult` and `bech32DecodeResult` functions and their respective structured types to allow for custom application handling of failures. This also exports the `maxBech32Length` function. * Desugar record wildcards * Disambiguate record fields
1 parent c3c81d2 commit ad02fdd

File tree

1 file changed

+89
-15
lines changed

1 file changed

+89
-15
lines changed

src/Bitcoin/Address/Bech32.hs

Lines changed: 89 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE MultiWayIf #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
23
{-# LANGUAGE OverloadedStrings #-}
34

45
-- |
@@ -16,16 +17,21 @@ module Bitcoin.Address.Bech32 (
1617
Data,
1718
bech32Encode,
1819
bech32Decode,
20+
Bech32EncodeResult (..),
21+
bech32EncodeResult,
22+
Bech32DecodeResult (..),
23+
bech32DecodeResult,
1924
toBase32,
2025
toBase256,
2126
segwitEncode,
2227
segwitDecode,
2328
Word5 (..),
2429
word5,
2530
fromWord5,
31+
maxBech32Length,
2632
) where
2733

28-
import Control.Monad (guard)
34+
import Control.Monad (guard, join)
2935
import Data.Array (
3036
Array,
3137
assocs,
@@ -78,7 +84,7 @@ type Data = [Word8]
7884
-- | Five-bit word for Bech32.
7985
newtype Word5
8086
= UnsafeWord5 Word8
81-
deriving (Eq, Ord)
87+
deriving (Show, Eq, Ord)
8288

8389

8490
instance Ix Word5 where
@@ -174,12 +180,36 @@ maxBech32Length = 90
174180
-- than 90 characters.
175181
bech32Encode :: Bech32Encoding -> HRP -> [Word5] -> Maybe Bech32
176182
bech32Encode enc hrp dat = do
177-
guard $ checkHRP hrp
183+
Bech32EncodeResult
184+
{ encodeResult
185+
, encodeValidHrp = True
186+
, encodeValidLength = True
187+
} <-
188+
pure $ bech32EncodeResult enc hrp dat
189+
return encodeResult
190+
191+
192+
-- | The result of encoding a 'Bech32' string
193+
data Bech32EncodeResult = Bech32EncodeResult
194+
{ encodeResult :: Text
195+
, encodeValidHrp :: Bool
196+
, encodeValidLength :: Bool
197+
}
198+
deriving (Show, Eq)
199+
200+
201+
-- | Encode string of five-bit words into 'Bech32' using a provided
202+
-- human-readable part. This is similar to 'bech32Encode', but allows the caller
203+
-- to define custom failure conditions. This may be useful for custom
204+
-- applications like lightning and taro or for rich error reporting.
205+
bech32EncodeResult :: Bech32Encoding -> HRP -> [Word5] -> Bech32EncodeResult
206+
bech32EncodeResult enc hrp dat =
178207
let dat' = dat ++ bech32CreateChecksum enc (T.toLower hrp) dat
179208
rest = map (charset !) dat'
180-
result = T.concat [T.toLower hrp, T.pack "1", T.pack rest]
181-
guard $ T.length result <= maxBech32Length
182-
return result
209+
encodeResult = T.concat [T.toLower hrp, T.pack "1", T.pack rest]
210+
encodeValidHrp = checkHRP hrp
211+
encodeValidLength = encodeResult `T.compareLength` maxBech32Length /= GT
212+
in Bech32EncodeResult{encodeResult, encodeValidHrp, encodeValidLength}
183213

184214

185215
-- | Check that human-readable part is valid for a 'Bech32' string.
@@ -193,19 +223,63 @@ checkHRP hrp =
193223
-- string of five-bit words.
194224
bech32Decode :: Bech32 -> Maybe (Bech32Encoding, HRP, [Word5])
195225
bech32Decode bech32 = do
196-
guard $ T.length bech32 <= maxBech32Length
197-
guard $ T.toUpper bech32 == bech32 || lowerBech32 == bech32
198-
let (hrp, dat) = T.breakOnEnd "1" lowerBech32
199-
guard $ T.length dat >= 6
200-
hrp' <- T.stripSuffix "1" hrp
201-
guard $ checkHRP hrp'
202-
dat' <- mapM charsetMap $ T.unpack dat
203-
enc <- bech32VerifyChecksum hrp' dat'
204-
return (enc, hrp', take (T.length dat - 6) dat')
226+
Bech32DecodeResult
227+
{ decodeValidChecksum = Just enc
228+
, decodeValidHrp = Just hrp
229+
, decodeResult = Just words
230+
, decodeValidLength = True
231+
, decodeValidCase = True
232+
, decodeValidDataLength = True
233+
} <-
234+
pure $ bech32DecodeResult bech32
235+
return (enc, hrp, words)
236+
237+
238+
-- | Decode human-readable 'Bech32' string into a human-readable part and a
239+
-- string of five-bit words. This is similar to 'bech32Encode', but allows the
240+
-- caller to define custom failure conditions. This may be useful for custom
241+
-- applications like lightning and taro or rich error reporting.
242+
bech32DecodeResult :: Bech32 -> Bech32DecodeResult
243+
bech32DecodeResult bech32 =
244+
let decodeValidLength = bech32 `T.compareLength` maxBech32Length /= GT
245+
decodeValidCase = T.toUpper bech32 == bech32 || lowerBech32 == bech32
246+
(hrp, dat) = T.breakOnEnd "1" lowerBech32
247+
decodeValidDataLength = dat `T.compareLength` 6 /= LT
248+
decodeValidHrp = do
249+
hrp' <- T.stripSuffix "1" hrp
250+
guard $ checkHRP hrp'
251+
return hrp'
252+
decodeValidDataPart = mapM charsetMap $ T.unpack dat
253+
decodeValidChecksum =
254+
join $
255+
bech32VerifyChecksum
256+
<$> decodeValidHrp
257+
<*> decodeValidDataPart
258+
decodeResult = take (T.length dat - 6) <$> decodeValidDataPart
259+
in Bech32DecodeResult
260+
{ decodeValidChecksum
261+
, decodeValidHrp
262+
, decodeResult
263+
, decodeValidLength
264+
, decodeValidCase
265+
, decodeValidDataLength
266+
}
205267
where
206268
lowerBech32 = T.toLower bech32
207269

208270

271+
-- | The result of decoding a 'Bech32' string
272+
data Bech32DecodeResult = Bech32DecodeResult
273+
{ decodeValidChecksum :: Maybe Bech32Encoding
274+
, decodeValidHrp :: Maybe HRP
275+
, decodeResult :: Maybe [Word5]
276+
, decodeValidLength :: Bool
277+
, decodeValidCase :: Bool
278+
, decodeValidDataLength :: Bool
279+
}
280+
deriving (Show, Eq)
281+
282+
209283
type Pad f = Int -> Int -> Word -> [[Word]] -> f [[Word]]
210284

211285

0 commit comments

Comments
 (0)