{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoFieldSelectors #-}

-- |
-- Module      : Haskoin.Address.CashAddr
-- Copyright   : No rights reserved
-- License     : MIT
-- Maintainer  : jprupp@protonmail.ch
-- Stability   : experimental
-- Portability : POSIX
--
-- Support for Bitcoin Cash (BCH) CashAddr format.
module Haskoin.Address.CashAddr
  ( -- * CashAddr
    CashPrefix,
    CashVersion,
    CashAddr,
    Cash32,
    cashAddrDecode,
    cashAddrEncode,
    cash32decodeType,
    cash32encodeType,
    cash32decode,
    cash32encode,
  )
where

import Control.Monad (guard)
import Data.Bits
  ( Bits
      ( shiftL,
        shiftR,
        testBit,
        xor,
        (.&.),
        (.|.)
      ),
  )
import Data.ByteString (ByteString)
import Data.ByteString qualified as B
import Data.ByteString.Char8 qualified as C
import Data.Char (ord, toLower, toUpper)
import Data.List (elemIndex, foldl')
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import Data.Word (Word64, Word8)
import Haskoin.Network.Data (Network (cashAddrPrefix))
import Haskoin.Util.Helpers (convertBits)

-- | 'CashAddr' prefix, usually shown before the colon in addresses, but sometimes
-- omitted. It is used in the checksum calculation to avoid parsing an address
-- from the wrong network.
type CashPrefix = Text

-- | 'CashAddr' version, until new address schemes appear it will be zero.
type CashVersion = Word8

-- | High level 'CashAddr' human-reabale string, with explicit or implicit prefix.
type CashAddr = Text

-- | Low level 'Cash32' is the human-readable low-level encoding used by 'CashAddr'.
-- It need not encode a valid address but any binary data.
type Cash32 = Text

-- | Symbols for encoding 'Cash32' data in human-readable strings.
charset :: String
charset :: String
charset = String
"qpzry9x8gf2tvdw0s3jn54khce6mua7l"

-- | Get the 32-bit number associated with this 'Cash32' character.
base32char :: Char -> Maybe Word8
base32char :: Char -> Maybe Word8
base32char = (Int -> Word8) -> Maybe Int -> Maybe Word8
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Maybe Int -> Maybe Word8)
-> (Char -> Maybe Int) -> Char -> Maybe Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> String -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
`elemIndex` String
charset)

-- | High-Level: decode 'CashAddr' string if it is valid for the
-- provided 'Network'. Prefix may be omitted from the string.
cashAddrDecode :: Network -> CashAddr -> Maybe (CashVersion, ByteString)
cashAddrDecode :: Network -> Text -> Maybe (Word8, ByteString)
cashAddrDecode Network
net Text
ca = do
  Text
epfx <- Network
net.cashAddrPrefix
  let (Text
cpfx, Text
cdat) = HasCallStack => Text -> Text -> (Text, Text)
Text -> Text -> (Text, Text)
T.breakOnEnd Text
":" (Text -> Text
T.toLower Text
ca)
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text -> Bool
T.null Text
cpfx Bool -> Bool -> Bool
|| HasCallStack => Text -> Text
Text -> Text
T.init Text
cpfx Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
epfx)
  (Text
dpfx, Word8
ver, ByteString
bs) <- Text -> Maybe (Text, Word8, ByteString)
cash32decodeType (Text
epfx Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cdat)
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text
dpfx Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
epfx)
  (Word8, ByteString) -> Maybe (Word8, ByteString)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word8
ver, ByteString
bs)

-- | High-Level: encode 'CashAddr' string for the provided network and hash.
-- Fails if the 'CashVersion' or length of hash 'ByteString' is invalid.
cashAddrEncode :: Network -> CashVersion -> ByteString -> Maybe CashAddr
cashAddrEncode :: Network -> Word8 -> ByteString -> Maybe Text
cashAddrEncode Network
net Word8
cv ByteString
bs = do
  Text
pfx <- Network
net.cashAddrPrefix
  Text -> Word8 -> ByteString -> Maybe Text
