Skip to content
Closed
Show file tree
Hide file tree
Changes from 1 commit
Commits
Show all changes
44 commits
Select commit Hold shift + click to select a range
5625233
wip: cardano-api with kes-agent support
fraser-iohk Jun 25, 2025
156d119
Add `DijkstraEra era` to `CardanoEra era`
Jimbo4350 Jul 30, 2025
2872eda
Add `ShelleyBasedEraDijkstra` to `ShelleyBasedEra era`
Jimbo4350 Jul 30, 2025
dda8797
Add Dijkstra era to eons
Jimbo4350 Jul 30, 2025
704d11d
Add `DijkstraEra` to `Era era`
Jimbo4350 Jul 30, 2025
7a86381
COMBINE ME: cabal file updates
Jimbo4350 Jul 30, 2025
5be60e0
Update `QueryInShelleyBasedEra era result`
Jimbo4350 Jul 30, 2025
3a8826d
Update `makeShelleyTransactionBody` with Dijkstra era
Jimbo4350 Jul 30, 2025
e63bb2c
Update ledger types `PParamUpdatePurpose`, `CommitteePurpose` and
Jimbo4350 Jul 30, 2025
63ad603
Propagate `ChainAccountState`
Jimbo4350 Jul 30, 2025
b483de7
Consensus related Dijkstra changes
Jimbo4350 Jul 30, 2025
0d8ee49
Temporary Cardano.Api.LedgerState Dijkstra update
Jimbo4350 Jul 30, 2025
730ff11
Update TxOut rendering to handle Dijkstra era
Jimbo4350 Jul 30, 2025
ca28c36
Update `eraSpecificLedgerTxBody` with Dijkstra era
Jimbo4350 Jul 30, 2025
d91aedc
Update `decodeBigLedgerPeerSnapshot` to support snapshot SRV names
Jimbo4350 Jul 30, 2025
338a657
Update generators with PlutusScriptV4
Jimbo4350 Jul 30, 2025
acdff31
Introduce PlutusScriptV4
Jimbo4350 Jul 30, 2025
3437b94
Propagate Dijkstra era
Jimbo4350 Jul 30, 2025
0a737a6
Merge with PlutusV4 intro
Jimbo4350 Jul 30, 2025
5229ec3
Merge with propagate Dikstra
Jimbo4350 Jul 30, 2025
6e832cb
REMOVE ME: Add ledger and consensus SRPs
Jimbo4350 Jul 30, 2025
8330132
Update nix flake
Jimbo4350 Jul 30, 2025
f3ca538
Update cardano-rpc with PlutusV4
Jimbo4350 Jul 31, 2025
6d81484
Implement `executeLocalStateQueryExprWithVersion`
Jimbo4350 Jul 31, 2025
4904a0d
Fix parseHardForkTriggers
Jimbo4350 Jul 31, 2025
2da81eb
Fix cardano-rpc-test for protocol parameters roundtrip
carbolymer Aug 1, 2025
673e4a8
Update flake lock and ouroboros-network and plutus patches
palas Aug 1, 2025
65013af
Update wasm cache
palas Aug 1, 2025
1efbb74
Merge with: Consensus related Dijkstra change
Aug 7, 2025
faab1c2
Use exampleDijkstraGenesis value
Aug 7, 2025
7b8fa12
Fix cabal-gild CI failure
Aug 7, 2025
0eeff17
Run formolu
Aug 7, 2025
a93eab2
Fix HLS CI job
carbolymer Aug 11, 2025
79b9c02
Address lints
palas Aug 12, 2025
64e62e7
Update `ouroboros-consensus` stanza
palas Aug 12, 2025
bb549c0
Merge remote-tracking branch 'origin/ana/v2-node-release-10.6' into a…
ana-pantilie Aug 20, 2025
ff4b7ca
Merge remote-tracking branch 'origin/fraser-iohk/cardano-api-kes-agen…
ana-pantilie Aug 20, 2025
7ae44e9
WIP: update ledger and index-state
ana-pantilie Aug 21, 2025
f18e5cb
Fix most compilation errors
ana-pantilie Aug 25, 2025
764c708
Upgrade plutus to 1.52
ana-pantilie Aug 25, 2025
c21f792
Add bounds to quickcheck
ana-pantilie Aug 26, 2025
ee5eccf
Add another quickcheck bound
ana-pantilie Aug 26, 2025
f3de953
Fill in undefineds
Jimbo4350 Aug 26, 2025
22b76a1
Bump CHaP in nix flake
Jimbo4350 Sep 9, 2025
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Prev Previous commit
Next Next commit
Fill in undefineds
  • Loading branch information
