{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Cardano.CLI.EraBased.Run.Governance.Vote
( runGovernanceVoteCmds
)
where
import Cardano.Api
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley
import qualified Cardano.CLI.EraBased.Commands.Governance.Vote as Cmd
import Cardano.CLI.Read (readSingleVote)
import Cardano.CLI.Run.Hash (carryHashChecks)
import Cardano.CLI.Types.Common
import Cardano.CLI.Types.Errors.CmdError
import Cardano.CLI.Types.Errors.GovernanceVoteCmdError
import Cardano.CLI.Types.Governance
import Cardano.CLI.Types.Key
import Data.Aeson.Encode.Pretty
import Data.Function
import qualified Data.Yaml.Pretty as Yaml
runGovernanceVoteCmds
:: ()
=> Cmd.GovernanceVoteCmds era
-> ExceptT CmdError IO ()
runGovernanceVoteCmds :: forall era. GovernanceVoteCmds era -> ExceptT CmdError IO ()
runGovernanceVoteCmds = \case
Cmd.GovernanceVoteCreateCmd GovernanceVoteCreateCmdArgs era
args ->
GovernanceVoteCreateCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
forall era.
GovernanceVoteCreateCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
runGovernanceVoteCreateCmd GovernanceVoteCreateCmdArgs era
args
ExceptT GovernanceVoteCmdError IO ()
-> (ExceptT GovernanceVoteCmdError IO () -> ExceptT CmdError IO ())
-> ExceptT CmdError IO ()
forall a b. a -> (a -> b) -> b
& (GovernanceVoteCmdError -> CmdError)
-> ExceptT GovernanceVoteCmdError IO () -> ExceptT CmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT GovernanceVoteCmdError -> CmdError
CmdGovernanceVoteError
Cmd.GovernanceVoteViewCmd GovernanceVoteViewCmdArgs era
args ->
GovernanceVoteViewCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
forall era.
GovernanceVoteViewCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
runGovernanceVoteViewCmd GovernanceVoteViewCmdArgs era
args
ExceptT GovernanceVoteCmdError IO ()
-> (ExceptT GovernanceVoteCmdError IO () -> ExceptT CmdError IO ())
-> ExceptT CmdError IO ()
forall a b. a -> (a -> b) -> b
& (GovernanceVoteCmdError -> CmdError)
-> ExceptT GovernanceVoteCmdError IO () -> ExceptT CmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT GovernanceVoteCmdError -> CmdError
CmdGovernanceVoteError
runGovernanceVoteCreateCmd
:: ()
=> Cmd.GovernanceVoteCreateCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
runGovernanceVoteCreateCmd :: forall era.
GovernanceVoteCreateCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
runGovernanceVoteCreateCmd
Cmd.GovernanceVoteCreateCmdArgs
{ ConwayEraOnwards era
eon :: ConwayEraOnwards era
eon :: forall era. GovernanceVoteCreateCmdArgs era -> ConwayEraOnwards era
eon
, Vote
voteChoice :: Vote
voteChoice :: forall era. GovernanceVoteCreateCmdArgs era -> Vote
voteChoice
, (TxId, Word16)
governanceAction :: (TxId, Word16)
governanceAction :: forall era. GovernanceVoteCreateCmdArgs era -> (TxId, Word16)
governanceAction
, AnyVotingStakeVerificationKeyOrHashOrFile
votingStakeCredentialSource :: AnyVotingStakeVerificationKeyOrHashOrFile
votingStakeCredentialSource :: forall era.
GovernanceVoteCreateCmdArgs era
-> AnyVotingStakeVerificationKeyOrHashOrFile
votingStakeCredentialSource
, Maybe
(PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))
mAnchor :: Maybe
(PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))
mAnchor :: forall era.
GovernanceVoteCreateCmdArgs era
-> Maybe
(PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))
mAnchor
, VoteFile 'Out
outFile :: VoteFile 'Out
outFile :: forall era. GovernanceVoteCreateCmdArgs era -> VoteFile 'Out
outFile
} = do
let (TxId
govActionTxId, Word16
govActionIndex) = (TxId, Word16)
governanceAction
sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
conwayEraOnwardsToShelleyBasedEra ConwayEraOnwards era
eon
mAnchor' :: Maybe (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
mAnchor' =
(PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)
-> PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
-> Maybe
(PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))
-> Maybe (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
( \pca :: PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)
pca@PotentiallyCheckedAnchor{pcaAnchor :: forall anchorType anchor.
PotentiallyCheckedAnchor anchorType anchor -> anchor
pcaAnchor = (VoteUrl Url
url, SafeHash StandardCrypto AnchorData
voteHash)} ->
PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)
pca{pcaAnchor = L.Anchor{L.anchorUrl = url, L.anchorDataHash = voteHash}}
)
Maybe
(PotentiallyCheckedAnchor
VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))
mAnchor
(PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto)
-> ExceptT GovernanceVoteCmdError IO ())
-> Maybe (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
-> ExceptT GovernanceVoteCmdError IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
((HashCheckError -> GovernanceVoteCmdError)
-> ExceptT HashCheckError IO ()
-> ExceptT GovernanceVoteCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
withExceptT HashCheckError -> GovernanceVoteCmdError
GovernanceVoteCmdResignationCertHashCheckError (ExceptT HashCheckError IO ()
-> ExceptT GovernanceVoteCmdError IO ())
-> (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto)
-> ExceptT HashCheckError IO ())
-> PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto)
-> ExceptT GovernanceVoteCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto)
-> ExceptT HashCheckError IO ()
forall anchorType.
PotentiallyCheckedAnchor anchorType (Anchor StandardCrypto)
-> ExceptT HashCheckError IO ()
carryHashChecks)
Maybe (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
mAnchor'
VotingProcedure era
voteProcedure <- case Maybe (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
mAnchor' of
Maybe (PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto))
Nothing -> VotingProcedure era
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era)
forall a. a -> ExceptT GovernanceVoteCmdError IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VotingProcedure era
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era))
-> VotingProcedure era
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era)
forall a b. (a -> b) -> a -> b
$ ConwayEraOnwards era
-> Vote -> Maybe (Url, Text) -> VotingProcedure era
forall era.
ConwayEraOnwards era
-> Vote -> Maybe (Url, Text) -> VotingProcedure era
createVotingProcedure ConwayEraOnwards era
eon Vote
voteChoice Maybe (Url, Text)
forall a. Maybe a
Nothing
Just PotentiallyCheckedAnchor VoteUrl (Anchor StandardCrypto)
voteAnchor ->
ShelleyBasedEra era
-> (ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO (VotingProcedure era))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era)
forall era a.
ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
shelleyBasedEraConstraints ShelleyBasedEra era
sbe ((ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO (VotingProcedure era))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era))
-> (ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO (VotingProcedure era))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era)
forall a b. (a -> b) -> a -> b
$
let VotingProcedure VotingProcedure (ShelleyLedgerEra era)
votingProcedureWithoutAnchor = ConwayEraOnwards era
-> Vote -> Maybe (Url, Text) -> VotingProcedure era
forall era.
ConwayEraOnwards era
-> Vote -> Maybe (Url, Text) -> VotingProcedure era
createVotingProcedure ConwayEraOnwards era
eon Vote
voteChoice Maybe (Url, Text)
forall a. Maybe a
Nothing
votingProcedureWithAnchor :: VotingProcedure era
votingProcedureWithAnchor = VotingProcedure (ShelleyLedgerEra era) -> VotingProcedure era
forall era.
VotingProcedure (ShelleyLedgerEra era) -> VotingProcedure era
VotingProcedure (VotingProcedure (ShelleyLedgerEra era) -> VotingProcedure era)
-> VotingProcedure (ShelleyLedgerEra era) -> VotingProcedure era
forall a b. (a -> b) -> a -> b
$ VotingProcedure (ShelleyLedgerEra era)
votingProcedureWithoutAnchor{L.vProcAnchor = L.SJust (pcaAnchor voteAnchor)}
in VotingProcedure era
-> ExceptT GovernanceVoteCmdError IO (VotingProcedure era)
forall a. a -> ExceptT GovernanceVoteCmdError IO a
forall (m :: * -> *) a. Monad m => a -> m a
return VotingProcedure era
votingProcedureWithAnchor
ShelleyBasedEra era
-> (ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO ())
-> ExceptT GovernanceVoteCmdError IO ()
forall era a.
ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
shelleyBasedEraConstraints ShelleyBasedEra era
sbe ((ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO ())
-> ExceptT GovernanceVoteCmdError IO ())
-> (ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO ())
-> ExceptT GovernanceVoteCmdError IO ()
forall a b. (a -> b) -> a -> b
$ do
Voter StandardCrypto
voter <- (FileError InputDecodeError -> GovernanceVoteCmdError)
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
-> ExceptT GovernanceVoteCmdError IO (Voter StandardCrypto)
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError InputDecodeError -> GovernanceVoteCmdError
GovernanceVoteCmdReadVerificationKeyError (ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
-> ExceptT GovernanceVoteCmdError IO (Voter StandardCrypto))
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
-> ExceptT GovernanceVoteCmdError IO (Voter StandardCrypto)
forall a b. (a -> b) -> a -> b
$ case AnyVotingStakeVerificationKeyOrHashOrFile
votingStakeCredentialSource of
AnyDRepVerificationKeyOrHashOrFileOrScriptHash VerificationKeyOrHashOrFileOrScriptHash DRepKey
stake -> do
Credential 'DRepRole StandardCrypto
drepCred <- AsType DRepKey
-> (Hash DRepKey -> KeyHash 'DRepRole StandardCrypto)
-> VerificationKeyOrHashOrFileOrScriptHash DRepKey
-> ExceptT
(FileError InputDecodeError)
IO
(Credential 'DRepRole StandardCrypto)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) keyrole
(kr :: KeyRole).
(MonadIOTransError (FileError InputDecodeError) t m,
Key keyrole) =>
AsType keyrole
-> (Hash keyrole -> KeyHash kr StandardCrypto)
-> VerificationKeyOrHashOrFileOrScriptHash keyrole
-> t m (Credential kr StandardCrypto)
readVerificationKeyOrHashOrFileOrScriptHash AsType DRepKey
AsDRepKey Hash DRepKey -> KeyHash 'DRepRole StandardCrypto
unDRepKeyHash VerificationKeyOrHashOrFileOrScriptHash DRepKey
stake
Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
forall a. a -> ExceptT (FileError InputDecodeError) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto))
-> Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
forall a b. (a -> b) -> a -> b
$ Credential 'DRepRole StandardCrypto -> Voter StandardCrypto
forall c. Credential 'DRepRole c -> Voter c
L.DRepVoter Credential 'DRepRole StandardCrypto
drepCred
AnyStakePoolVerificationKeyOrHashOrFile VerificationKeyOrHashOrFile StakePoolKey
stake -> do
StakePoolKeyHash KeyHash 'StakePool StandardCrypto
h <- AsType StakePoolKey
-> VerificationKeyOrHashOrFile StakePoolKey
-> ExceptT (FileError InputDecodeError) IO (Hash StakePoolKey)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) keyrole.
(MonadIOTransError (FileError InputDecodeError) t m,
Key keyrole) =>
AsType keyrole
-> VerificationKeyOrHashOrFile keyrole -> t m (Hash keyrole)
readVerificationKeyOrHashOrTextEnvFile AsType StakePoolKey
AsStakePoolKey VerificationKeyOrHashOrFile StakePoolKey
stake
Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
forall a. a -> ExceptT (FileError InputDecodeError) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto))
-> Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
forall a b. (a -> b) -> a -> b
$ KeyHash 'StakePool StandardCrypto -> Voter StandardCrypto
forall c. KeyHash 'StakePool c -> Voter c
L.StakePoolVoter KeyHash 'StakePool StandardCrypto
h
AnyCommitteeHotVerificationKeyOrHashOrFileOrScriptHash VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey
stake -> do
Credential 'HotCommitteeRole StandardCrypto
hotCred <- AsType CommitteeHotKey
-> (Hash CommitteeHotKey
-> KeyHash 'HotCommitteeRole StandardCrypto)
-> VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey
-> ExceptT
(FileError InputDecodeError)
IO
(Credential 'HotCommitteeRole StandardCrypto)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) keyrole
(kr :: KeyRole).
(MonadIOTransError (FileError InputDecodeError) t m,
Key keyrole) =>
AsType keyrole
-> (Hash keyrole -> KeyHash kr StandardCrypto)
-> VerificationKeyOrHashOrFileOrScriptHash keyrole
-> t m (Credential kr StandardCrypto)
readVerificationKeyOrHashOrFileOrScriptHash AsType CommitteeHotKey
AsCommitteeHotKey Hash CommitteeHotKey -> KeyHash 'HotCommitteeRole StandardCrypto
unCommitteeHotKeyHash VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey
stake
Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
forall a. a -> ExceptT (FileError InputDecodeError) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto))
-> Voter StandardCrypto
-> ExceptT (FileError InputDecodeError) IO (Voter StandardCrypto)
forall a b. (a -> b) -> a -> b
$ Credential 'HotCommitteeRole StandardCrypto -> Voter StandardCrypto
forall c. Credential 'HotCommitteeRole c -> Voter c
L.CommitteeVoter Credential 'HotCommitteeRole StandardCrypto
hotCred
let govActIdentifier :: GovActionId StandardCrypto
govActIdentifier = TxId -> Word16 -> GovActionId StandardCrypto
createGovernanceActionId TxId
govActionTxId Word16
govActionIndex
votingProcedures :: VotingProcedures era
votingProcedures = ConwayEraOnwards era
-> Voter (EraCrypto (ShelleyLedgerEra era))
-> GovActionId (EraCrypto (ShelleyLedgerEra era))
-> VotingProcedure (ShelleyLedgerEra era)
-> VotingProcedures era
forall era.
ConwayEraOnwards era
-> Voter (EraCrypto (ShelleyLedgerEra era))
-> GovActionId (EraCrypto (ShelleyLedgerEra era))
-> VotingProcedure (ShelleyLedgerEra era)
-> VotingProcedures era
singletonVotingProcedures ConwayEraOnwards era
eon Voter (EraCrypto (ShelleyLedgerEra era))
Voter StandardCrypto
voter GovActionId (EraCrypto (ShelleyLedgerEra era))
GovActionId StandardCrypto
govActIdentifier (VotingProcedure era -> VotingProcedure (ShelleyLedgerEra era)
forall era.
VotingProcedure era -> VotingProcedure (ShelleyLedgerEra era)
unVotingProcedure VotingProcedure era
voteProcedure)
(FileError () -> GovernanceVoteCmdError)
-> ExceptT (FileError ()) IO ()
-> ExceptT GovernanceVoteCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> GovernanceVoteCmdError
GovernanceVoteCmdWriteError (ExceptT (FileError ()) IO ()
-> ExceptT GovernanceVoteCmdError IO ())
-> (IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> IO (Either (FileError ()) ())
-> ExceptT GovernanceVoteCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO (Either (FileError ()) ())
-> ExceptT GovernanceVoteCmdError IO ())
-> IO (Either (FileError ()) ())
-> ExceptT GovernanceVoteCmdError IO ()
forall a b. (a -> b) -> a -> b
$
VoteFile 'Out
-> Maybe TextEnvelopeDescr
-> VotingProcedures era
-> IO (Either (FileError ()) ())
forall a content.
HasTextEnvelope a =>
File content 'Out
-> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
writeFileTextEnvelope VoteFile 'Out
outFile Maybe TextEnvelopeDescr
forall a. Maybe a
Nothing VotingProcedures era
votingProcedures
runGovernanceVoteViewCmd
:: ()
=> Cmd.GovernanceVoteViewCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
runGovernanceVoteViewCmd :: forall era.
GovernanceVoteViewCmdArgs era
-> ExceptT GovernanceVoteCmdError IO ()
runGovernanceVoteViewCmd
Cmd.GovernanceVoteViewCmdArgs
{ ConwayEraOnwards era
eon :: ConwayEraOnwards era
eon :: forall era. GovernanceVoteViewCmdArgs era -> ConwayEraOnwards era
eon
, ViewOutputFormat
outFormat :: ViewOutputFormat
outFormat :: forall era. GovernanceVoteViewCmdArgs era -> ViewOutputFormat
outFormat
, VoteFile 'In
voteFile :: VoteFile 'In
voteFile :: forall era. GovernanceVoteViewCmdArgs era -> VoteFile 'In
voteFile
, Maybe (File () 'Out)
mOutFile :: Maybe (File () 'Out)
mOutFile :: forall era. GovernanceVoteViewCmdArgs era -> Maybe (File () 'Out)
mOutFile
} = do
let sbe :: ShelleyBasedEra era
sbe = ConwayEraOnwards era -> ShelleyBasedEra era
forall era. ConwayEraOnwards era -> ShelleyBasedEra era
conwayEraOnwardsToShelleyBasedEra ConwayEraOnwards era
eon
ShelleyBasedEra era
-> (ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO ())
-> ExceptT GovernanceVoteCmdError IO ()
forall era a.
ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
shelleyBasedEraConstraints ShelleyBasedEra era
sbe ((ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO ())
-> ExceptT GovernanceVoteCmdError IO ())
-> (ShelleyBasedEraConstraints era =>
ExceptT GovernanceVoteCmdError IO ())
-> ExceptT GovernanceVoteCmdError IO ()
forall a b. (a -> b) -> a -> b
$ do
VotingProcedures era
voteProcedures <-
((VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
-> VotingProcedures era)
-> ExceptT
GovernanceVoteCmdError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedures era)
forall a b.
(a -> b)
-> ExceptT GovernanceVoteCmdError IO a
-> ExceptT GovernanceVoteCmdError IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
-> VotingProcedures era
forall a b. (a, b) -> a
fst (ExceptT
GovernanceVoteCmdError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedures era))
-> (IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT
GovernanceVoteCmdError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedures era)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (VoteError -> GovernanceVoteCmdError)
-> ExceptT
VoteError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
-> ExceptT
GovernanceVoteCmdError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT VoteError -> GovernanceVoteCmdError
GovernanceVoteCmdReadVoteFileError (ExceptT
VoteError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
-> ExceptT
GovernanceVoteCmdError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> (IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT
VoteError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT
GovernanceVoteCmdError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT
VoteError
IO
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedures era))
-> IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
-> ExceptT GovernanceVoteCmdError IO (VotingProcedures era)
forall a b. (a -> b) -> a -> b
$
ConwayEraOnwards era
-> (VoteFile 'In, Maybe (ScriptWitnessFiles WitCtxStake))
-> IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
forall era.
ConwayEraOnwards era
-> (VoteFile 'In, Maybe (ScriptWitnessFiles WitCtxStake))
-> IO
(Either
VoteError
(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era)))
readSingleVote ConwayEraOnwards era
eon (VoteFile 'In
voteFile, Maybe (ScriptWitnessFiles WitCtxStake)
forall a. Maybe a
Nothing)
(FileError () -> GovernanceVoteCmdError)
-> ExceptT (FileError ()) IO ()
-> ExceptT GovernanceVoteCmdError IO ()
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT FileError () -> GovernanceVoteCmdError
GovernanceVoteCmdWriteError
(ExceptT (FileError ()) IO ()
-> ExceptT GovernanceVoteCmdError IO ())
-> (VotingProcedures era -> ExceptT (FileError ()) IO ())
-> VotingProcedures era
-> ExceptT GovernanceVoteCmdError IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ()
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT
(IO (Either (FileError ()) ()) -> ExceptT (FileError ()) IO ())
-> (VotingProcedures era -> IO (Either (FileError ()) ()))
-> VotingProcedures era
-> ExceptT (FileError ()) IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ( case ViewOutputFormat
outFormat of
ViewOutputFormat
ViewOutputFormatYaml ->
Maybe (File () 'Out) -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
Maybe (File content 'Out)
-> ByteString -> m (Either (FileError e) ())
writeByteStringOutput Maybe (File () 'Out)
mOutFile
(ByteString -> IO (Either (FileError ()) ()))
-> (VotingProcedures (ShelleyLedgerEra era) -> ByteString)
-> VotingProcedures (ShelleyLedgerEra era)
-> IO (Either (FileError ()) ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> VotingProcedures (ShelleyLedgerEra era) -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
Yaml.encodePretty
((Text -> Text -> Ordering) -> Config -> Config
Yaml.setConfCompare Text -> Text -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Config
Yaml.defConfig)
ViewOutputFormat
ViewOutputFormatJson ->
Maybe (File () 'Out) -> ByteString -> IO (Either (FileError ()) ())
forall (m :: * -> *) content e.
MonadIO m =>
Maybe (File content 'Out)
-> ByteString -> m (Either (FileError e) ())
writeLazyByteStringOutput Maybe (File () 'Out)
mOutFile
(ByteString -> IO (Either (FileError ()) ()))
-> (VotingProcedures (ShelleyLedgerEra era) -> ByteString)
-> VotingProcedures (ShelleyLedgerEra era)
-> IO (Either (FileError ()) ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> VotingProcedures (ShelleyLedgerEra era) -> ByteString
forall a. ToJSON a => Config -> a -> ByteString
encodePretty'
(Config
defConfig{confCompare = compare})
)
(VotingProcedures (ShelleyLedgerEra era)
-> IO (Either (FileError ()) ()))
-> (VotingProcedures era
-> VotingProcedures (ShelleyLedgerEra era))
-> VotingProcedures era
-> IO (Either (FileError ()) ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. VotingProcedures era -> VotingProcedures (ShelleyLedgerEra era)
forall era.
VotingProcedures era -> VotingProcedures (ShelleyLedgerEra era)
unVotingProcedures
(VotingProcedures era -> ExceptT GovernanceVoteCmdError IO ())
-> VotingProcedures era -> ExceptT GovernanceVoteCmdError IO ()
forall a b. (a -> b) -> a -> b
$ VotingProcedures era
voteProcedures