Skip to content

Commit

Permalink
Update and qualify Cardano.Api.Ledger as L
Browse files Browse the repository at this point in the history
  • Loading branch information
palas committed Feb 23, 2024
1 parent cf36980 commit 8acffb1
Show file tree
Hide file tree
Showing 23 changed files with 189 additions and 193 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/haskell.yml
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ jobs:

env:
# Modify this value to "invalidate" the cabal cache.
CABAL_CACHE_VERSION: "2024-02-12-2"
CABAL_CACHE_VERSION: "2024-02-23"

concurrency:
group: >
Expand Down
4 changes: 2 additions & 2 deletions cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,8 @@ repository cardano-haskell-packages
-- See CONTRIBUTING for information about these, including some Nix commands
-- you need to run if you change them
index-state:
, hackage.haskell.org 2024-02-14T11:32:54Z
, cardano-haskell-packages 2024-02-14T10:17:08Z
, hackage.haskell.org 2024-02-23T02:09:28Z
, cardano-haskell-packages 2024-02-22T17:04:08Z

packages:
cardano-cli
Expand Down
2 changes: 1 addition & 1 deletion cardano-cli/cardano-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,7 @@ library
, binary
, bytestring
, canonical-json
, cardano-api ^>= 8.38.0.2
, cardano-api ^>= 8.39.0.0
, cardano-binary
, cardano-crypto
, cardano-crypto-class ^>= 2.1.2
Expand Down
30 changes: 15 additions & 15 deletions cardano-cli/src/Cardano/CLI/EraBased/Commands/Governance/Actions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module Cardano.CLI.EraBased.Commands.Governance.Actions
) where

import Cardano.Api
import qualified Cardano.Api.Ledger as Ledger
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley

