Skip to content

Commit

Permalink
Use a richer error return type for encode.
Browse files Browse the repository at this point in the history
  • Loading branch information
jonathanknowles committed May 16, 2019
1 parent 5d49758 commit ace34cc
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 13 deletions.
35 changes: 29 additions & 6 deletions lib/bech32/src/Codec/Binary/Bech32/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,9 +19,12 @@ module Codec.Binary.Bech32.Internal
(
-- * Encoding & Decoding
encode
, EncodingError (..)
, decode
, checksumLength
, maxEncodedStringLength
, separatorLength
, encodedStringMaxLength
, encodedStringMinLength

-- * Human-Readable Parts
, HumanReadablePart
Expand Down Expand Up @@ -126,18 +129,21 @@ humanReadablePartMaxLength = 83
Encoding & Decoding
-------------------------------------------------------------------------------}

encode :: HumanReadablePart -> ByteString -> Maybe ByteString
encode :: HumanReadablePart -> ByteString -> Either EncodingError ByteString
encode hrp@(HumanReadablePart hrpBytes) payload = do
let payload5 = toBase32 (BS.unpack payload)
let payload' = payload5 ++ bech32CreateChecksum hrp payload5
let rest = map (charset Arr.!) payload'
let output = B8.map toLower hrpBytes <> B8.pack "1" <> B8.pack rest
guard (BS.length output <= maxEncodedStringLength)
guardE (BS.length output <= encodedStringMaxLength) EncodedStringTooLong
return output

data EncodingError = EncodedStringTooLong
deriving (Eq, Show)

decode :: ByteString -> Maybe (HumanReadablePart, ByteString)
decode bech32 = do
guard $ BS.length bech32 <= maxEncodedStringLength
guard $ BS.length bech32 <= encodedStringMaxLength
guard $ B8.map toUpper bech32 == bech32 || B8.map toLower bech32 == bech32
let (hrp, dat) = B8.breakEnd (== '1') $ B8.map toLower bech32
guard $ BS.length dat >= checksumLength
Expand All @@ -152,11 +158,22 @@ decode bech32 = do
checksumLength :: Int
checksumLength = 6

-- | The length of the separator portion of an encoded string, in bytes.
separatorLength :: Int
separatorLength = 1

-- | The maximum length of an encoded string, in bytes. This length includes the
-- human-readable part, the separator character, the encoded data portion,
-- and the checksum.
maxEncodedStringLength :: Int
maxEncodedStringLength = 90
encodedStringMaxLength :: Int
encodedStringMaxLength = 90

-- | The minimum length of an encoded string, in bytes. This length includes the
-- human-readable part, the separator character, the encoded data portion,
-- and the checksum.
encodedStringMinLength :: Int
encodedStringMinLength =
humanReadablePartMinLength + separatorLength + checksumLength

{-------------------------------------------------------------------------------
Character Manipulation
Expand Down Expand Up @@ -282,3 +299,9 @@ toBase256 :: [Word5] -> Maybe [Word8]
toBase256 dat =
map fromIntegral <$> convertBits (map fromWord5 dat) 5 8 noPadding

{-------------------------------------------------------------------------------
Utilities
-------------------------------------------------------------------------------}

guardE :: Bool -> e -> Either e ()
guardE b e = if b then Right () else Left e
14 changes: 7 additions & 7 deletions lib/bech32/test/Codec/Binary/Bech32Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ spec = do
-- test that re-encoding the decoded checksum results in
-- the same checksum.
let checksumEncoded = Bech32.encode resultHRP resultData
let expectedChecksum = Just $ B8.map toLower checksum
let expectedChecksum = Right $ B8.map toLower checksum
checksumEncoded `shouldBe` expectedChecksum

describe "Invalid Checksums" $ forM_ invalidChecksums $ \checksum ->
Expand All @@ -74,21 +74,21 @@ spec = do
let hrpUnpacked = "ca"
let hrpLength = length hrpUnpacked
let (Right hrp) = mkHumanReadablePart (B8.pack hrpUnpacked)
let separatorLength = 1
let maxDataLength =
Bech32.maxEncodedStringLength
- Bech32.checksumLength - separatorLength - hrpLength
Bech32.encodedStringMaxLength
- Bech32.checksumLength - Bech32.separatorLength - hrpLength
Bech32.encode hrp (BS.pack (replicate (maxDataLength + 1) 1))
`shouldSatisfy` isNothing
`shouldBe` Left Bech32.EncodedStringTooLong

it "hrp lowercased" $ do
let (Right hrp) = mkHumanReadablePart (B8.pack "HRP")
Bech32.encode hrp mempty
`shouldBe` Just (B8.pack "hrp1g9xj8m")
`shouldBe` Right (B8.pack "hrp1g9xj8m")

describe "Roundtrip (encode . decode)" $ do
it "Can perform roundtrip for valid data" $ property $ \(hrp, bytes) ->
(Bech32.encode hrp bytes >>= Bech32.decode) === Just (hrp, bytes)
(eitherToMaybe (Bech32.encode hrp bytes)
>>= Bech32.decode) === Just (hrp, bytes)

describe "Roundtrip (toBase256 . toBase32)" $ do
it "Can perform roundtrip base conversion" $ property $ \ws ->
Expand Down

0 comments on commit ace34cc

Please sign in to comment.