Skip to content

Commit 9568077

Browse files
committed
WIP
1 parent 0826894 commit 9568077

27 files changed

+505
-40
lines changed

cardano-cli/cardano-cli.cabal

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -142,6 +142,14 @@ library
142142
Cardano.CLI.EraIndependent.Address.Info.Run
143143
Cardano.CLI.EraIndependent.Address.Option
144144
Cardano.CLI.EraIndependent.Address.Run
145+
Cardano.CLI.EraIndependent.Cip.Cip129.Command
146+
Cardano.CLI.EraIndependent.Cip.Cip129.Conversion
147+
Cardano.CLI.EraIndependent.Cip.Cip129.Options
148+
Cardano.CLI.EraIndependent.Cip.Cip129.Run
149+
Cardano.CLI.EraIndependent.Cip.Command
150+
Cardano.CLI.EraIndependent.Cip.Common
151+
Cardano.CLI.EraIndependent.Cip.Options
152+
Cardano.CLI.EraIndependent.Cip.Run
145153
Cardano.CLI.EraIndependent.Debug.CheckNodeConfiguration.Command
146154
Cardano.CLI.EraIndependent.Debug.CheckNodeConfiguration.Run
147155
Cardano.CLI.EraIndependent.Debug.Command
@@ -181,6 +189,10 @@ library
181189
Cardano.CLI.Orphan
182190
Cardano.CLI.Parser
183191
Cardano.CLI.Read
192+
Cardano.CLI.Read.Committee.ColdKey
193+
Cardano.CLI.Read.Committee.HotKey
194+
Cardano.CLI.Read.DRep
195+
Cardano.CLI.Read.GovernanceActionId
184196
Cardano.CLI.Render
185197
Cardano.CLI.Run
186198
Cardano.CLI.Run.Mnemonic
@@ -287,6 +299,7 @@ library
287299
transformers-except ^>=0.1.3,
288300
unliftio-core,
289301
utf8-string,
302+
validation,
290303
vary ^>=0.1.1.2,
291304
vector,
292305
yaml,

cardano-cli/src/Cardano/CLI/Command.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ import Cardano.CLI.Compatible.Command
1010
import Cardano.CLI.EraBased.Command
1111
import Cardano.CLI.EraBased.Query.Command
1212
import Cardano.CLI.EraIndependent.Address.Command
13+
import Cardano.CLI.EraIndependent.Cip.Command (CipFormatCmds)
1314
import Cardano.CLI.EraIndependent.Debug.Command
1415
import Cardano.CLI.EraIndependent.Hash.Command (HashCmds)
1516
import Cardano.CLI.EraIndependent.Key.Command
@@ -37,6 +38,8 @@ data ClientCommand
3738
forall era. QueryCommands (QueryCmds era)
3839
| -- | Legacy shelley-based Commands
3940
LegacyCmds LegacyCmds
41+
| -- | Miscellaneous commands
42+
CipFormatCmds CipFormatCmds
4043
| CliPingCommand PingCmd
4144
| CliDebugCmds DebugCmds
4245
| forall a. Help ParserPrefs (ParserInfo a)

cardano-cli/src/Cardano/CLI/EraBased/Common/Option.hs

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1830,12 +1830,30 @@ pFormatFlags content =
18301830
, "."
18311831
]
18321832

1833+
flagFormatBech32
1834+
:: FormatBech32 :| fs
1835+
=> Flag (Vary fs)
1836+
flagFormatBech32 =
1837+
mkFlag "output-bech32" "Bech32" FormatBech32
1838+
18331839
flagFormatCbor
18341840
:: FormatCbor :| fs
18351841
=> Flag (Vary fs)
18361842
flagFormatCbor =
18371843
mkFlag "output-cbor" "BASE16 CBOR" FormatCbor
18381844