cash32encodeType Text
pfx Word8
cv ByteString
bs

-- | Mid-Level: decode 'CashAddr' string containing arbitrary prefix, plus a
-- version byte before the 'ByteString' that encodes type and length.
cash32decodeType :: Cash32 -> Maybe (CashPrefix, CashVersion, ByteString)
cash32decodeType :: Text -> Maybe (Text, Word8, ByteString)
cash32decodeType Text
ca' = do
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text -> Text
T.toUpper Text
ca' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
ca' Bool -> Bool -> Bool
|| Text
ca Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
ca')
  (Text
dpfx, ByteString
bs) <- Text -> Maybe (Text, ByteString)
cash32decode Text
ca
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (ByteString -> Bool
B.null ByteString
bs))
  let vb :: Word8
vb = HasCallStack => ByteString -> Word8
ByteString -> Word8
B.head ByteString
bs
      pay :: ByteString
pay = HasCallStack => ByteString -> ByteString
ByteString -> ByteString
B.tail ByteString
bs
  (Word8
ver, Int
len) <- Word8 -> Maybe (Word8, Int)
decodeVersionByte Word8
vb
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (ByteString -> Int
B.length ByteString
pay Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len)
  (Text, Word8, ByteString) -> Maybe (Text, Word8, ByteString)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
dpfx, Word8
ver, ByteString
pay)
  where
    ca :: Text
ca = Text -> Text
T.toLower Text
ca'

-- | Mid-Level: encode 'CashAddr' string containing arbitrary prefix and
-- 'CashVersion'. Length must be among those allowed by the standard.
cash32encodeType :: CashPrefix -> CashVersion -> ByteString -> Maybe Cash32
cash32encodeType :: Text -> Word8 -> ByteString -> Maybe Text
cash32encodeType Text
pfx Word8
cv ByteString
bs = do
  let len :: Int
len = ByteString -> Int
B.length ByteString
bs
  Word8
vb <- Word8 -> Int -> Maybe Word8
encodeVersionByte Word8
cv Int
len
  let pl :: ByteString
pl = Word8
vb Word8 -> ByteString -> ByteString
`B.cons` ByteString
bs
  Text -> Maybe Text
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ByteString -> Text
cash32encode Text
pfx ByteString
pl)

-- | Low-Level: decode 'Cash32' string. 'CashPrefix' must be part of the string.
-- No version or hash length validation is performed.
cash32decode :: Cash32 -> Maybe (CashPrefix, ByteString)
cash32decode :: Text -> Maybe (Text, ByteString)
cash32decode Text
text = do
  let bs :: ByteString
bs = (Char -> Char) -> ByteString -> ByteString
C.map Char -> Char
toLower ByteString
bs'
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard ((Char -> Char) -> ByteString -> ByteString
C.map Char -> Char
toUpper ByteString
bs' ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bs' Bool -> Bool -> Bool
|| ByteString
bs ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bs')
  let (ByteString
pfx', ByteString
dat) = (Char -> Bool) -> ByteString -> (ByteString, ByteString)
C.breakEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') ByteString
bs
  ByteString
pfx <-
    if ByteString -> Bool
B.null ByteString
pfx' Bool -> Bool -> Bool
|| ByteString
pfx' ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> ByteString
C.singleton Char
':'
      then Maybe ByteString
forall a. Maybe a
Nothing
      else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (HasCallStack => ByteString -> ByteString
ByteString -> ByteString
B.init ByteString
pfx')
  ByteString
b32 <- [Word8] -> ByteString
B.pack ([Word8] -> ByteString) -> Maybe [Word8] -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Char -> Maybe Word8) -> String -> Maybe [Word8]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Char -> Maybe Word8
base32char (ByteString -> String
C.unpack ByteString
dat)
  let px :: ByteString
px = (Word8 -> Word8) -> ByteString -> ByteString
B.map (Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x1f) ByteString
pfx
      pd :: ByteString
pd = ByteString
px ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Word8 -> ByteString
B.singleton Word8
0 ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
b32
      cs :: ByteString
cs = ByteString -> ByteString
cash32Polymod ByteString
pd
      bb :: ByteString
bb = Int -> ByteString -> ByteString
B.take (ByteString -> Int
B.length ByteString
b32 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8) ByteString
b32
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (ByteString -> Bool
verifyCash32Polymod ByteString
cs)
  let out :: ByteString
out = ByteString -> ByteString
toBase256 ByteString
bb
  (Text, ByteString) -> Maybe (Text, ByteString)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Text
decodeUtf8 ByteString
pfx, ByteString
out)
  where
    bs' :: ByteString