Jimbo4350 committed Aug 26, 2025
commit f3de95392d23ef54106f5310fdeecd3ed4f2f082
70 changes: 70 additions & 0 deletions cardano-api/src/Cardano/Api/Certificate/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,7 @@ module Cardano.Api.Certificate.Internal
, fromShelleyCertificate
, toShelleyPoolParams
, fromShelleyPoolParams
, fromShelleyStakePoolState

-- * Data family instances
, AsType (..)
Expand Down Expand Up @@ -100,6 +101,7 @@ import Cardano.Ledger.Api qualified as L
import Cardano.Ledger.BaseTypes (strictMaybe)
import Cardano.Ledger.Coin qualified as L
import Cardano.Ledger.Keys qualified as Ledger
import Cardano.Ledger.State qualified as Ledger

import Control.Monad.Except (MonadError (..))
import Data.ByteString (ByteString)
Expand Down Expand Up @@ -781,6 +783,74 @@ fromShelleyPoolParams
Text.encodeUtf8
. Ledger.dnsToText

fromShelleyStakePoolState
:: Ledger.KeyHash Ledger.StakePool
-> Ledger.StakePoolState
-> StakePoolParameters
fromShelleyStakePoolState
poolId
Ledger.StakePoolState
{ Ledger.spsVrf
, Ledger.spsPledge
, Ledger.spsCost
, Ledger.spsMargin
, Ledger.spsRewardAccount
, Ledger.spsOwners
, Ledger.spsRelays
, Ledger.spsMetadata
} =
StakePoolParameters
{ stakePoolId = StakePoolKeyHash poolId
, stakePoolVRF = VrfKeyHash (Ledger.fromVRFVerKeyHash spsVrf)
, stakePoolCost = spsCost
, stakePoolMargin = Ledger.unboundRational spsMargin
, stakePoolRewardAccount = fromShelleyStakeAddr spsRewardAccount
, stakePoolPledge = spsPledge
, stakePoolOwners = map StakeKeyHash (toList spsOwners)
, stakePoolRelays =
map
fromShelleyStakePoolRelay
(toList spsRelays)
, stakePoolMetadata =
fromShelleyPoolMetadata
<$> Ledger.strictMaybeToMaybe spsMetadata
}
where
fromShelleyStakePoolRelay :: Ledger.StakePoolRelay -> StakePoolRelay
fromShelleyStakePoolRelay (Ledger.SingleHostAddr mport mipv4 mipv6) =
StakePoolRelayIp
(Ledger.strictMaybeToMaybe mipv4)
(Ledger.strictMaybeToMaybe mipv6)
(fromIntegral . Ledger.portToWord16 <$> Ledger.strictMaybeToMaybe mport)
fromShelleyStakePoolRelay (Ledger.SingleHostName mport dnsname) =
StakePoolRelayDnsARecord
(fromShelleyDnsName dnsname)
(fromIntegral . Ledger.portToWord16 <$> Ledger.strictMaybeToMaybe mport)
fromShelleyStakePoolRelay (Ledger.MultiHostName dnsname) =
StakePoolRelayDnsSrvRecord
(fromShelleyDnsName dnsname)

fromShelleyPoolMetadata :: Ledger.PoolMetadata -> StakePoolMetadataReference
fromShelleyPoolMetadata
Ledger.PoolMetadata
{ Ledger.pmUrl
, Ledger.pmHash
} =
StakePoolMetadataReference
{ stakePoolMetadataURL = Ledger.urlToText pmUrl
, stakePoolMetadataHash =
StakePoolMetadataHash
. fromMaybe (error "fromShelleyPoolMetadata: invalid hash. TODO: proper validation")
. Ledger.hashFromBytes
$ pmHash
}

-- TODO: change the ledger rep of the DNS name to use ShortByteString
fromShelleyDnsName :: Ledger.DnsName -> ByteString
fromShelleyDnsName =
Text.encodeUtf8
. Ledger.dnsToText

data AnchorDataFromCertificateError
= InvalidPoolMetadataHashError Ledger.Url ByteString
deriving (Eq, Show)
Expand Down
6 changes: 3 additions & 3 deletions cardano-api/src/Cardano/Api/Experimental/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -214,11 +214,11 @@ newtype UnsignedTxError
= UnsignedTxError TxBodyError

