{-# LANGUAGE OverloadedStrings #-}
module Bcc.Api.TxSubmit.ErrorRender
( renderApplyMempoolPayloadErr
) where
import Bcc.Chain.Cole.API (ApplyMempoolPayloadErr (..))
import Bcc.Chain.UTxO.UTxO (UTxOError (..))
import Bcc.Chain.UTxO.Validation (TxValidationError (..), UTxOValidationError (..))
import Bcc.Prelude hiding ((%))
import qualified Data.Text as Text
import Formatting (build, sformat, stext, (%))
renderApplyMempoolPayloadErr :: ApplyMempoolPayloadErr -> Text
renderApplyMempoolPayloadErr :: ApplyMempoolPayloadErr -> Text
renderApplyMempoolPayloadErr ApplyMempoolPayloadErr
err =
case ApplyMempoolPayloadErr
err of
MempoolTxErr UTxOValidationError
ve -> UTxOValidationError -> Text
renderValidationError UTxOValidationError
ve
MempoolDlgErr {} -> Text
"Delegation error"
MempoolUpdateProposalErr {} -> Text
"Update proposal error"
MempoolUpdateVoteErr {} -> Text
"Update vote error"
renderValidationError :: UTxOValidationError -> Text
renderValidationError :: UTxOValidationError -> Text
renderValidationError UTxOValidationError
ve =
case UTxOValidationError
ve of
UTxOValidationTxValidationError TxValidationError
tve -> TxValidationError -> Text
renderTxValidationError TxValidationError
tve
UTxOValidationUTxOError UTxOError
ue -> UTxOError -> Text
renderUTxOError UTxOError
ue
renderTxValidationError :: TxValidationError -> Text
renderTxValidationError :: TxValidationError -> Text
renderTxValidationError TxValidationError
tve =
Text
"Tx Validation: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
case TxValidationError
tve of
TxValidationEntropicError Text
txt EntropicError
e ->
Format Text (Text -> EntropicError -> Text)
-> Text -> EntropicError -> Text
forall a. Format Text a -> a
sformat (Format
(Text -> EntropicError -> Text) (Text -> EntropicError -> Text)
"Entropic error "Format
(Text -> EntropicError -> Text) (Text -> EntropicError -> Text)
-> Format Text (Text -> EntropicError -> Text)
-> Format Text (Text -> EntropicError -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (EntropicError -> Text) (Text -> EntropicError -> Text)
forall r. Format r (Text -> r)
stext Format (EntropicError -> Text) (Text -> EntropicError -> Text)
-> Format Text (EntropicError -> Text)
-> Format Text (Text -> EntropicError -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format (EntropicError -> Text) (EntropicError -> Text)
": "Format (EntropicError -> Text) (EntropicError -> Text)
-> Format Text (EntropicError -> Text)
-> Format Text (EntropicError -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (EntropicError -> Text)
forall a r. Buildable a => Format r (a -> r)
build) Text
txt EntropicError
e
TxValidationFeeTooSmall Tx
tx Entropic
expected Entropic
actual ->
Format Text (Tx -> Entropic -> Entropic -> Text)
-> Tx -> Entropic -> Entropic -> Text
forall a. Format Text a -> a
sformat (Format
(Tx -> Entropic -> Entropic -> Text)
(Tx -> Entropic -> Entropic -> Text)
"Tx "Format
(Tx -> Entropic -> Entropic -> Text)
(Tx -> Entropic -> Entropic -> Text)
-> Format Text (Tx -> Entropic -> Entropic -> Text)
-> Format Text (Tx -> Entropic -> Entropic -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format
(Entropic -> Entropic -> Text) (Tx -> Entropic -> Entropic -> Text)
forall a r. Buildable a => Format r (a -> r)
build Format
(Entropic -> Entropic -> Text) (Tx -> Entropic -> Entropic -> Text)
-> Format Text (Entropic -> Entropic -> Text)
-> Format Text (Tx -> Entropic -> Entropic -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format
(Entropic -> Entropic -> Text) (Entropic -> Entropic -> Text)
" fee "Format
(Entropic -> Entropic -> Text) (Entropic -> Entropic -> Text)
-> Format Text (Entropic -> Entropic -> Text)
-> Format Text (Entropic -> Entropic -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (Entropic -> Text) (Entropic -> Entropic -> Text)
forall a r. Buildable a => Format r (a -> r)
build Format (Entropic -> Text) (Entropic -> Entropic -> Text)
-> Format Text (Entropic -> Text)
-> Format Text (Entropic -> Entropic -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format (Entropic -> Text) (Entropic -> Text)
"too low, expected "Format (Entropic -> Text) (Entropic -> Text)
-> Format Text (Entropic -> Text) -> Format Text (Entropic -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (Entropic -> Text)
forall a r. Buildable a => Format r (a -> r)
build) Tx
tx Entropic
actual Entropic
expected
TxValidationWitnessWrongSignature TxInWitness
wit ProtocolMagicId
pmid TxSigData
sig ->
Format Text (TxInWitness -> Text -> Text -> Text)
-> TxInWitness -> Text -> Text -> Text
forall a. Format Text a -> a
sformat (Format
(TxInWitness -> Text -> Text -> Text)
(TxInWitness -> Text -> Text -> Text)
"Bad witness "Format
(TxInWitness -> Text -> Text -> Text)
(TxInWitness -> Text -> Text -> Text)
-> Format Text (TxInWitness -> Text -> Text -> Text)
-> Format Text (TxInWitness -> Text -> Text -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (Text -> Text -> Text) (TxInWitness -> Text -> Text -> Text)
forall a r. Buildable a => Format r (a -> r)
build Format (Text -> Text -> Text) (TxInWitness -> Text -> Text -> Text)
-> Format Text (Text -> Text -> Text)
-> Format Text (TxInWitness -> Text -> Text -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format (Text -> Text -> Text) (Text -> Text -> Text)
" for signature "Format (Text -> Text -> Text) (Text -> Text -> Text)
-> Format Text (Text -> Text -> Text)
-> Format Text (Text -> Text -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (Text -> Text) (Text -> Text -> Text)
forall r. Format r (Text -> r)
stext Format (Text -> Text) (Text -> Text -> Text)
-> Format Text (Text -> Text) -> Format Text (Text -> Text -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format (Text -> Text) (Text -> Text)
" protocol magic id "Format (Text -> Text) (Text -> Text)
-> Format Text (Text -> Text) -> Format Text (Text -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (Text -> Text)
forall r. Format r (Text -> r)
stext) TxInWitness
wit (TxSigData -> Text
forall a. Show a => a -> Text
textShow TxSigData
sig) (ProtocolMagicId -> Text
forall a. Show a => a -> Text
textShow ProtocolMagicId
pmid)
TxValidationWitnessWrongKey TxInWitness
wit Address
addr ->
Format Text (TxInWitness -> Address -> Text)
-> TxInWitness -> Address -> Text
forall a. Format Text a -> a
sformat (Format
(TxInWitness -> Address -> Text) (TxInWitness -> Address -> Text)
"Bad witness "Format
(TxInWitness -> Address -> Text) (TxInWitness -> Address -> Text)
-> Format Text (TxInWitness -> Address -> Text)
-> Format Text (TxInWitness -> Address -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format (Address -> Text) (TxInWitness -> Address -> Text)
forall a r. Buildable a => Format r (a -> r)
build Format (Address -> Text) (TxInWitness -> Address -> Text)
-> Format Text (Address -> Text)
-> Format Text (TxInWitness -> Address -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format (Address -> Text) (Address -> Text)
" for address "Format (Address -> Text) (Address -> Text)
-> Format Text (Address -> Text) -> Format Text (Address -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (Address -> Text)
forall a r. Buildable a => Format r (a -> r)
build) TxInWitness
wit Address
addr
TxValidationMissingInput TxIn
tx ->
Format Text (TxIn -> Text) -> TxIn -> Text
forall a. Format Text a -> a
sformat (Format (TxIn -> Text) (TxIn -> Text)
"Validation cannot find input tx "Format (TxIn -> Text) (TxIn -> Text)
-> Format Text (TxIn -> Text) -> Format Text (TxIn -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (TxIn -> Text)
forall a r. Buildable a => Format r (a -> r)
build) TxIn
tx
TxValidationNetworkMagicMismatch NetworkMagic
expected NetworkMagic
actual ->
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"Bad network magic ", NetworkMagic -> Text
forall a. Show a => a -> Text
textShow NetworkMagic
actual, Text
", expected ", NetworkMagic -> Text
forall a. Show a => a -> Text
textShow NetworkMagic
expected ]
TxValidationTxTooLarge Natural
expected Natural
actual ->
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"Tx is ", Natural -> Text
forall a. Show a => a -> Text
textShow Natural
actual, Text
" bytes, but expected < ", Natural -> Text
forall a. Show a => a -> Text
textShow Natural
expected, Text
" bytes" ]
TxValidationError
TxValidationUnknownAddressAttributes ->
Text
"Unknown address attributes"
TxValidationError
TxValidationUnknownAttributes ->
Text
"Unknown attributes"
renderUTxOError :: UTxOError -> Text
renderUTxOError :: UTxOError -> Text
renderUTxOError UTxOError
ue =
Text
"UTxOError: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
case UTxOError
ue of
UTxOMissingInput TxIn
tx -> Format Text (TxIn -> Text) -> TxIn -> Text
forall a. Format Text a -> a
sformat (Format (TxIn -> Text) (TxIn -> Text)
"Lookup of tx "Format (TxIn -> Text) (TxIn -> Text)
-> Format Text (TxIn -> Text) -> Format Text (TxIn -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
% Format Text (TxIn -> Text)
forall a r. Buildable a => Format r (a -> r)
build Format Text (TxIn -> Text)
-> Format Text Text -> Format Text (TxIn -> Text)
forall r a r'. Format r a -> Format r' r -> Format r' a
%Format Text Text
" failed") TxIn
tx
UTxOError
UTxOOverlappingUnion -> Text
"Union or two overlapping UTxO sets"
textShow :: Show a => a -> Text
textShow :: a -> Text
textShow = String -> Text
Text.pack (String -> Text) -> (a -> String) -> a -> Text
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> String
forall a b. (Show a, ConvertText String b) => a -> b
show