import Cardano.CLI.Types.Common
Expand All @@ -44,11 +44,11 @@ data GovernanceActionCmds era
data GoveranceActionUpdateCommitteeCmdArgs era
= GoveranceActionUpdateCommitteeCmdArgs
{ eon :: !(ConwayEraOnwards era)
, networkId :: !Ledger.Network
, networkId :: !L.Network
, deposit :: !Lovelace
, returnAddress :: !(VerificationKeyOrHashOrFile StakeKey)
, proposalUrl :: !ProposalUrl
, proposalHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, oldCommitteeVkeySource :: ![VerificationKeyOrHashOrFile CommitteeColdKey]
, newCommitteeVkeySource :: ![(VerificationKeyOrHashOrFile CommitteeColdKey, EpochNo)]
, requiredQuorum :: !Rational
Expand All @@ -59,37 +59,37 @@ data GoveranceActionUpdateCommitteeCmdArgs era
data GovernanceActionCreateConstitutionCmdArgs era
= GovernanceActionCreateConstitutionCmdArgs
{ eon :: !(ConwayEraOnwards era)
, networkId :: !Ledger.Network
, networkId :: !L.Network
, deposit :: !Lovelace
, stakeCredential :: !(VerificationKeyOrHashOrFile StakeKey)
, mPrevGovernanceActionId :: !(Maybe (TxId, Word32))
, proposalUrl :: !ProposalUrl
, proposalHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, constitutionUrl :: !ConstitutionUrl
, constitutionHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, constitutionHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, outFile :: !(File () Out)
} deriving Show

-- | Datatype to carry data for the create-info governance action
data GovernanceActionInfoCmdArgs era
= GovernanceActionInfoCmdArgs
{ eon :: !(ConwayEraOnwards era)
, networkId :: !Ledger.Network
, networkId :: !L.Network
, deposit :: !Lovelace
, returnStakeAddress :: !(VerificationKeyOrHashOrFile StakeKey)
, proposalUrl :: !ProposalUrl
, proposalHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, outFile :: !(File () Out)
} deriving Show

data GovernanceActionCreateNoConfidenceCmdArgs era
= GovernanceActionCreateNoConfidenceCmdArgs
{ eon :: !(ConwayEraOnwards era)
, networkId :: !Ledger.Network
, networkId :: !L.Network
, deposit :: !Lovelace
, returnStakeAddress :: !(VerificationKeyOrHashOrFile StakeKey)
, proposalUrl :: !ProposalUrl
, proposalHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, governanceActionId :: !TxId
, governanceActionIndex :: !Word32
, outFile :: !(File () Out)
Expand All @@ -115,11 +115,11 @@ data GovernanceActionProtocolParametersUpdateCmdArgs era
data GovernanceActionTreasuryWithdrawalCmdArgs era
= GovernanceActionTreasuryWithdrawalCmdArgs
{ eon :: !(ConwayEraOnwards era)
, networkId :: !Ledger.Network
, networkId :: !L.Network
, deposit :: !Lovelace
, returnAddr :: !(VerificationKeyOrHashOrFile StakeKey)
, proposalUrl :: !ProposalUrl
, proposalHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, treasuryWithdrawal :: ![(VerificationKeyOrHashOrFile StakeKey, Lovelace)]
, constitutionScriptHash :: !(Maybe ScriptHash)
, outFile :: !(File () Out)
Expand All @@ -136,19 +136,19 @@ data GovernanceActionViewCmdArgs era
data UpdateProtocolParametersConwayOnwards era
= UpdateProtocolParametersConwayOnwards
{ eon :: !(ConwayEraOnwards era)
, networkId :: !Ledger.Network
, networkId :: !L.Network
, deposit :: !Lovelace
, returnAddr :: !(VerificationKeyOrHashOrFile StakeKey)
, proposalUrl :: !ProposalUrl
, proposalHash :: !(Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, governanceActionId :: !(Maybe (TxId, Word32))
, constitutionScriptHash :: !(Maybe ScriptHash)
}

data CostModelsFile era
= CostModelsFile
{ eon :: !(AlonzoEraOnwards era)
, costModelsFile :: !(File Ledger.CostModels In)
, costModelsFile :: !(File L.CostModels In)
} deriving Show

deriving instance Show (UpdateProtocolParametersConwayOnwards era)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module Cardano.CLI.EraBased.Commands.Governance.Committee
) where

import Cardano.Api
import qualified Cardano.Api.Ledger as Ledger
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley

import Cardano.CLI.Types.Key
Expand Down Expand Up @@ -61,7 +61,7 @@ data GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era =
GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs
{ eon :: !(ConwayEraOnwards era)
, vkeyColdKeySource :: !(VerificationKeyOrHashOrFile CommitteeColdKey)
, anchor :: !(Maybe (Ledger.Anchor (Ledger.EraCrypto (ShelleyLedgerEra era))))
, anchor :: !(Maybe (L.Anchor (L.EraCrypto (ShelleyLedgerEra era))))
, outFile :: !(File () Out)
} deriving Show

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module Cardano.CLI.EraBased.Commands.Governance.DRep
where

import Cardano.Api
import qualified Cardano.Api.Ledger as Ledger
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley

import Cardano.CLI.Types.Common
Expand Down Expand Up @@ -52,7 +52,7 @@ data GovernanceDRepRegistrationCertificateCmdArgs era =
{ eon :: !(ConwayEraOnwards era)
, drepHashSource :: !DRepHashSource
, deposit :: !Lovelace
, mAnchor :: !(Maybe (Ledger.Anchor (Ledger.EraCrypto (ShelleyLedgerEra era))))
, mAnchor :: !(Maybe (L.Anchor (L.EraCrypto (ShelleyLedgerEra era))))
, outFile :: !(File () Out)
}

Expand All @@ -68,7 +68,7 @@ data GovernanceDRepUpdateCertificateCmdArgs era =
GovernanceDRepUpdateCertificateCmdArgs
{ eon :: !(ConwayEraOnwards era)
, drepVkeyHashSource :: !(VerificationKeyOrHashOrFile DRepKey)
, mAnchor :: !(Maybe (Ledger.Anchor (Ledger.EraCrypto (ShelleyLedgerEra era))))
, mAnchor :: !(Maybe (L.Anchor (L.EraCrypto (ShelleyLedgerEra era))))
, outFile :: !(File () Out)
}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module Cardano.CLI.EraBased.Commands.Governance.Vote
, GovernanceVoteCreateCmdArgs(..)
, renderGovernanceVoteCmds
) where
import qualified Cardano.Api.Ledger as Ledger
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley

import Cardano.CLI.Types.Common
Expand All @@ -30,7 +30,7 @@ data GovernanceVoteCreateCmdArgs era
, voteChoice :: Vote
, governanceAction :: (TxId, Word32)
, votingStakeCredentialSource :: AnyVotingStakeVerificationKeyOrHashOrFile
, mAnchor :: Maybe (VoteUrl, Ledger.SafeHash Ledger.StandardCrypto Ledger.AnchorData)
, mAnchor :: Maybe (VoteUrl, L.SafeHash L.StandardCrypto L.AnchorData)
, outFile :: VoteFile Out
}

Expand Down
15 changes: 7 additions & 8 deletions cardano-cli/src/Cardano/CLI/EraBased/Options/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ module Cardano.CLI.EraBased.Options.Common where

import Cardano.Api
import qualified Cardano.Api.Ledger as L
import qualified Cardano.Api.Ledger as Ledger
import Cardano.Api.Pretty
import Cardano.Api.Shelley

Expand Down Expand Up @@ -124,7 +123,7 @@ pTarget = inEonForEra (pure Consensus.VolatileTip) pTargetFromConway
]

