{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cardano.Api.SerialiseBech32
( SerialiseAsBech32 (..)
, serialiseToBech32
, Bech32DecodeError (..)
, deserialiseFromBech32
, deserialiseAnyOfFromBech32
)
where
import Cardano.Api.Error
import Cardano.Api.HasTypeProxy
import Cardano.Api.Orphans ()
import Cardano.Api.Pretty
import Cardano.Api.SerialiseRaw
import Cardano.Api.Utils
import qualified Codec.Binary.Bech32 as Bech32
import Control.Monad (guard)
import Data.ByteString (ByteString)
import Data.Data (Data)
import qualified Data.List as List
import Data.Set (Set)
import Data.Text (Text)
import GHC.Exts (IsList (..))
class (HasTypeProxy a, SerialiseAsRawBytes a) => SerialiseAsBech32 a where
bech32PrefixFor :: a -> Text
bech32PrefixesPermitted :: AsType a -> [Text]
serialiseToBech32 :: SerialiseAsBech32 a => a -> Text
serialiseToBech32 :: forall a. SerialiseAsBech32 a => a -> Text
serialiseToBech32 a
a =
HumanReadablePart -> DataPart -> Text
Bech32.encodeLenient
HumanReadablePart
humanReadablePart
(ByteString -> DataPart
Bech32.dataPartFromBytes (a -> ByteString
forall a. SerialiseAsRawBytes a => a -> ByteString
serialiseToRawBytes a
a))
where
humanReadablePart :: HumanReadablePart
humanReadablePart =
case Text -> Either HumanReadablePartError HumanReadablePart
Bech32.humanReadablePartFromText (a -> Text
forall a. SerialiseAsBech32 a => a -> Text
bech32PrefixFor a
a) of
Right HumanReadablePart
p -> HumanReadablePart
p
Left HumanReadablePartError
err ->
[Char] -> HumanReadablePart
forall a. HasCallStack => [Char] -> a
error ([Char] -> HumanReadablePart) -> [Char] -> HumanReadablePart
forall a b. (a -> b) -> a -> b
$
[Char]
"serialiseToBech32: invalid prefix "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Text -> [Char]
forall a. Show a => a -> [Char]
show (a -> Text
forall a. SerialiseAsBech32 a => a -> Text
bech32PrefixFor a
a)
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
", "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ HumanReadablePartError -> [Char]
forall a. Show a => a -> [Char]
show HumanReadablePartError
err
deserialiseFromBech32
:: SerialiseAsBech32 a
=> AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 :: forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
deserialiseFromBech32 AsType a
asType Text
bech32Str = do
(HumanReadablePart
prefix, DataPart
dataPart) <-
Text -> Either DecodingError (HumanReadablePart, DataPart)
Bech32.decodeLenient Text
bech32Str
Either DecodingError (HumanReadablePart, DataPart)
-> (DecodingError -> Bech32DecodeError)
-> Either Bech32DecodeError (HumanReadablePart, DataPart)
forall e a e'. Either e a -> (e -> e') -> Either e' a
?!. DecodingError -> Bech32DecodeError
Bech32DecodingError
let actualPrefix :: Text
actualPrefix = HumanReadablePart -> Text
Bech32.humanReadablePartToText HumanReadablePart
prefix
permittedPrefixes :: [Text]
permittedPrefixes = AsType a -> [Text]
forall a. SerialiseAsBech32 a => AsType a -> [Text]
bech32PrefixesPermitted AsType a
asType
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text
actualPrefix Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
permittedPrefixes)
Maybe () -> Bech32DecodeError -> Either Bech32DecodeError ()
forall a e. Maybe a -> e -> Either e a
?! Text -> Set Text -> Bech32DecodeError
Bech32UnexpectedPrefix Text
actualPrefix ([Item (Set Text)] -> Set Text
forall l. IsList l => [Item l] -> l
fromList [Item (Set Text)]
[Text]
permittedPrefixes)
ByteString
payload <-
DataPart -> Maybe ByteString
Bech32.dataPartToBytes DataPart
dataPart
Maybe ByteString
-> Bech32DecodeError -> Either Bech32DecodeError ByteString
forall a e. Maybe a -> e -> Either e a
?! Text -> Bech32DecodeError
Bech32DataPartToBytesError (DataPart -> Text
Bech32.dataPartToText DataPart
dataPart)
a
value <- case AsType a -> ByteString -> Either SerialiseAsRawBytesError a
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
deserialiseFromRawBytes AsType a
asType ByteString
payload of
Right a
a -> a -> Either Bech32DecodeError a
forall a b. b -> Either a b
Right a
a
Left SerialiseAsRawBytesError
_ -> Bech32DecodeError -> Either Bech32DecodeError a
forall a b. a -> Either a b
Left (Bech32DecodeError -> Either Bech32DecodeError a)
-> Bech32DecodeError -> Either Bech32DecodeError a
forall a b. (a -> b) -> a -> b
$ ByteString -> Bech32DecodeError
Bech32DeserialiseFromBytesError ByteString
payload
let expectedPrefix :: Text
expectedPrefix = a -> Text
forall a. SerialiseAsBech32 a => a -> Text
bech32PrefixFor a
value
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text
actualPrefix Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
expectedPrefix)
Maybe () -> Bech32DecodeError -> Either Bech32DecodeError ()
forall a e. Maybe a -> e -> Either e a
?! Text -> Text -> Bech32DecodeError
Bech32WrongPrefix Text
actualPrefix Text
expectedPrefix
a -> Either Bech32DecodeError a
forall a. a -> Either Bech32DecodeError a
forall (m :: * -> *) a. Monad m => a -> m a
return a
value
deserialiseAnyOfFromBech32
:: forall b
. [FromSomeType SerialiseAsBech32 b]
-> Text
-> Either Bech32DecodeError b
deserialiseAnyOfFromBech32 :: forall b.
[FromSomeType SerialiseAsBech32 b]
-> Text -> Either Bech32DecodeError b
deserialiseAnyOfFromBech32 [FromSomeType SerialiseAsBech32 b]
types Text
bech32Str = do
(HumanReadablePart
prefix, DataPart
dataPart) <-
Text -> Either DecodingError (HumanReadablePart, DataPart)
Bech32.decodeLenient Text
bech32Str
Either DecodingError (HumanReadablePart, DataPart)
-> (DecodingError -> Bech32DecodeError)
-> Either Bech32DecodeError (HumanReadablePart, DataPart)
forall e a e'. Either e a -> (e -> e') -> Either e' a
?!. DecodingError -> Bech32DecodeError
Bech32DecodingError
let actualPrefix :: Text
actualPrefix = HumanReadablePart -> Text
Bech32.humanReadablePartToText HumanReadablePart
prefix
FromSomeType AsType a
actualType a -> b
fromType <-
Text -> Maybe (FromSomeType SerialiseAsBech32 b)
findForPrefix Text
actualPrefix
Maybe (FromSomeType SerialiseAsBech32 b)
-> Bech32DecodeError
-> Either Bech32DecodeError (FromSomeType SerialiseAsBech32 b)
forall a e. Maybe a -> e -> Either e a
?! Text -> Set Text -> Bech32DecodeError
Bech32UnexpectedPrefix Text
actualPrefix Set Text
permittedPrefixes
ByteString
payload <-
DataPart -> Maybe ByteString
Bech32.dataPartToBytes DataPart
dataPart
Maybe ByteString
-> Bech32DecodeError -> Either Bech32DecodeError ByteString
forall a e. Maybe a -> e -> Either e a
?! Text -> Bech32DecodeError
Bech32DataPartToBytesError (DataPart -> Text
Bech32.dataPartToText DataPart
dataPart)
a
value <- case AsType a -> ByteString -> Either SerialiseAsRawBytesError a
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either SerialiseAsRawBytesError a
deserialiseFromRawBytes AsType a
actualType ByteString
payload of
Right a
a -> a -> Either Bech32DecodeError a
forall a b. b -> Either a b
Right a
a
Left SerialiseAsRawBytesError
_ -> Bech32DecodeError -> Either Bech32DecodeError a
forall a b. a -> Either a b
Left (Bech32DecodeError -> Either Bech32DecodeError a)
-> Bech32DecodeError -> Either Bech32DecodeError a
forall a b. (a -> b) -> a -> b
$ ByteString -> Bech32DecodeError
Bech32DeserialiseFromBytesError ByteString
payload
let expectedPrefix :: Text
expectedPrefix = a -> Text
forall a. SerialiseAsBech32 a => a -> Text
bech32PrefixFor a
value
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Text
actualPrefix Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
expectedPrefix)
Maybe () -> Bech32DecodeError -> Either Bech32DecodeError ()
forall a e. Maybe a -> e -> Either e a
?! Text -> Text -> Bech32DecodeError
Bech32WrongPrefix Text
actualPrefix Text
expectedPrefix
b -> Either Bech32DecodeError b
forall a. a -> Either Bech32DecodeError a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> b
fromType a
value)
where
findForPrefix
:: Text
-> Maybe (FromSomeType SerialiseAsBech32 b)
findForPrefix :: Text -> Maybe (FromSomeType SerialiseAsBech32 b)
findForPrefix Text
prefix =
(FromSomeType SerialiseAsBech32 b -> Bool)
-> [FromSomeType SerialiseAsBech32 b]
-> Maybe (FromSomeType SerialiseAsBech32 b)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
List.find
(\(FromSomeType AsType a
t a -> b
_) -> Text
prefix Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` AsType a -> [Text]
forall a. SerialiseAsBech32 a => AsType a -> [Text]
bech32PrefixesPermitted AsType a
t)
[FromSomeType SerialiseAsBech32 b]
types
permittedPrefixes :: Set Text
permittedPrefixes :: Set Text
permittedPrefixes =
[Item (Set Text)] -> Set Text
forall l. IsList l => [Item l] -> l
fromList ([Item (Set Text)] -> Set Text) -> [Item (Set Text)] -> Set Text
forall a b. (a -> b) -> a -> b
$
[[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ AsType a -> [Text]
forall a. SerialiseAsBech32 a => AsType a -> [Text]
bech32PrefixesPermitted AsType a
ttoken
| FromSomeType AsType a
ttoken a -> b
_f <- [FromSomeType SerialiseAsBech32 b]
types
]
data Bech32DecodeError
=
Bech32DecodingError !Bech32.DecodingError
|
Bech32UnexpectedPrefix !Text !(Set Text)
|
Bech32DataPartToBytesError !Text
|
Bech32DeserialiseFromBytesError !ByteString
|
Bech32WrongPrefix !Text !Text
deriving (Bech32DecodeError -> Bech32DecodeError -> Bool
(Bech32DecodeError -> Bech32DecodeError -> Bool)
-> (Bech32DecodeError -> Bech32DecodeError -> Bool)
-> Eq Bech32DecodeError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Bech32DecodeError -> Bech32DecodeError -> Bool
== :: Bech32DecodeError -> Bech32DecodeError -> Bool
$c/= :: Bech32DecodeError -> Bech32DecodeError -> Bool
/= :: Bech32DecodeError -> Bech32DecodeError -> Bool
Eq, Int -> Bech32DecodeError -> [Char] -> [Char]
[Bech32DecodeError] -> [Char] -> [Char]
Bech32DecodeError -> [Char]
(Int -> Bech32DecodeError -> [Char] -> [Char])
-> (Bech32DecodeError -> [Char])
-> ([Bech32DecodeError] -> [Char] -> [Char])
-> Show Bech32DecodeError
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> Bech32DecodeError -> [Char] -> [Char]
showsPrec :: Int -> Bech32DecodeError -> [Char] -> [Char]
$cshow :: Bech32DecodeError -> [Char]
show :: Bech32DecodeError -> [Char]
$cshowList :: [Bech32DecodeError] -> [Char] -> [Char]
showList :: [Bech32DecodeError] -> [Char] -> [Char]
Show, Typeable Bech32DecodeError
Typeable Bech32DecodeError =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> Bech32DecodeError
-> c Bech32DecodeError)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bech32DecodeError)
-> (Bech32DecodeError -> Constr)
-> (Bech32DecodeError -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bech32DecodeError))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Bech32DecodeError))
-> ((forall b. Data b => b -> b)
-> Bech32DecodeError -> Bech32DecodeError)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r)
-> (forall u.
(forall d. Data d => d -> u) -> Bech32DecodeError -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Bech32DecodeError -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError)
-> Data Bech32DecodeError
Bech32DecodeError -> Constr
Bech32DecodeError -> DataType
(forall b. Data b => b -> b)
-> Bech32DecodeError -> Bech32DecodeError
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> Bech32DecodeError -> u
forall u. (forall d. Data d => d -> u) -> Bech32DecodeError -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bech32DecodeError
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bech32DecodeError -> c Bech32DecodeError
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bech32DecodeError)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Bech32DecodeError)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bech32DecodeError -> c Bech32DecodeError
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Bech32DecodeError -> c Bech32DecodeError
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bech32DecodeError
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Bech32DecodeError
$ctoConstr :: Bech32DecodeError -> Constr
toConstr :: Bech32DecodeError -> Constr
$cdataTypeOf :: Bech32DecodeError -> DataType
dataTypeOf :: Bech32DecodeError -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bech32DecodeError)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Bech32DecodeError)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Bech32DecodeError)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c Bech32DecodeError)
$cgmapT :: (forall b. Data b => b -> b)
-> Bech32DecodeError -> Bech32DecodeError
gmapT :: (forall b. Data b => b -> b)
-> Bech32DecodeError -> Bech32DecodeError
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Bech32DecodeError -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Bech32DecodeError -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> Bech32DecodeError -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> Bech32DecodeError -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> Bech32DecodeError -> m Bech32DecodeError
Data)
instance Error Bech32DecodeError where
prettyError :: forall ann. Bech32DecodeError -> Doc ann
prettyError = \case
Bech32DecodingError DecodingError
decErr ->
DecodingError -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow DecodingError
decErr
Bech32UnexpectedPrefix Text
actual Set Text
permitted ->
[Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat
[ Doc ann
"Unexpected Bech32 prefix: the actual prefix is " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Text -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow Text
actual
, Doc ann
", but it was expected to be "
, [Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$ Doc ann -> [Doc ann] -> [Doc ann]
forall a. a -> [a] -> [a]
List.intersperse Doc ann
" or " ((Text -> Doc ann) -> [Text] -> [Doc ann]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow (Set Text -> [Item (Set Text)]
forall l. IsList l => l -> [Item l]
toList Set Text
permitted))
]
Bech32DataPartToBytesError Text
_dataPart ->
[Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat
[ Doc ann
"There was an error in extracting the bytes from the data part of the "
, Doc ann
"Bech32-encoded string."
]
Bech32DeserialiseFromBytesError ByteString
_bytes ->
[Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat
[ Doc ann
"There was an error in deserialising the data part of the "
, Doc ann
"Bech32-encoded string into a value of the expected type."
]
Bech32WrongPrefix Text
actual Text
expected ->
[Doc ann] -> Doc ann
forall a. Monoid a => [a] -> a
mconcat
[ Doc ann
"Mismatch in the Bech32 prefix: the actual prefix is " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Text -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow Text
actual
, Doc ann
", but the prefix for this payload value should be " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Text -> Doc ann
forall a ann. Show a => a -> Doc ann
pshow Text
expected
]