1845+
flagFormatCip129
1846+
:: FormatCip129 :| fs
1847+
=> Flag (Vary fs)
1848+
flagFormatCip129 =
1849+
mkFlag "output-cip129" "CIP-129" FormatCip129
1850+
1851+
flagFormatHex
1852+
:: FormatHex :| fs
1853+
=> Flag (Vary fs)
1854+
flagFormatHex =
1855+
mkFlag "output-hex" "BASE16" FormatHex
1856+
18391857
flagFormatJson
18401858
:: FormatJson :| fs
18411859
=> Flag (Vary fs)
@@ -1996,6 +2014,7 @@ pKesVerificationKey =
19962014
Left err@(Bech32DataPartToBytesError _) -> Left (docToString $ prettyError err)
19972015
Left err@(Bech32DeserialiseFromBytesError _) -> Left (docToString $ prettyError err)
19982016
Left err@(Bech32WrongPrefix _ _) -> Left (docToString $ prettyError err)
2017+
Left err@(Bech32UnexpectedHeader _ _) -> Left (docToString $ prettyError err)
19992018
-- The input was not valid Bech32. Attempt to deserialise it as hex.
20002019
Left (Bech32DecodingError _) ->
20012020
first

cardano-cli/src/Cardano/CLI/EraBased/Governance/DRep/Command.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE DuplicateRecordFields #-}
3+
{-# LANGUAGE GADTs #-}
34
{-# LANGUAGE LambdaCase #-}
45

56
module Cardano.CLI.EraBased.Governance.DRep.Command
@@ -24,6 +25,8 @@ import Cardano.CLI.Type.Key
2425

2526
import Data.Text (Text)
2627

28+
import Vary (Vary)
29+
2730
data GovernanceDRepCmds era
2831
= GovernanceDRepKeyGenCmd !(GovernanceDRepKeyGenCmdArgs era)
2932
| GovernanceDRepIdCmd !(GovernanceDRepIdCmdArgs era)
@@ -43,7 +46,7 @@ data GovernanceDRepIdCmdArgs era
4346
= GovernanceDRepIdCmdArgs
4447
{ eon :: !(ConwayEraOnwards era)
4548
, vkeySource :: !(VerificationKeyOrHashOrFile DRepKey)
46-
, idOutputFormat :: !IdOutputFormat
49+
, idOutputFormat :: !(Vary [FormatHex, FormatBech32, FormatCip129])
4750
, mOutFile :: !(Maybe (File () Out))
4851
}
4952

cardano-cli/src/Cardano/CLI/EraBased/Governance/DRep/Option.hs

Lines changed: 8 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -14,12 +14,13 @@ import Cardano.Api.Shelley (Hash (DRepMetadataHash))
1414
import Cardano.CLI.EraBased.Common.Option
1515
import Cardano.CLI.EraBased.Governance.DRep.Command
1616
import Cardano.CLI.EraIndependent.Hash.Command (HashGoal (..))
17+
import Cardano.CLI.Option.Flag
1718
import Cardano.CLI.Parser
1819
import Cardano.CLI.Read
19-
import Cardano.CLI.Type.Common hiding (CheckHash)
2020

2121
import Control.Applicative (Alternative ((<|>)), optional)
2222
import Data.Foldable (asum)
23+
import Data.Function
2324
import Options.Applicative (Parser)
2425
import Options.Applicative qualified as Opt
2526

@@ -73,27 +74,16 @@ pGovernanceDRepKeyIdCmd era = do
7374
( fmap GovernanceDRepIdCmd $
7475
GovernanceDRepIdCmdArgs w
7576
<$> pDRepVerificationKeyOrHashOrFile
76-
<*> pDRepIdOutputFormat
77+
<*> pFormatFlags
78+
"drep id output"
79+
[ flagFormatHex
80+
, flagFormatBech32 & setDefault
81+
, flagFormatCip129
82+
]
7783
<*> optional pOutputFile
7884
)
7985
$ Opt.progDesc "Generate a drep id."
8086

81-
pDRepIdOutputFormat :: Parser IdOutputFormat
82-
pDRepIdOutputFormat =
83-
asum [make IdOutputFormatHex "hex", make IdOutputFormatBech32 "bech32"]
84-
<|> pure default_
85-
where
86-
default_ = IdOutputFormatBech32
87-
make format flag_ =
88-
Opt.flag' format $
89-
mconcat
90-
[ Opt.help $
91-
"Format drep id output as "
92-
<> flag_
93-
<> (if format == default_ then " (the default)." else ".")
94-
, Opt.long ("output-" <> flag_)
95-
]
96-
9787
-- Registration Certificate related
9888

9989
pRegistrationCertificateCmd

cardano-cli/src/Cardano/CLI/EraBased/Governance/DRep/Run.hs

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ where
1717

1818
import Cardano.Api
1919
import Cardano.Api.Ledger qualified as L
20+
import Cardano.Api.Shelley
2021

2122
import Cardano.CLI.EraBased.Governance.DRep.Command qualified as Cmd
2223
import Cardano.CLI.EraIndependent.Hash.Command qualified as Cmd
@@ -38,6 +39,8 @@ import Data.ByteString (ByteString)
3839
import Data.Function
3940
import Data.Text.Encoding qualified as Text
4041

42+
import Vary qualified
43+
4144
runGovernanceDRepCmds
4245
:: ()
4346
=> Cmd.GovernanceDRepCmds era
@@ -92,9 +95,18 @@ runGovernanceDRepIdCmd
9295
readVerificationKeyOrHashOrTextEnvFile AsDRepKey vkeySource
9396

9497
content <-
95-
pure $ case idOutputFormat of
96-
IdOutputFormatHex -> serialiseToRawBytesHex drepVerKeyHash
97-
IdOutputFormatBech32 -> Text.encodeUtf8 $ serialiseToBech32 drepVerKeyHash
98+
pure $
99+
idOutputFormat
100+
& ( Vary.on (\FormatHex -> serialiseToRawBytesHex drepVerKeyHash)
101+
$ Vary.on (\FormatBech32 -> Text.encodeUtf8 $ serialiseToBech32 drepVerKeyHash)
102+
$ Vary.on
103+
( \FormatCip129 ->
104+
let DRepKeyHash kh = drepVerKeyHash
105+
keyCredential = L.KeyHashObj kh
106+
in Text.encodeUtf8 $ serialiseToBech32Cip129 keyCredential
107+
)
108+
$ Vary.exhaustiveCase
109+
)
98110

99111
lift (writeByteStringOutput mOutFile content)
100112
& onLeft (left . WriteFileError)

cardano-cli/src/Cardano/CLI/EraBased/Query/Run.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ where
4242
import Cardano.Api hiding (QueryInShelleyBasedEra (..))
4343
import Cardano.Api qualified as Api
4444
import Cardano.Api.Consensus qualified as Consensus
45-
import Cardano.Api.Ledger (StandardCrypto, strictMaybeToMaybe)
45+
import Cardano.Api.Ledger (strictMaybeToMaybe)
4646
import Cardano.Api.Ledger qualified as L
4747
import Cardano.Api.Network (LedgerPeerSnapshot, Serialised (..))
4848
import Cardano.Api.Network qualified as Consensus
@@ -1118,7 +1118,7 @@ writePoolState mOutFile serialisedCurrentEpochState = do
11181118
<> Map.keysSet (L.psFutureStakePoolParams poolState)
11191119
<> Map.keysSet (L.psRetiring poolState)
11201120

1121-
let poolStates :: Map (L.KeyHash 'L.StakePool) (Params StandardCrypto)
1121+
let poolStates :: Map (L.KeyHash 'L.StakePool) Params
11221122
poolStates =
11231123
fromList $
11241124
hks

cardano-cli/src/Cardano/CLI/EraIndependent/Key/Run.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ import Cardano.Api
3737
import Cardano.Api.Byron qualified as ByronApi
3838
import Cardano.Api.Crypto.Ed25519Bip32 (xPrvFromBytes)
3939
import Cardano.Api.Ledger qualified as L
40-
import Cardano.Api.Shelley (StakePoolKey)
40+
import Cardano.Api.Shelley
4141

4242
import Cardano.CLI.Byron.Key qualified as Byron
4343
import Cardano.CLI.EraIndependent.Key.Command qualified as Cmd
@@ -205,8 +205,8 @@ runNonExtendedKeyCmd
205205
vk@AGenesisUTxOVerificationKey{} -> goFail vk
206206
vk@AKesVerificationKey{} -> goFail vk
207207
vk@AVrfVerificationKey{} -> goFail vk
208-
vk@AStakeVerificationKey{} -> goFail vk
209208
vk@AStakePoolVerificationKey{} -> goFail vk
209+
vk@AStakeVerificationKey{} -> goFail vk
210210
vk@ADRepVerificationKey{} -> goFail vk
211211
vk@ACommitteeColdVerificationKey{} -> goFail vk
212212
vk@ACommitteeHotVerificationKey{} -> goFail vk
@@ -245,18 +245,18 @@ readExtendedVerificationKeyFile evkfile = do
245245
k@ADRepExtendedVerificationKey{} -> return k
246246
k@ACommitteeColdExtendedVerificationKey{} -> return k
247247
k@ACommitteeHotExtendedVerificationKey{} -> return k
248+
k@AStakePoolExtendedVerificationKey{} -> return k
248249
k@AStakeExtendedVerificationKey{} -> return k
249250
k@AGenesisExtendedVerificationKey{} -> return k
250251
k@AGenesisDelegateExtendedVerificationKey{} -> return k
251-
k@AStakePoolExtendedVerificationKey{} -> return k
252252
-- Non-extended keys are below and cause failure.
253253
k@AByronVerificationKey{} -> goFail k
254254
k@APaymentVerificationKey{} -> goFail k
255255
k@AGenesisUTxOVerificationKey{} -> goFail k
256256
k@AKesVerificationKey{} -> goFail k
257257
k@AVrfVerificationKey{} -> goFail k
258-
k@AStakeVerificationKey{} -> goFail k
259258
k@AStakePoolVerificationKey{} -> goFail k
259+
k@AStakeVerificationKey{} -> goFail k
260260
k@ADRepVerificationKey{} -> goFail k
261261
k@ACommitteeColdVerificationKey{} -> goFail k
262262
k@ACommitteeHotVerificationKey{} -> goFail k

cardano-cli/src/Cardano/CLI/Option.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ import Cardano.CLI.EraBased.Common.Option
1616
import Cardano.CLI.EraBased.Option
1717
import Cardano.CLI.EraBased.Query.Option (pQueryCmdsTopLevel)
1818
import Cardano.CLI.EraIndependent.Address.Option
19+
import Cardano.CLI.EraIndependent.Cip.Options
1920
import Cardano.CLI.EraIndependent.Debug.Option
2021
import Cardano.CLI.EraIndependent.Hash.Option
2122
import Cardano.CLI.EraIndependent.Key.Option
@@ -88,6 +89,7 @@ parseClientCommand envCli =
8889
, parseDebug envCli
8990
, backwardsCompatibilityCommands envCli
9091
, parseDisplayVersion (opts envCli)
92+
, parseCipCmd
9193
, parseCompatibilityCommands envCli
9294
]
9395

cardano-cli/src/Cardano/CLI/Orphan.hs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ import Cardano.Ledger.Conway.Governance qualified as L
1717
import Cardano.Ledger.State qualified as L
1818

1919
import Data.Aeson
20+
import Text.Parsec qualified as Text
2021

2122
instance ToJSON L.DefaultVote where
2223
toJSON defaultVote =
@@ -25,6 +26,15 @@ instance ToJSON L.DefaultVote where
2526
L.DefaultAbstain -> String "DefaultAbstain"
2627
L.DefaultNoConfidence -> String "DefaultNoConfidence"
2728

29+
instance Error [Bech32DecodeError] where
30+
prettyError errs = mconcat $ map prettyError errs
31+
32+
instance Error [RawBytesHexError] where
33+
prettyError errs = mconcat $ map prettyError errs
34+
35+
instance Error Text.ParseError where
36+
prettyError = pretty . show
37+
2838
instance Error (VotesMergingConflict era) where
2939
prettyError = pretty . show
3040

cardano-cli/src/Cardano/CLI/Read.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@ module Cardano.CLI.Read
6868
, fileOrPipePath
6969
, fileOrPipeCache
7070
, readFileOrPipe
71+
, readFileOrPipeTextEnvelopeAnyOf
7172

7273
-- * Stake credentials
7374
, getStakeCredentialFromVerifier
Lines changed: 68 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,68 @@
1+
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE GADTs #-}
3+
{-# LANGUAGE StandaloneDeriving #-}
4+
5+
module Cardano.CLI.Read.Committee.ColdKey
6+
( AnyCommitteeColdVerificationKey (..)
7+
8+
-- * Read bech32 or hex encoded Committee Hot verification key
9+
, readCommitteeColdBech32VerificationKeyText
10+
, readCommitteeColdHexVerificationKeyText
11+
12+
-- * Read TextEnvelope Committee Hot verification key file
13+
, readCommitteeColdVerificationKeyFile
14+
)
15+
where
16+
17+
import Cardano.Api.Shelley
18+
19+
import Cardano.CLI.Read
20+
import Cardano.Prelude qualified as Text
21+
22+
import Prelude
23+
24+
import Data.Text (Text)
25+
import Data.Validation
26+
27+
data AnyCommitteeColdVerificationKey where
28+
AnyCommitteeColdVerificationKey :: VerificationKey CommitteeColdKey -> AnyCommitteeColdVerificationKey
29+
AnyCommitteeColdExtendedVerificationKey
30+
:: VerificationKey CommitteeColdExtendedKey -> AnyCommitteeColdVerificationKey
31+
32+
deriving instance Show AnyCommitteeColdVerificationKey
33+
34+
readCommitteeColdBech32VerificationKeyText
35+
:: Text -> Validation [Bech32DecodeError] AnyCommitteeColdVerificationKey
36+
readCommitteeColdBech32VerificationKeyText committeeColdText =
37+
let vkey =
38+
liftError return $
39+
AnyCommitteeColdVerificationKey
40+
<$> deserialiseFromBech32 (AsVerificationKey AsCommitteeColdKey) committeeColdText
41+
extendedVkey =
42+
liftError return $
43+
AnyCommitteeColdExtendedVerificationKey
44+
<$> deserialiseFromBech32 (AsVerificationKey AsCommitteeColdExtendedKey) committeeColdText
45+
in vkey <> extendedVkey
46+
47+
readCommitteeColdHexVerificationKeyText
48+
:: Text -> Validation [RawBytesHexError] AnyCommitteeColdVerificationKey
49+
readCommitteeColdHexVerificationKeyText committeeColdText =
50+
let committeeColdBs = Text.encodeUtf8 committeeColdText
51+
vkey =
52+
liftError return $
53+
AnyCommitteeColdVerificationKey
54+
<$> deserialiseFromRawBytesHex (AsVerificationKey AsCommitteeColdKey) committeeColdBs
55+
extendedVkey =
56+
liftError return $
57+
AnyCommitteeColdExtendedVerificationKey
58+
<$> deserialiseFromRawBytesHex (AsVerificationKey AsCommitteeColdExtendedKey) committeeColdBs
59+
in vkey <> extendedVkey
60+
61+
readCommitteeColdVerificationKeyFile
62+
:: FileOrPipe -> IO (Either (FileError TextEnvelopeError) AnyCommitteeColdVerificationKey)
63+
readCommitteeColdVerificationKeyFile = readFileOrPipeTextEnvelopeAnyOf types
64+
where
65+
types =
66+
[ FromSomeType (AsVerificationKey AsCommitteeColdKey) AnyCommitteeColdVerificationKey
67+
, FromSomeType (AsVerificationKey AsCommitteeColdExtendedKey) AnyCommitteeColdExtendedVerificationKey
68+
]

0 commit comments

Comments
 (0)