{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}

module Cardano.CLI.Types.Errors.GovernanceVoteCmdError where

import           Cardano.Api.Shelley

import           Cardano.Binary (DecoderError)
import           Cardano.CLI.Read (VoteError)

import qualified Data.Text.Lazy.Builder as TL
import qualified Formatting.Buildable as B

data GovernanceVoteCmdError
  = GovernanceVoteCmdReadVerificationKeyError !(FileError InputDecodeError)
  | GovernanceVoteCmdReadVoteFileError !VoteError
  | GovernanceVoteCmdCredentialDecodeError !DecoderError
  | GovernanceVoteCmdWriteError !(FileError ())
  | GovernanceVoteCmdReadVoteTextError !VoteError
  deriving Int -> GovernanceVoteCmdError -> ShowS
[GovernanceVoteCmdError] -> ShowS
GovernanceVoteCmdError -> String
(Int -> GovernanceVoteCmdError -> ShowS)
-> (GovernanceVoteCmdError -> String)
-> ([GovernanceVoteCmdError] -> ShowS)
-> Show GovernanceVoteCmdError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GovernanceVoteCmdError -> ShowS
showsPrec :: Int -> GovernanceVoteCmdError -> ShowS
$cshow :: GovernanceVoteCmdError -> String
show :: GovernanceVoteCmdError -> String
$cshowList :: [GovernanceVoteCmdError] -> ShowS
showList :: [GovernanceVoteCmdError] -> ShowS
Show

instance Error GovernanceVoteCmdError where
  prettyError :: forall ann. GovernanceVoteCmdError -> Doc ann
prettyError = \case
    GovernanceVoteCmdReadVerificationKeyError FileError InputDecodeError
e ->
      Doc ann
"Cannot read verification key: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> FileError InputDecodeError -> Doc ann
forall e ann. Error e => e -> Doc ann
forall ann. FileError InputDecodeError -> Doc ann
prettyError FileError InputDecodeError
e
    GovernanceVoteCmdReadVoteFileError VoteError
e ->
      Doc ann
"Cannot read vote file: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> VoteError -> Doc ann
forall e ann. Error e => e -> Doc ann
forall ann. VoteError -> Doc ann
prettyError VoteError
e
    GovernanceVoteCmdCredentialDecodeError DecoderError
e ->
      Doc ann
"Cannot decode voting credential: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> DecoderError -> Doc ann
forall {ann}. DecoderError -> Doc ann
renderDecoderError DecoderError
e
    GovernanceVoteCmdWriteError FileError ()
e ->
      Doc ann
"Cannot write vote: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> FileError () -> Doc ann
forall e ann. Error e => e -> Doc ann
forall ann. FileError () -> Doc ann
prettyError FileError ()
e
    GovernanceVoteCmdReadVoteTextError VoteError
e ->
      Doc ann
"Cannot read vote text: " Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> VoteError -> Doc ann
forall e ann. Error e => e -> Doc ann
forall ann. VoteError -> Doc ann
prettyError VoteError
e
   where
    renderDecoderError :: DecoderError -> Doc ann
renderDecoderError = Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Text -> Doc ann
pretty (Text -> Doc ann)
-> (DecoderError -> Text) -> DecoderError -> Doc ann
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TL.toLazyText (Builder -> Text)
-> (DecoderError -> Builder) -> DecoderError -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DecoderError -> Builder
forall p. Buildable p => p -> Builder
B.build