bs' = Text -> ByteString
encodeUtf8 Text
text

-- | Low-Level: encode 'Cash32' string for 'CashPrefix' provided. Can encode
-- arbitrary data. No prefix or length validation is performed.
cash32encode :: CashPrefix -> ByteString -> Cash32
cash32encode :: Text -> ByteString -> Text
cash32encode Text
pfx ByteString
bs =
  let b32 :: ByteString
b32 = ByteString -> ByteString
toBase32 ByteString
bs
      px :: ByteString
px = (Word8 -> Word8) -> ByteString -> ByteString
B.map (Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x1f) (Text -> ByteString
encodeUtf8 Text
pfx)
      pd :: ByteString
pd = ByteString
px ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Word8 -> ByteString
B.singleton Word8
0 ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
b32 ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int -> Word8 -> ByteString
B.replicate Int
8 Word8
0
      cs :: ByteString
cs = ByteString -> ByteString
cash32Polymod ByteString
pd
      c32 :: ByteString
c32 = (Word8 -> Word8) -> ByteString -> ByteString
B.map Word8 -> Word8
f (ByteString
b32 ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
cs)
      f :: Word8 -> Word8
f = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (Word8 -> Int) -> Word8 -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord (Char -> Int) -> (Word8 -> Char) -> Word8 -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
charset String -> Int -> Char
forall a. HasCallStack => [a] -> Int -> a
!!) (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral
   in Text
pfx Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ByteString -> Text
decodeUtf8 ByteString
c32

-- | Convert base of 'ByteString' from eight bits per byte to five bits per
-- byte, adding padding as necessary.
toBase32 :: ByteString -> ByteString
toBase32 :: ByteString -> ByteString
toBase32 =
  [Word8] -> ByteString
B.pack
    ([Word8] -> ByteString)
-> (ByteString -> [Word8]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word -> Word8) -> [Word] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map Word -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    ([Word] -> [Word8])
-> (ByteString -> [Word]) -> ByteString -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Word], Bool) -> [Word]
forall a b. (a, b) -> a
fst
    (([Word], Bool) -> [Word])
-> (ByteString -> ([Word], Bool)) -> ByteString -> [Word]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int -> Int -> [Word] -> ([Word], Bool)
convertBits Bool
True Int
8 Int
5
    ([Word] -> ([Word], Bool))
-> (ByteString -> [Word]) -> ByteString -> ([Word], Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word) -> [Word8] -> [Word]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    ([Word8] -> [Word])
-> (ByteString -> [Word8]) -> ByteString -> [Word]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
B.unpack

-- | Convert base of 'ByteString' from five to eight bits per byte. Ignore
-- padding to be symmetric with respect to 'toBase32' function.
toBase256 :: ByteString -> ByteString
toBase256 :: ByteString -> ByteString
toBase256 =
  [Word8] -> ByteString
B.pack
    ([Word8] -> ByteString)
-> (ByteString -> [Word8]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word -> Word8) -> [Word] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map Word -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    ([Word] -> [Word8])
-> (ByteString -> [Word]) -> ByteString -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Word], Bool) -> [Word]
forall a b. (a, b) -> a
fst
    (([Word], Bool) -> [Word])
-> (ByteString -> ([Word], Bool)) -> ByteString -> [Word]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int -> Int -> [Word] -> ([Word], Bool)
convertBits Bool
False Int
5 Int
8
    ([Word] -> ([Word], Bool))