makeUnsignedTx
:: Ledger.ProtVerAtMost (LedgerEra era) 11
=> Era era
:: Era era
-> TxBodyContent BuildTx era
-> Either TxBodyError (UnsignedTx era)
makeUnsignedTx era bc = obtainCommonConstraints era $ do
makeUnsignedTx DijkstraEra _ = error "makeUnsignedTx: Dijkstra era not supported yet"
makeUnsignedTx era@ConwayEra bc = obtainCommonConstraints era $ do
let sbe = convert era
aeon = convert era
TxScriptWitnessRequirements languages scripts datums redeemers <-
Expand Down
27 changes: 22 additions & 5 deletions cardano-api/src/Cardano/Api/Internal/Orphans/Serialisation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,10 +45,12 @@ import Cardano.Chain.Update.Validation.Voting qualified as L.Voting
import Cardano.Crypto.Hash qualified as Crypto
import Cardano.Ledger.Allegra.Rules qualified as L
import Cardano.Ledger.Alonzo.PParams qualified as Ledger
import Cardano.Ledger.Alonzo.Rules qualified as Alonzo
import Cardano.Ledger.Alonzo.Rules qualified as L
import Cardano.Ledger.Alonzo.Tx qualified as L
import Cardano.Ledger.Api qualified as L
import Cardano.Ledger.Babbage.PParams qualified as Ledger
import Cardano.Ledger.Babbage.Rules qualified as Babbage
import Cardano.Ledger.Babbage.Rules qualified as L
import Cardano.Ledger.BaseTypes (strictMaybeToMaybe)
import Cardano.Ledger.BaseTypes qualified as L
Expand Down Expand Up @@ -91,11 +93,20 @@ import PlutusLedgerApi.V2 qualified as V2

import Codec.Binary.Bech32 qualified as Bech32
import Codec.CBOR.Read qualified as CBOR
import Data.Aeson (KeyValue ((.=)), ToJSON (..), ToJSONKey (..), object, pairs)
import Data.Aeson
( KeyValue ((.=))
, ToJSON (..)
, ToJSONKey (..)
, defaultOptions
, genericToJSON
, object
, pairs
)
import Data.Aeson qualified as A
import Data.Aeson qualified as Aeson
import Data.Bifunctor
import Data.ByteString qualified as BS
import Data.ByteString.Base16 qualified as B16
import Data.ByteString.Base16 qualified as Base16
import Data.ByteString.Char8 qualified as C8
import Data.ByteString.Short qualified as SBS
Expand All @@ -106,6 +117,7 @@ import Data.ListMap qualified as ListMap
import Data.Maybe.Strict (StrictMaybe (..))
import Data.Monoid
import Data.Text qualified as T
import Data.Text qualified as Text
import Data.Text.Encoding qualified as Text
import Data.Typeable (Typeable)
import GHC.Exts (IsList (..), IsString (..))
Expand Down Expand Up @@ -200,17 +212,22 @@ instance
, ToJSON (L.PlutusPurpose L.AsItem ledgerera)
, ToJSON (L.PlutusPurpose L.AsIx ledgerera)
)
=> ToJSON (L.AlonzoUtxowPredFailure ledgerera) where
toJSON = undefined
=> ToJSON (L.AlonzoUtxowPredFailure ledgerera)
where
toJSON = genericToJSON defaultOptions

instance ToJSON C8.ByteString where
toJSON = Aeson.String . Text.decodeLatin1 . B16.encode

instance
( ToJSON (L.PredicateFailure (L.EraRule "UTXO" ledgerera))
, ToJSON (L.TxCert ledgerera)
, ToJSON (L.PlutusPurpose L.AsItem ledgerera)
, ToJSON (L.PlutusPurpose L.AsIx ledgerera)
)
=> ToJSON (L.BabbageUtxowPredFailure ledgerera) where
toJSON = undefined
=> ToJSON (L.BabbageUtxowPredFailure ledgerera)
where
toJSON = genericToJSON defaultOptions