toUnitIntervalOrErr :: Rational -> L.UnitInterval
toUnitIntervalOrErr r = case Ledger.boundRational r of
toUnitIntervalOrErr r = case L.boundRational r of
Nothing ->
error $ mconcat [ "toUnitIntervalOrErr: "
, "rational out of bounds " <> show r
Expand Down Expand Up @@ -907,10 +906,10 @@ pConstitutionHash =
, Opt.help "Hash of the constitution data (obtain it with \"cardano-cli conway governance hash anchor-data ...\")."
]

pUrl :: String -> String -> Parser Ledger.Url
pUrl :: String -> String -> Parser L.Url
pUrl l h =
let toUrl urlText = fromMaybe (error "Url longer than 64 bytes")
$ Ledger.textToUrl (Text.length urlText) urlText
$ L.textToUrl (Text.length urlText) urlText
in fmap toUrl . Opt.strOption
$ mconcat [ Opt.long l
, Opt.metavar "TEXT"
Expand Down Expand Up @@ -2898,9 +2897,9 @@ pProtocolVersion =
]
]

pPoolVotingThresholds :: Parser Ledger.PoolVotingThresholds
pPoolVotingThresholds :: Parser L.PoolVotingThresholds
pPoolVotingThresholds =
Ledger.PoolVotingThresholds
L.PoolVotingThresholds
<$> pMotionNoConfidence
<*> pCommitteeNormal
<*> pCommitteeNoConfidence
Expand Down Expand Up @@ -2938,9 +2937,9 @@ pPoolVotingThresholds =
, Opt.help "Acceptance threshold for stake pool votes on protocol parameters for parameters in the 'security' group."
]

pDRepVotingThresholds :: Parser Ledger.DRepVotingThresholds
pDRepVotingThresholds :: Parser L.DRepVotingThresholds
pDRepVotingThresholds =
Ledger.DRepVotingThresholds
L.DRepVotingThresholds
<$> pMotionNoConfidence
<*> pCommitteeNormal
<*> pCommitteeNoConfidence
Expand Down
25 changes: 12 additions & 13 deletions cardano-cli/src/Cardano/CLI/EraBased/Options/Governance/Actions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,7 @@ module Cardano.CLI.EraBased.Options.Governance.Actions
) where

import Cardano.Api
import Cardano.Api.Ledger
import qualified Cardano.Api.Ledger as Ledger
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley

import qualified Cardano.CLI.EraBased.Commands.Governance.Actions as Cmd
Expand Down Expand Up @@ -219,20 +218,20 @@ pGovernanceActionProtocolParametersUpdateCmd era = do
<$> pUpdateProtocolParametersCmd w


convertToLedger :: (a -> b) -> Parser (Maybe a) -> Parser (StrictMaybe b)
convertToLedger conv = fmap (maybeToStrictMaybe . fmap conv)
convertToLedger :: (a -> b) -> Parser (Maybe a) -> Parser (L.StrictMaybe b)
convertToLedger conv = fmap (L.maybeToStrictMaybe . fmap conv)

toNonNegativeIntervalOrErr :: Rational -> NonNegativeInterval
toNonNegativeIntervalOrErr r = case Ledger.boundRational r of
toNonNegativeIntervalOrErr :: Rational -> L.NonNegativeInterval
toNonNegativeIntervalOrErr r = case L.boundRational r of
Nothing ->
error $ mconcat [ "toNonNegativeIntervalOrErr: "
, "rational out of bounds " <> show r
]
Just n -> n

mkProtocolVersionOrErr :: (Natural, Natural) -> Ledger.ProtVer
mkProtocolVersionOrErr :: (Natural, Natural) -> L.ProtVer
mkProtocolVersionOrErr (majorProtVer, minorProtVer) =
case (`Ledger.ProtVer` minorProtVer) <$> Ledger.mkVersion majorProtVer of
case (`L.ProtVer` minorProtVer) <$> L.mkVersion majorProtVer of
Just v -> v
Nothing ->
error $ "mkProtocolVersionOrErr: invalid protocol version " <> show (majorProtVer, minorProtVer)
Expand Down Expand Up @@ -273,7 +272,7 @@ pShelleyToAlonzoPParams =