-> (ByteString -> [Word]) -> ByteString -> ([Word], Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word) -> [Word8] -> [Word]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral
    ([Word8] -> [Word])
-> (ByteString -> [Word8]) -> ByteString -> [Word]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
B.unpack

-- | Obtain 'CashVersion' and payload length from 'CashAddr' version byte.
decodeVersionByte :: Word8 -> Maybe (CashVersion, Int)
decodeVersionByte :: Word8 -> Maybe (Word8, Int)
decodeVersionByte Word8
vb = do
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Word8
vb Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x80 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0)
  (Word8, Int) -> Maybe (Word8, Int)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word8
ver, Int
len)
  where
    ver :: Word8
ver = Word8
vb Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftR` Int
3
    len :: Int
len = [Int]
ls [Int] -> Int -> Int
forall a. HasCallStack => [a] -> Int -> a
!! Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8
vb Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x07)
    ls :: [Int]
ls = [Int
20, Int
24, Int
28, Int
32, Int
40, Int
48, Int
56, Int
64]

-- | Encode 'CashVersion' and length into version byte. Fail if version is
-- larger than five bits, or length incorrect, since that is invalid.
encodeVersionByte :: CashVersion -> Int -> Maybe Word8
encodeVersionByte :: Word8 -> Int -> Maybe Word8
encodeVersionByte Word8
ver Int
len = do
  Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Word8
ver Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
ver Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x0f)
  Word8
l <- case Int
len of
    Int
20 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
0
    Int
24 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
1
    Int
28 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
2
    Int
32 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
3
    Int
40 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
4
    Int
48 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
5
    Int
56 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
6
    Int
64 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
7
    Int
_ -> Maybe Word8
forall a. Maybe a
Nothing
  Word8 -> Maybe Word8
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word8
ver Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftL` Int
3) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
l)

-- | Calculate or validate checksum from base32 'ByteString' (excluding prefix).
cash32Polymod :: ByteString -> ByteString
cash32Polymod :: ByteString -> ByteString
cash32Polymod ByteString
v =
  [Word8] -> ByteString
B.pack
    [Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
polymod Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` (Int
5 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
7 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i))) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x1f | Int
i <- [Int
0 .. Int
7]]
  where
    polymod :: Word64
polymod = (Word64 -> Word8 -> Word64) -> Word64 -> ByteString -> Word64
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
B.foldl' Word64 -> Word8 -> Word64
forall {p}. Integral p => Word64 -> p -> Word64
outer (Word64
1 :: Word64) ByteString
v Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
`xor` Word64
1
    outer :: Word64 -> p -> Word64
outer Word64
c p
d =
      let c0 :: Word8
c0 = (Word64 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64
c Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftR` Int
35) :: Word8)
          c' :: Word64
c' = ((Word64
c Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.&. Word64
0x07ffffffff) Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
`shiftL` Int
5) Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
`xor` p -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral p
d
       in (Word64 -> (Int, Word64) -> Word64)
-> Word64 -> [(Int, Word64)] -> Word64
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Word8 -> Word64 -> (Int, Word64) -> Word64
forall {a} {a}. (Bits a, Bits a) => a -> a -> (Int, a) -> a
inner Word8
c0) Word64
c' ([Int] -> [Word64] -> [(Int, Word64)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0 ..] [Word64]
generator)
    generator :: [Word64]
generator =
      [Word64
0x98f2bc8e61, Word64
0x79b76d99e2, Word64
0xf33e5fb3c4, Word64
0xae2eabe2a8, Word64
0x1e4f43e470]
    inner :: a -> a -> (Int, a) -> a
inner a
c0 a
c (Int
b, a
g)
      | a
c0 a -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
b = a
c a -> a -> a
forall a. Bits a => a -> a -> a
`xor` a
g
      | Bool
otherwise = a
c

-- | Validate that polymod 'ByteString' (eight bytes) is equal to zero.
verifyCash32Polymod :: ByteString -> Bool
verifyCash32Polymod :: ByteString -> Bool
verifyCash32Polymod = (ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Word8 -> ByteString
B.replicate Int
8 Word8
0)