deriving anyclass instance
ToJSON (L.PredicateFailure (L.EraRule "LEDGER" ledgerera))
Expand Down
21 changes: 10 additions & 11 deletions cardano-api/src/Cardano/Api/Query/Internal/Type/QueryInMode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -643,11 +643,11 @@ toConsensusQueryShelleyBased sbe = \case
)
(const $ Some (consensusQueryInEraInMode era Consensus.GetFuturePParams))
sbe
QueryDRepState _creds ->
QueryDRepState creds ->
caseShelleyToBabbageOrConwayEraOnwards
(const $ error "toConsensusQueryShelleyBased: QueryDRepState is only available in the Conway era")
( \w ->
Some (consensusQueryInEraInMode era (conwayEraOnwardsConstraints w $ Consensus.GetDRepState _creds))
Some (consensusQueryInEraInMode era (conwayEraOnwardsConstraints w $ Consensus.GetDRepState creds))
)
sbe
QueryDRepStakeDistr dreps ->
Expand All @@ -664,16 +664,15 @@ toConsensusQueryShelleyBased sbe = \case
)
(const $ Some (consensusQueryInEraInMode era (Consensus.GetSPOStakeDistr spos)))
sbe
QueryCommitteeMembersState _coldCreds _hotCreds _statuses ->
QueryCommitteeMembersState coldCreds hotCreds statuses ->
caseShelleyToBabbageOrConwayEraOnwards
( const $
error "toConsensusQueryShelleyBased: QueryCommitteeMembersState is only available in the Conway era"
)
undefined
-- ( const $
-- Some
-- (consensusQueryInEraInMode era (Consensus.GetCommitteeMembersState coldCreds hotCreds statuses))
-- )
( const $
Some
(consensusQueryInEraInMode era (Consensus.GetCommitteeMembersState coldCreds hotCreds statuses))
)
sbe
QueryStakeVoteDelegatees creds ->
caseShelleyToBabbageOrConwayEraOnwards
Expand Down Expand Up @@ -934,9 +933,9 @@ fromConsensusQueryResultShelleyBased sbe sbeQuery q' r' =
QueryStakePoolParameters{} ->
case q' of
Consensus.GetStakePoolParams{} ->
Map.map fromShelleyPoolParams
. Map.mapKeysMonotonic StakePoolKeyHash
$ undefined -- r'
Map.mapKeysMonotonic StakePoolKeyHash
. Map.mapWithKey fromShelleyStakePoolState
$ r'
_ -> fromConsensusQueryResultMismatch
QueryDebugLedgerState{} ->
case q' of
Expand Down
9 changes: 5 additions & 4 deletions cardano-api/src/Cardano/Api/Tx/Internal/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -272,6 +272,7 @@ import Cardano.Crypto.Hashing qualified as Byron
import Cardano.Ledger.Allegra.Core qualified as L
import Cardano.Ledger.Alonzo.Core qualified as L
import Cardano.Ledger.Alonzo.Scripts qualified as Alonzo
import Cardano.Ledger.Alonzo.Tx qualified as L
-- import Cardano.Ledger.Alonzo.Tx qualified as Alonzo (hashScriptIntegrity)
import Cardano.Ledger.Alonzo.TxWits qualified as Alonzo
import Cardano.Ledger.Api qualified as L
Expand Down Expand Up @@ -1981,13 +1982,13 @@ convPParamsToScriptIntegrityHash
-> Alonzo.TxDats (ShelleyLedgerEra era)
-> Set Plutus.Language
-> StrictMaybe L.ScriptIntegrityHash
convPParamsToScriptIntegrityHash w (BuildTxWith mTxProtocolParams) _ _ _ = -- redeemers datums languages =
convPParamsToScriptIntegrityHash w (BuildTxWith mTxProtocolParams) redeemers datums languages =
alonzoEraOnwardsConstraints w $
case mTxProtocolParams of
Nothing -> SNothing
Just (LedgerProtocolParameters _) -> undefined
-- Just (LedgerProtocolParameters pp) ->
-- Alonzo.hashScriptIntegrity (Set.map (L.getLanguageView pp) languages) redeemers datums
Just (LedgerProtocolParameters pp) ->
let scriptIntegrity = L.ScriptIntegrity redeemers datums (Set.map (L.getLanguageView pp) languages)
in SJust $ L.hashScriptIntegrity scriptIntegrity

convLanguages :: [(ScriptWitnessIndex, AnyScriptWitness era)] -> Set Plutus.Language
convLanguages witnesses =
Expand Down
8 changes: 7 additions & 1 deletion cardano-api/src/Cardano/Api/Tx/Internal/Body/Lens.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}

{- HLINT ignore "Eta reduce" -}

-- TODO: Deprecate all the lenses that use eons. Explore parameterizing them on `Era era` instead.

module Cardano.Api.Tx.Internal.Body.Lens
( -- * Types
LedgerTxBody (..)
Expand Down Expand Up @@ -163,7 +166,10 @@ collateralInputsTxBodyL w = alonzoEraOnwardsConstraints w $ txBodyL . L.collater

reqSignerHashesTxBodyL
:: AlonzoEraOnwards era -> Lens' (LedgerTxBody era) (Set (L.KeyHash L.Witness))
reqSignerHashesTxBodyL w = alonzoEraOnwardsConstraints w $ txBodyL . undefined -- L.reqSignerHashesTxBodyL
reqSignerHashesTxBodyL w@AlonzoEraOnwardsAlonzo = alonzoEraOnwardsConstraints w $ txBodyL . L.reqSignerHashesTxBodyL
reqSignerHashesTxBodyL w@AlonzoEraOnwardsBabbage = alonzoEraOnwardsConstraints w $ txBodyL . L.reqSignerHashesTxBodyL
reqSignerHashesTxBodyL w@AlonzoEraOnwardsConway = alonzoEraOnwardsConstraints w $ txBodyL . L.reqSignerHashesTxBodyL
reqSignerHashesTxBodyL AlonzoEraOnwardsDijkstra = error "reqSignerHashesTxBodyL: DijkstraEra not supported yet"

referenceInputsTxBodyL
:: BabbageEraOnwards era -> Lens' (LedgerTxBody era) (Set L.TxIn)
Expand Down