Skip to content

Commit

Permalink
Fix breaking changes from cardano-ledger
Browse files Browse the repository at this point in the history
  • Loading branch information
klarkc committed Apr 23, 2024
1 parent ec0f2c3 commit e8e9df7
Show file tree
Hide file tree
Showing 7 changed files with 46 additions and 46 deletions.
18 changes: 9 additions & 9 deletions server/src/Ogmios/Data/Json/Alonzo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Ogmios.Data.Json.Alonzo where
import Ogmios.Data.Json.Prelude

import Cardano.Ledger.Api
( AsIndex
( AsIx
, PlutusPurpose
)
import Data.SatInt
Expand Down Expand Up @@ -364,14 +364,14 @@ encodeRedeemers
:: forall era.
( Al.AlonzoEraScript era
)
=> (PlutusPurpose AsIndex era -> Json)
=> (PlutusPurpose AsIx era -> Json)
-> Al.Redeemers era
-> Json
encodeRedeemers encodeScriptPurposeIndexInEra (Al.Redeemers redeemers) =
encodeMapAsList encodeDataAndUnits redeemers
where
encodeDataAndUnits
:: PlutusPurpose AsIndex era
:: PlutusPurpose AsIx era
-> (Al.Data era, Al.ExUnits)
-> Json
encodeDataAndUnits ptr (redeemer, units) =
Expand Down Expand Up @@ -408,28 +408,28 @@ encodeScript opts = encodeObject . \case
encodeByteStringBase16 (Ledger.originalBytes (Al.plutusScriptBinary script))

encodeScriptPurposeIndex
:: Al.AlonzoPlutusPurpose Ledger.AsIndex era
:: Al.AlonzoPlutusPurpose Ledger.AsIx era
-> Json
encodeScriptPurposeIndex = encodeObject . \case
Al.AlonzoSpending (Ledger.AsIndex ix) ->
Al.AlonzoSpending (Ledger.AsIx ix) ->
( "index" .=
encodeWord32 ix
<> "purpose" .=
encodeText "spend"
)
Al.AlonzoMinting (Ledger.AsIndex ix) ->
Al.AlonzoMinting (Ledger.AsIx ix) ->
( "index" .=
encodeWord32 ix
<> "purpose" .=
encodeText "mint"
)
Al.AlonzoCertifying (Ledger.AsIndex ix) ->
Al.AlonzoCertifying (Ledger.AsIx ix) ->
( "index" .=
encodeWord32 ix
<> "purpose" .=
encodeText "publish"
)
Al.AlonzoRewarding (Ledger.AsIndex ix) ->
Al.AlonzoRewarding (Ledger.AsIx ix) ->
( "index" .=
encodeWord32 ix
<> "purpose" .=
Expand Down Expand Up @@ -572,7 +572,7 @@ encodeWitnessSet
)
=> IncludeCbor
-> StrictMaybe (AuxiliaryScripts era)
-> (PlutusPurpose AsIndex era -> Json)
-> (PlutusPurpose AsIx era -> Json)
-> Al.AlonzoTxWits era
-> Series
encodeWitnessSet opts (fromSMaybe mempty -> auxScripts) encodeScriptPurposeIndexInEra x =
Expand Down
12 changes: 6 additions & 6 deletions server/src/Ogmios/Data/Json/Babbage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Cardano.Ledger.Alonzo.Plutus.TxInfo
( TxOutSource (..)
)
import Cardano.Ledger.Api
( AsIndex (..)
( AsIx (..)
)
import Cardano.Ledger.Binary
( sizedValue
Expand Down Expand Up @@ -76,7 +76,7 @@ encodeBlock opts (ShelleyBlock (Ledger.Block blkHeader txs) headerHash) =

encodeContextError
:: ( Crypto (EraCrypto era)
, Ba.PlutusPurpose AsIndex era ~ Al.AlonzoPlutusPurpose AsIndex era
, Ba.PlutusPurpose AsIx era ~ Al.AlonzoPlutusPurpose AsIx era
)
=> Ba.BabbageContextError era
-> Json
Expand All @@ -94,10 +94,10 @@ encodeContextError err = encodeText $ case err of
Ba.RedeemerPointerPointsToNothing purpose ->
let (title, ptr) =
case purpose of
Al.AlonzoSpending (AsIndex ix) -> ("spending input", ix)
Al.AlonzoMinting (AsIndex ix) -> ("minting policy", ix)
Al.AlonzoCertifying (AsIndex ix) -> ("publishing certificate", ix)
Al.AlonzoRewarding (AsIndex ix) -> ("withdrawing from account", ix)
Al.AlonzoSpending (AsIx ix) -> ("spending input", ix)
Al.AlonzoMinting (AsIx ix) -> ("minting policy", ix)
Al.AlonzoCertifying (AsIx ix) -> ("publishing certificate", ix)
Al.AlonzoRewarding (AsIx ix) -> ("withdrawing from account", ix)
in "Couldn't find corresponding redeemer for " <> title <> " #" <> show ptr <> ". Verify your transaction's construction."
Ba.AlonzoContextError (Al.TimeTranslationPastHorizon e) ->
"Uncomputable slot arithmetic; transaction's validity bounds go beyond the foreseeable end of the current era: " <> e
Expand Down
26 changes: 13 additions & 13 deletions server/src/Ogmios/Data/Json/Conway.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module Ogmios.Data.Json.Conway where
import Ogmios.Data.Json.Prelude

import Cardano.Ledger.Api
( AsIndex (..)
( AsIx (..)
, AsItem (..)
, PlutusPurpose
)
Expand Down Expand Up @@ -113,12 +113,12 @@ encodeCommittee x = encodeObject
( "members" .=
encodeMapAsList (\k -> encodeConstitutionalCommitteeMember k . SJust) (Cn.committeeMembers x)
<> "quorum" .=
encodeUnitInterval (Cn.committeeQuorum x)
encodeUnitInterval (Cn.committeeThreshold x)
)

encodeContextError
:: ( Crypto (EraCrypto era)
, PlutusPurpose AsIndex era ~ Cn.ConwayPlutusPurpose AsIndex era
, PlutusPurpose AsIx era ~ Cn.ConwayPlutusPurpose AsIx era
)
=> Cn.ConwayContextError era
-> Json
Expand All @@ -140,12 +140,12 @@ encodeContextError err = encodeText $ case err of
Cn.BabbageContextError (Ba.RedeemerPointerPointsToNothing purpose) ->
let (title, ptr) =
case purpose of
Cn.ConwaySpending (AsIndex ix) -> ("spending input", ix)
Cn.ConwayMinting (AsIndex ix) -> ("minting policy", ix)
Cn.ConwayCertifying (AsIndex ix) -> ("publishing certificate", ix)
Cn.ConwayRewarding (AsIndex ix) -> ("withdrawing from account", ix)
Cn.ConwayVoting (AsIndex ix) -> ("voting as voter", ix)
Cn.ConwayProposing (AsIndex ix) -> ("proposing governance proposal", ix)
Cn.ConwaySpending (AsIx ix) -> ("spending input", ix)
Cn.ConwayMinting (AsIx ix) -> ("minting policy", ix)
Cn.ConwayCertifying (AsIx ix) -> ("publishing certificate", ix)
Cn.ConwayRewarding (AsIx ix) -> ("withdrawing from account", ix)
Cn.ConwayVoting (AsIx ix) -> ("voting as voter", ix)
Cn.ConwayProposing (AsIx ix) -> ("proposing governance proposal", ix)
in "Couldn't find corresponding redeemer for " <> title <> " #" <> show ptr <> ". Verify your transaction's construction."
Cn.BabbageContextError (Ba.AlonzoContextError (Al.TimeTranslationPastHorizon e)) ->
"Uncomputable slot arithmetic; transaction's validity bounds go beyond the foreseeable end of the current era: " <> e
Expand Down Expand Up @@ -565,25 +565,25 @@ encodeProposalProcedure x = encodeObject

encodeScriptPurposeIndex
:: forall era. ()
=> Cn.ConwayPlutusPurpose AsIndex era
=> Cn.ConwayPlutusPurpose AsIx era
-> Json
encodeScriptPurposeIndex = \case
Cn.ConwaySpending ix ->
translate (Al.AlonzoSpending ix)
Cn.ConwayMinting ix ->
translate (Al.AlonzoMinting ix)
Cn.ConwayCertifying (AsIndex (AsIndex -> ix)) ->
Cn.ConwayCertifying (AsIx (AsIx -> ix)) ->
translate (Al.AlonzoCertifying ix)
Cn.ConwayRewarding ix ->
translate (Al.AlonzoRewarding ix)
Cn.ConwayVoting (AsIndex ix) ->
Cn.ConwayVoting (AsIx ix) ->
encodeObject
( "index" .=
encodeWord32 ix
<> "purpose" .=
encodeText "vote"
)
Cn.ConwayProposing (AsIndex ix) ->
Cn.ConwayProposing (AsIx ix) ->
encodeObject
( "index" .=
encodeWord32 ix
Expand Down
10 changes: 5 additions & 5 deletions server/src/Ogmios/Data/Json/Shelley.hs
Original file line number Diff line number Diff line change
Expand Up @@ -581,7 +581,7 @@ encodePoolParams x =
"margin" .=
encodeUnitInterval (Ledger.ppMargin x) <>
"rewardAccount" .=
encodeRewardAcnt (Ledger.ppRewardAcnt x) <>
encodeRewardAcnt (Ledger.ppRewardAccount x) <>
"owners" .=
encodeFoldable encodeKeyHash (Ledger.ppOwners x) <>
"relays" .=
Expand Down Expand Up @@ -729,7 +729,7 @@ encodeProtVer x =
& encodeObject

encodeRewardAcnt
:: Sh.RewardAcnt era
:: Sh.RewardAccount era
-> Json
encodeRewardAcnt =
encodeText . stringifyRewardAcnt
Expand Down Expand Up @@ -1075,10 +1075,10 @@ stringifyPoolId (Ledger.KeyHash (CC.UnsafeHash h)) =
encodeBech32 hrpPool (fromShort h)

stringifyRewardAcnt
:: Sh.RewardAcnt era
:: Sh.RewardAccount era
-> Text
stringifyRewardAcnt x@(Sh.RewardAcnt ntwrk _credential) =
encodeBech32 (hrp ntwrk) (Ledger.serialiseRewardAcnt x)
stringifyRewardAcnt x@(Sh.RewardAccount ntwrk _credential) =
encodeBech32 (hrp ntwrk) (Ledger.serialiseRewardAccount x)
where
hrp = \case
Ledger.Mainnet -> hrpStakeMainnet
Expand Down
14 changes: 7 additions & 7 deletions server/src/Ogmios/Data/Ledger.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,13 @@ import Ogmios.Prelude

import Cardano.Ledger.Address
( Addr (..)
, RewardAcnt (..)
, RewardAccount (..)
)
import Cardano.Ledger.Alonzo.Plutus.Context
( ContextError
)
import Cardano.Ledger.Api
( AsIndex
( AsIx
, AsItem
)
import Cardano.Ledger.Conway.Core
Expand All @@ -48,7 +48,7 @@ import qualified Prelude

data DiscriminatedEntities crypto
= DiscriminatedAddresses (Set (Addr crypto))
| DiscriminatedRewardAccounts (Set (RewardAcnt crypto))
| DiscriminatedRewardAccounts (Set (RewardAccount crypto))
| DiscriminatedPoolRegistrationCertificate (KeyHash 'StakePool crypto)
| DiscriminatedTransaction
deriving (Show, Ord, Eq)
Expand Down Expand Up @@ -78,7 +78,7 @@ data ScriptPurposeIndexInAnyEra crypto =
forall era. Era (era crypto) =>
ScriptPurposeIndexInAnyEra
( AlonzoBasedEra (era crypto)
, PlutusPurpose AsIndex (era crypto)
, PlutusPurpose AsIx (era crypto)
)

instance Crypto crypto => Show (ScriptPurposeIndexInAnyEra crypto) where
Expand All @@ -92,12 +92,12 @@ instance Crypto crypto => Ord (ScriptPurposeIndexInAnyEra crypto) where

scriptPurposeInMostRecentEra
:: ScriptPurposeIndexInAnyEra crypto
-> PlutusPurpose AsIndex (MostRecentEra (CardanoBlock crypto))
-> PlutusPurpose AsIx (MostRecentEra (CardanoBlock crypto))
scriptPurposeInMostRecentEra = \case
ScriptPurposeIndexInAnyEra (AlonzoBasedEraAlonzo, ix) ->
upgradePlutusPurposeAsIndex (upgradePlutusPurposeAsIndex ix)
upgradePlutusPurposeAsIx (upgradePlutusPurposeAsIx ix)
ScriptPurposeIndexInAnyEra (AlonzoBasedEraBabbage, ix) ->
upgradePlutusPurposeAsIndex ix
upgradePlutusPurposeAsIx ix
ScriptPurposeIndexInAnyEra (AlonzoBasedEraConway, ix) ->
ix

Expand Down
6 changes: 3 additions & 3 deletions server/src/Ogmios/Data/Ledger/PredicateFailure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@ module Ogmios.Data.Ledger.PredicateFailure
, Language (..)
, Network (..)
, ProtVer (..)
, RewardAcnt (..)
, RewardAccount (..)
, ScriptHash (..)
, ScriptIntegrityHash
, ScriptPurposeItemInAnyEra (..)
Expand All @@ -42,7 +42,7 @@ import Ogmios.Prelude

import Cardano.Ledger.Address
( Addr (..)
, RewardAcnt (..)
, RewardAccount (..)
)
import Cardano.Ledger.Allegra.Scripts
( ValidityInterval (..)
Expand Down Expand Up @@ -406,7 +406,7 @@ data MultiEraPredicateFailure crypto

-- When present, withdrawals must withdraw rewards entirely
| IncompleteWithdrawals
{ withdrawals :: Map (RewardAcnt crypto) Coin
{ withdrawals :: Map (RewardAccount crypto) Coin
}

---------------------------------------------------------------------------
Expand Down
6 changes: 3 additions & 3 deletions server/src/Ogmios/Data/Protocol/TxSubmission.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ import Cardano.Ledger.Alonzo.Plutus.Context
)
import Cardano.Ledger.Alonzo.Scripts
( AlonzoScript
, AsIndex
, AsIx
, ExUnits (..)
, PlutusPurpose
, Script
Expand Down Expand Up @@ -435,7 +435,7 @@ evaluateExecutionUnits pparams systemStart epochInfo utxo tx = case evaluation o
else EvaluationFailure $ ScriptExecutionFailures failures
where
aggregateReports
:: PlutusPurpose AsIndex (era crypto)
:: PlutusPurpose AsIx (era crypto)
-> Either (TransactionScriptFailure (era crypto)) ExUnits
-> (Map ix [TransactionScriptFailureInAnyEra crypto], Map ix ExUnits)
-> (Map ix [TransactionScriptFailureInAnyEra crypto], Map ix ExUnits)
Expand All @@ -457,7 +457,7 @@ evaluateExecutionUnits pparams systemStart epochInfo utxo tx = case evaluation o
:: Either
(ContextError (era crypto))
(Map
(PlutusPurpose AsIndex (era crypto))
(PlutusPurpose AsIx (era crypto))
(Either (TransactionScriptFailure (era crypto)) ExUnits)
)
evaluation =
Expand Down

0 comments on commit e8e9df7

Please sign in to comment.