Skip to content

Commit

Permalink
Add outstanding Error instances
Browse files Browse the repository at this point in the history
  • Loading branch information
Jimbo4350 committed Feb 11, 2025
1 parent 96e5e11 commit 5a36d5d
Show file tree
Hide file tree
Showing 6 changed files with 27 additions and 3 deletions.
2 changes: 2 additions & 0 deletions cardano-cli/cardano-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,7 @@ library
Cardano.CLI.Commands.Node
Cardano.CLI.Commands.Ping
Cardano.CLI.Compatible.Commands
Cardano.CLI.Compatible.Exception
Cardano.CLI.Compatible.Governance
Cardano.CLI.Compatible.Run
Cardano.CLI.Compatible.Transaction
Expand Down Expand Up @@ -251,6 +252,7 @@ library
prettyprinter,
prettyprinter-ansi-terminal,
random,
rio,
split,
strict-stm,
text <2.1.2,
Expand Down
6 changes: 5 additions & 1 deletion cardano-cli/src/Cardano/CLI/Orphans.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
Expand All @@ -10,10 +11,13 @@ where

import Cardano.Api
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley (scriptDataToJsonDetailedSchema)
import Cardano.Api.Shelley (VotesMergingConflict, scriptDataToJsonDetailedSchema)

import Data.Aeson

instance Error (VotesMergingConflict era) where
prettyError = pretty . show

-- TODO upstream this orphaned instance to the ledger
instance (L.EraTxOut ledgerera, L.EraGov ledgerera) => ToJSON (L.NewEpochState ledgerera) where
toJSON (L.NewEpochState nesEL nesBprev nesBCur nesEs nesRu nesPd _stashedAvvm) =
Expand Down
9 changes: 9 additions & 0 deletions cardano-cli/src/Cardano/CLI/Read.hs
Original file line number Diff line number Diff line change
Expand Up @@ -717,6 +717,15 @@ data ReadWitnessSigningDataError
ReadWitnessSigningDataSigningKeyAndAddressMismatch
deriving Show

instance Error ReadWitnessSigningDataError where
prettyError = \case
ReadWitnessSigningDataSigningKeyDecodeError fileErr ->
prettyError fileErr
ReadWitnessSigningDataScriptError fileErr ->
prettyError fileErr
ReadWitnessSigningDataSigningKeyAndAddressMismatch ->
"Only a Byron signing key may be accompanied by a Byron address."

-- | Render an error message for a 'ReadWitnessSigningDataError'.
renderReadWitnessSigningDataError :: ReadWitnessSigningDataError -> Doc ann
renderReadWitnessSigningDataError = \case
Expand Down
2 changes: 1 addition & 1 deletion cardano-cli/src/Cardano/CLI/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ import Cardano.CLI.Types.Errors.NodeCmdError
import Cardano.CLI.Types.Errors.QueryCmdError
import Cardano.Git.Rev (gitRev)

import Control.Monad (forM_)
import Control.Monad
import Data.Function
import qualified Data.List as L
import Data.Text (Text)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Cardano.CLI.Types.Errors.BootstrapWitnessError
)
where

import Prettyprinter
import Cardano.Api

-- | Error constructing a Shelley bootstrap witness (i.e. a Byron key witness
-- in the Shelley era).
Expand All @@ -14,6 +14,9 @@ data BootstrapWitnessError
MissingNetworkIdOrByronAddressError
deriving Show

instance Error BootstrapWitnessError where
prettyError = renderBootstrapWitnessError

-- | Render an error message for a 'BootstrapWitnessError'.
renderBootstrapWitnessError :: BootstrapWitnessError -> Doc ann
renderBootstrapWitnessError MissingNetworkIdOrByronAddressError =
Expand Down
6 changes: 6 additions & 0 deletions cardano-cli/src/Cardano/CLI/Types/Errors/TxCmdError.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,12 @@ data TxCmdError
| TxCmdHashCheckError L.Url HashCheckError
| TxCmdUnregisteredStakeAddress !(Set StakeCredential)

instance Show TxCmdError where
show = show . renderTxCmdError

instance Error TxCmdError where
prettyError = renderTxCmdError

renderTxCmdError :: TxCmdError -> Doc ann
renderTxCmdError = \case
TxCmdProtocolParamsConverstionError err' ->
Expand Down

0 comments on commit 5a36d5d

Please sign in to comment.