pAlonzoOnwardsPParams :: Parser (AlonzoOnwardsPParams ledgerera)
pAlonzoOnwardsPParams =
AlonzoOnwardsPParams SNothing -- The cost models are read separately from a file, so we use 'SNothing' as the place holder here
AlonzoOnwardsPParams L.SNothing -- The cost models are read separately from a file, so we use 'SNothing' as the place holder here
<$> convertToLedger (either (\e -> error $ "pAlonzoOnwardsPParams: " <> show e) id . toAlonzoPrices)
(optional pExecutionUnitPrices)
<*> convertToLedger toAlonzoExUnits (optional pMaxTxExecutionUnits)
Expand All @@ -286,7 +285,7 @@ pAlonzoOnwardsPParams =
pIntroducedInBabbagePParams :: Parser (IntroducedInBabbagePParams ledgerera)
pIntroducedInBabbagePParams =
IntroducedInBabbagePParams
<$> convertToLedger (CoinPerByte . toShelleyLovelace) (optional pUTxOCostPerByte)
<$> convertToLedger (L.CoinPerByte . toShelleyLovelace) (optional pUTxOCostPerByte)

pIntroducedInConwayPParams :: Parser (IntroducedInConwayPParams ledgerera)
pIntroducedInConwayPParams =
Expand Down Expand Up @@ -363,13 +362,13 @@ pGovernanceActionTreasuryWithdrawalCmd era = do
)
$ Opt.progDesc "Create a treasury withdrawal."

pNetwork :: Parser Ledger.Network
pNetwork :: Parser L.Network
pNetwork = asum $ mconcat
[ [ Opt.flag' Ledger.Mainnet $ mconcat
[ [ Opt.flag' L.Mainnet $ mconcat
[ Opt.long "mainnet"
, Opt.help "Use the mainnet magic id."
]
, Opt.flag' Ledger.Testnet $ mconcat
, Opt.flag' L.Testnet $ mconcat
[ Opt.long "testnet"
, Opt.help "Use the testnet magic id."
]
Expand Down
12 changes: 6 additions & 6 deletions cardano-cli/src/Cardano/CLI/EraBased/Run/Genesis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -657,14 +657,14 @@ updateOutputTemplate
-> Maybe Lovelace -- ^ Amount of lovelace not delegated
-> Int -- ^ Number of UTxO addresses that are delegating
-> [AddressInEra ShelleyEra] -- ^ UTxO addresses that are not delegating
-> [(Ledger.KeyHash 'Ledger.StakePool StandardCrypto, Ledger.PoolParams StandardCrypto)] -- ^ Pool map
-> [(Ledger.KeyHash 'Ledger.Staking StandardCrypto, Ledger.KeyHash 'Ledger.StakePool StandardCrypto)] -- ^ Delegaton map
-> [(L.KeyHash 'L.StakePool L.StandardCrypto, L.PoolParams L.StandardCrypto)] -- ^ Pool map
-> [(L.KeyHash 'L.Staking L.StandardCrypto, L.KeyHash 'L.StakePool L.StandardCrypto)] -- ^ Delegaton map
-> Maybe Lovelace -- ^ Amount of lovelace to delegate
-> Int -- ^ Number of UTxO address for delegation
-> [AddressInEra ShelleyEra] -- ^ UTxO address for delegation
-> [AddressInEra ShelleyEra] -- ^ Stuffed UTxO addresses
-> ShelleyGenesis StandardCrypto -- ^ Template from which to build a genesis
-> ShelleyGenesis StandardCrypto -- ^ Updated genesis
-> ShelleyGenesis L.StandardCrypto -- ^ Template from which to build a genesis
-> ShelleyGenesis L.StandardCrypto -- ^ Updated genesis
updateOutputTemplate
(SystemStart sgSystemStart)
genDelegMap mAmountNonDeleg nUtxoAddrsNonDeleg utxoAddrsNonDeleg pools stake
Expand Down Expand Up @@ -709,10 +709,10 @@ updateOutputTemplate

mkStuffedUtxo :: [AddressInEra ShelleyEra] -> [(AddressInEra ShelleyEra, Lovelace)]
mkStuffedUtxo xs = (, Lovelace minUtxoVal) <$> xs
where Coin minUtxoVal = sgProtocolParams ^. ppMinUTxOValueL
where L.Coin minUtxoVal = sgProtocolParams ^. L.ppMinUTxOValueL

shelleyDelKeys = Map.fromList
[ (gh, Ledger.GenDelegPair gdh h)
[ (gh, L.GenDelegPair gdh h)
| (GenesisKeyHash gh,
(GenesisDelegateKeyHash gdh, VrfKeyHash h)) <- Map.toList genDelegMap
]
Expand Down
Loading

0 comments on commit 8acffb1

Please sign in to comment.