Skip to content

Commit

Permalink
Merge pull request #2510 from input-output-hk/jc/parametrize-block-by…
Browse files Browse the repository at this point in the history
…-header

parameterize Block by the header type
  • Loading branch information
nc6 committed Oct 12, 2021
2 parents dd970d0 + 98e21f5 commit 6a73c8a
Show file tree
Hide file tree
Showing 77 changed files with 879 additions and 640 deletions.
4 changes: 2 additions & 2 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ import Cardano.Ledger.Alonzo.TxInfo (validScript)
import qualified Cardano.Ledger.Alonzo.TxSeq as Alonzo (TxSeq (..), hashTxSeq)
import Cardano.Ledger.Alonzo.TxWitness (TxWitness (..))
import Cardano.Ledger.AuxiliaryData (AuxiliaryDataHash (..), ValidateAuxiliaryData (..))
import qualified Cardano.Ledger.BaseTypes as Shelley
import Cardano.Ledger.BaseTypes (BlocksMade (..))
import Cardano.Ledger.Coin
import qualified Cardano.Ledger.Core as Core
import qualified Cardano.Ledger.Crypto as CC
Expand Down Expand Up @@ -178,7 +178,7 @@ instance
pp = sgProtocolParams sg

instance (CC.Crypto c) => UsesTxOut (AlonzoEra c) where
makeTxOut _proxy addr val = TxOut addr val Shelley.SNothing
makeTxOut _proxy addr val = TxOut addr val SNothing

instance CC.Crypto c => API.CLI (AlonzoEra c) where
evaluateMinFee = minfee
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -57,13 +57,13 @@ import Cardano.Ledger.Shelley.Scripts (ScriptHash (..))
import Cardano.Ledger.Shelley.TxBody
( DelegCert (..),
Delegation (..),
TxIn (..),
Wdrl (..),
getRwdCred,
witKeyHash,
)
import Cardano.Ledger.Shelley.UTxO (UTxO (..), getScriptHash, scriptCred)
import Cardano.Ledger.ShelleyMA.Timelocks (evalTimelock)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Slotting.EpochInfo (EpochInfo)
import Cardano.Slotting.Time (SystemStart)
import Data.Coders
Expand Down
7 changes: 4 additions & 3 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Bbody.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ import qualified Cardano.Ledger.Alonzo.TxSeq as Alonzo (TxSeq)
import Cardano.Ledger.Alonzo.TxWitness (TxWitness)
import Cardano.Ledger.BHeaderView (BHeaderView (..), isOverlaySlot)
import Cardano.Ledger.BaseTypes (ShelleyBase, UnitInterval, epochInfo)
import Cardano.Ledger.Block (Block (..))
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Era (Era (Crypto), SupportsSegWit (..))
import qualified Cardano.Ledger.Era as Era
Expand Down Expand Up @@ -120,7 +121,7 @@ bbodyTransition ::
forall (someBBODY :: Type -> Type) era.
( -- Conditions that the Abstract someBBODY must meet
STS (someBBODY era),
Signal (someBBODY era) ~ (BHeaderView (Crypto era), TxSeq era),
Signal (someBBODY era) ~ (Block BHeaderView era),
PredicateFailure (someBBODY era) ~ AlonzoBbodyPredFail era,
BaseM (someBBODY era) ~ ShelleyBase,
State (someBBODY era) ~ BbodyState era,
Expand All @@ -144,7 +145,7 @@ bbodyTransition =
>>= \( TRC
( BbodyEnv pp account,
BbodyState ls b,
(bh, txsSeq)
(UnserialisedBlock bh txsSeq)
)
) -> do
let txs = txSeqTxns txsSeq
Expand Down Expand Up @@ -218,7 +219,7 @@ instance

type
Signal (AlonzoBBODY era) =
(BHeaderView (Crypto era), TxSeq era)
(Block BHeaderView era)

type Environment (AlonzoBBODY era) = BbodyEnv era

Expand Down
3 changes: 2 additions & 1 deletion eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Utxos.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,9 @@ import qualified Cardano.Ledger.Shelley.LedgerState as Shelley
import Cardano.Ledger.Shelley.PParams (Update)
import Cardano.Ledger.Shelley.Rules.Ppup (PPUP, PPUPEnv (..), PpupPredicateFailure)
import Cardano.Ledger.Shelley.Rules.Utxo (UtxoEnv (..))
import Cardano.Ledger.Shelley.TxBody (DCert, TxIn (..), Wdrl)
import Cardano.Ledger.Shelley.TxBody (DCert, Wdrl)
import Cardano.Ledger.Shelley.UTxO (balance, totalDeposits)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.Val as Val
import Control.Iterate.SetAlgebra (eval, (∪), (⋪), (◁))
import Control.Monad.Except (MonadError (throwError))
Expand Down
3 changes: 2 additions & 1 deletion eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -135,8 +135,9 @@ import Cardano.Ledger.SafeHash
import Cardano.Ledger.Shelley.Address.Bootstrap (BootstrapWitness)
import Cardano.Ledger.Shelley.Delegation.Certificates (DCert (..))
import Cardano.Ledger.Shelley.Scripts (ScriptHash)
import Cardano.Ledger.Shelley.TxBody (TxIn (..), Wdrl (..), WitVKey, unWdrl)
import Cardano.Ledger.Shelley.TxBody (Wdrl (..), WitVKey, unWdrl)
import qualified Cardano.Ledger.Shelley.UTxO as Shelley
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.Val (Val (coin, (<+>), (<×>)))
import Control.DeepSeq (NFData (..))
import qualified Data.ByteString.Lazy as LBS
Expand Down
3 changes: 2 additions & 1 deletion eras/alonzo/impl/src/Cardano/Ledger/Alonzo/TxBody.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,8 +113,9 @@ import Cardano.Ledger.Shelley.CompactAddr (CompactAddr, compactAddr, decompactAd
import Cardano.Ledger.Shelley.Delegation.Certificates (DCert)
import Cardano.Ledger.Shelley.PParams (Update)
import Cardano.Ledger.Shelley.Scripts (ScriptHash)
import Cardano.Ledger.Shelley.TxBody (TxIn (..), Wdrl (Wdrl), unWdrl)
import Cardano.Ledger.Shelley.TxBody (Wdrl (Wdrl), unWdrl)
import Cardano.Ledger.ShelleyMA.Timelocks (ValidityInterval (..), ppValidityInterval)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.Val
( DecodeNonNegative,
decodeMint,
Expand Down
3 changes: 1 addition & 2 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/TxInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,13 +52,12 @@ import Cardano.Ledger.Shelley.TxBody
Delegation (..),
PoolCert (..),
PoolParams (..),
TxId (..),
TxIn (..),
Wdrl (..),
WitVKey (..),
)
import Cardano.Ledger.Shelley.UTxO (UTxO (..))
import Cardano.Ledger.ShelleyMA.Timelocks (ValidityInterval (..))
import Cardano.Ledger.TxIn (TxId (..), TxIn (..))
import Cardano.Ledger.Val (Val (..))
import Cardano.Slotting.EpochInfo (EpochInfo, epochInfoSlotToUTCTime)
import Cardano.Slotting.Slot (EpochNo (..), SlotNo (..))
Expand Down
1 change: 1 addition & 0 deletions eras/alonzo/test-suite/cardano-ledger-alonzo-test.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -96,6 +96,7 @@ test-suite cardano-ledger-alonzo-test
cardano-ledger-shelley-ma,
cardano-ledger-core,
cardano-ledger-shelley-ma-test,
cardano-protocol-tpraos,
cardano-slotting,
containers,
data-default-class,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -52,10 +52,11 @@ import Cardano.Ledger.Keys (KeyHash, KeyRole (Witness))
import Cardano.Ledger.Mary (MaryEra)
import Cardano.Ledger.Mary.Value (AssetName (..), PolicyID (..), Value, policies, valueFromList)
import Cardano.Ledger.Shelley.PParams (Update)
import Cardano.Ledger.Shelley.TxBody (DCert, TxIn, Wdrl)
import Cardano.Ledger.Shelley.TxBody (DCert, Wdrl)
import Cardano.Ledger.Shelley.UTxO (UTxO (..), balance)
import Cardano.Ledger.ShelleyMA.AuxiliaryData as Mary (pattern AuxiliaryData)
import Cardano.Ledger.ShelleyMA.Timelocks (Timelock (..))
import Cardano.Ledger.TxIn (TxIn)
import Cardano.Ledger.Val (Val (coin), adaOnly, (<+>), (<×>))
import Cardano.Slotting.Slot (SlotNo (..))
import Control.Iterate.SetAlgebra (eval, (◁))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -16,9 +16,10 @@ import Cardano.Ledger.Alonzo.Rules.Utxow (AlonzoPredFail)
import Cardano.Ledger.Alonzo.Scripts (Script, decodeCostModel)
import Cardano.Ledger.Alonzo.TxBody (TxBody)
import Cardano.Ledger.Alonzo.TxWitness
import Cardano.Ledger.Shelley.BlockChain (Block)
import Cardano.Ledger.Block (Block)
import Cardano.Ledger.Shelley.Metadata (Metadata)
import qualified Cardano.Ledger.Shelley.Tx as LTX
import Cardano.Protocol.TPraos.BHeader (BHeader)
import qualified Data.ByteString.Base16.Lazy as Base16
import qualified Data.ByteString.Lazy.Char8 as BSL
import Test.Cardano.Ledger.Alonzo.Serialisation.Generators ()
Expand Down Expand Up @@ -99,5 +100,5 @@ tests =
testProperty "alonzo/Tx" $
trippingAnn @(LTX.Tx (AlonzoEra C_Crypto)),
testProperty "alonzo/Block" $
trippingAnn @(Block (AlonzoEra C_Crypto))
trippingAnn @(Block BHeader (AlonzoEra C_Crypto))
]
10 changes: 6 additions & 4 deletions eras/alonzo/test-suite/test/Test/Cardano/Ledger/Alonzo/Trials.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,14 +58,14 @@ import Cardano.Ledger.Alonzo.Scripts (ppScript)
import Cardano.Ledger.Alonzo.Tx (ValidatedTx)
import Cardano.Ledger.Alonzo.TxBody ()
import Cardano.Ledger.BaseTypes (Globals)
import Cardano.Ledger.Block (Block)
import Cardano.Ledger.Coin (Coin (..))
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Era (Era (Crypto))
import Cardano.Ledger.Hashes (EraIndependentData)
import Cardano.Ledger.Pretty (PDoc, PrettyA (..))
import Cardano.Ledger.SafeHash (SafeHash, hashAnnotated)
import Cardano.Ledger.Shelley (ShelleyEra)
import Cardano.Ledger.Shelley.BlockChain (Block)
import Cardano.Ledger.Shelley.Constraints
( TransValue,
UsesAuxiliary,
Expand All @@ -88,7 +88,9 @@ import Cardano.Ledger.Shelley.Rules.Delegs (DelegsEnv)
import Cardano.Ledger.Shelley.Rules.Delpl (DelplEnv, DelplPredicateFailure)
import Cardano.Ledger.Shelley.Rules.Ledger (LedgerEnv (..))
import Cardano.Ledger.Shelley.Rules.Utxo (UtxoEnv)
import Cardano.Ledger.Shelley.TxBody (DCert, TxIn)
import Cardano.Ledger.Shelley.TxBody (DCert)
import Cardano.Ledger.TxIn (TxIn)
import Cardano.Protocol.TPraos.BHeader (BHeader)
import Cardano.Slotting.Slot (SlotNo (..))
import Control.Monad.Trans.Reader (runReaderT)
import Control.State.Transition
Expand Down Expand Up @@ -239,7 +241,7 @@ ledgerEnv = LedgerEnv (SlotNo 0) 0 def (AccountState (Coin 0) (Coin 0))
genAlonzoTx :: Gen (Core.Tx A)
genAlonzoTx = genstuff ap (\genv _cs _nep _ep _ls _pp utxo dp _d _p -> genTx genv ledgerEnv (utxo, dp))

genAlonzoBlock :: Gen (Block A)
genAlonzoBlock :: Gen (Block BHeader A)
genAlonzoBlock = genstuff ap (\genv cs _nep _ep _ls _pp _utxo _dp _d _p -> genBlock genv cs)

genShelleyTx :: Gen (Core.Tx (ShelleyEra TestCrypto))
Expand All @@ -248,7 +250,7 @@ genShelleyTx =
(Proxy @(ShelleyEra TestCrypto))
(\genv _cs _nep _ep _ls _pp utxo dp _d _p -> genTx genv ledgerEnv (utxo, dp))

genShelleyBlock :: Gen (Block (ShelleyEra TestCrypto))
genShelleyBlock :: Gen (Block BHeader (ShelleyEra TestCrypto))
genShelleyBlock = genstuff (Proxy @(ShelleyEra TestCrypto)) (\genv cs _nep _ep _ls _pp _utxo _dp _d _p -> genBlock genv cs)

-- ==================================================================================================
Expand Down
3 changes: 2 additions & 1 deletion eras/shelley-ma/impl/src/Cardano/Ledger/Allegra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,11 +19,12 @@ module Cardano.Ledger.Allegra
)
where

import Cardano.Ledger.BaseTypes (BlocksMade (..))
import Cardano.Ledger.Crypto (Crypto)
import qualified Cardano.Ledger.Crypto as CC
import qualified Cardano.Ledger.Era as E (Era (Crypto))
import Cardano.Ledger.Shelley.API hiding (PParams, Tx, TxBody, TxOut, WitnessSet)
import Cardano.Ledger.Shelley.EpochBoundary (BlocksMade (..), emptySnapShots)
import Cardano.Ledger.Shelley.EpochBoundary (emptySnapShots)
import Cardano.Ledger.Shelley.LedgerState (minfee)
import qualified Cardano.Ledger.Shelley.PParams as Shelley (PParamsUpdate)
import Cardano.Ledger.Shelley.Tx (WitnessSet)
Expand Down
3 changes: 2 additions & 1 deletion eras/shelley-ma/impl/src/Cardano/Ledger/Mary.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,12 +18,13 @@ module Cardano.Ledger.Mary
)
where

import Cardano.Ledger.BaseTypes (BlocksMade (..))
import Cardano.Ledger.Crypto (Crypto)
import qualified Cardano.Ledger.Crypto as CC
import qualified Cardano.Ledger.Era as E (Era (Crypto))
import qualified Cardano.Ledger.Mary.Value as V (Value)
import Cardano.Ledger.Shelley.API hiding (TxBody)
import Cardano.Ledger.Shelley.EpochBoundary (BlocksMade (..), emptySnapShots)
import Cardano.Ledger.Shelley.EpochBoundary (emptySnapShots)
import Cardano.Ledger.Shelley.LedgerState (minfee)
import qualified Cardano.Ledger.Shelley.PParams as Shelley (PParamsUpdate)
import Cardano.Ledger.ShelleyMA
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -74,11 +74,11 @@ import Cardano.Ledger.Shelley.Constraints (TransValue)
import Cardano.Ledger.Shelley.PParams (Update)
import Cardano.Ledger.Shelley.TxBody
( DCert (..),
TxIn (..),
TxOut (..),
Wdrl (..),
)
import Cardano.Ledger.ShelleyMA.Timelocks (ValidityInterval (..), ppValidityInterval)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.Val
( DecodeMint (..),
DecodeNonNegative,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -37,12 +37,13 @@ import Cardano.Ledger.Shelley.Constraints
)
import Cardano.Ledger.Shelley.PParams (PParams, PParams' (..), Update)
import Cardano.Ledger.Shelley.Tx (pattern Tx, pattern WitnessSet)
import Cardano.Ledger.Shelley.TxBody (DCert, TxIn, TxOut (..), Wdrl)
import Cardano.Ledger.Shelley.TxBody (DCert, TxOut (..), Wdrl)
import Cardano.Ledger.ShelleyMA.Timelocks (Timelock (..))
import Cardano.Ledger.ShelleyMA.TxBody
( TxBody (..),
ValidityInterval (ValidityInterval),
)
import Cardano.Ledger.TxIn (TxIn)
import Cardano.Ledger.Val (Val (zero), (<+>))
import Cardano.Slotting.Slot (SlotNo (SlotNo))
import Control.Monad (replicateM)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import qualified Cardano.Ledger.Shelley.API as S
import Cardano.Ledger.Shelley.LedgerState ()
import Cardano.Ledger.Shelley.PParams (emptyPParams)
import Cardano.Ledger.Shelley.Tx (hashScript, scriptWits)
import Cardano.Ledger.Shelley.UTxO (txid)
import Cardano.Ledger.TxIn (txid)
import qualified Cardano.Ledger.Val as Val
import Cardano.Slotting.Slot (SlotNo (..))
import Control.Monad.Except (runExcept)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -30,17 +30,13 @@ import Cardano.Ledger.Shelley.Tx
WitnessSetHKD (..),
hashScript,
)
import Cardano.Ledger.Shelley.TxBody
( TxId,
TxIn (..),
TxOut (..),
Wdrl (..),
)
import Cardano.Ledger.Shelley.UTxO (UTxO (..), makeWitnessesVKey, txid)
import Cardano.Ledger.Shelley.TxBody (TxOut (..), Wdrl (..))
import Cardano.Ledger.Shelley.UTxO (UTxO (..), makeWitnessesVKey)
import Cardano.Ledger.ShelleyMA.Rules.Utxo (UtxoPredicateFailure (..))
import Cardano.Ledger.ShelleyMA.Timelocks (Timelock (..), ValidityInterval (..))
import Cardano.Ledger.ShelleyMA.TxBody (TxBody (..))
import Cardano.Ledger.Slot (SlotNo (..))
import Cardano.Ledger.TxIn (TxId, TxIn (..), txid)
import Cardano.Ledger.Val ((<+>), (<->))
import qualified Cardano.Ledger.Val as Val
import Control.Exception (ErrorCall (ErrorCall), evaluate, try)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,6 @@ import Cardano.Ledger.Shelley.TxBody
( DCert (..),
DelegCert (..),
RewardAcnt (..),
TxIn (..),
TxOut (..),
Wdrl (..),
)
Expand All @@ -44,6 +43,7 @@ import Cardano.Ledger.ShelleyMA.Timelocks
)
import Cardano.Ledger.ShelleyMA.TxBody (TxBody (..))
import Cardano.Ledger.Slot (EpochNo (..), SlotNo (..))
import Cardano.Ledger.TxIn (TxIn (..))
import qualified Cardano.Ledger.Val as Val
import Codec.CBOR.Encoding (Tokens (..))
import qualified Data.ByteString.Char8 as BS
Expand Down
19 changes: 9 additions & 10 deletions eras/shelley/impl/src/Cardano/Ledger/Pretty.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Cardano.Ledger.Address
import Cardano.Ledger.AuxiliaryData (AuxiliaryDataHash (..))
import Cardano.Ledger.BaseTypes
( ActiveSlotCoeff,
BlocksMade (..),
BoundedRational (..),
DnsName,
FixedPoint,
Expand All @@ -42,6 +43,7 @@ import Cardano.Ledger.BaseTypes
activeSlotVal,
dnsToText,
)
import Cardano.Ledger.Block (Block (..))
import Cardano.Ledger.Coin (Coin (..), DeltaCoin (..))
import Cardano.Ledger.Compactible (Compactible (..))
import Cardano.Ledger.Core (PParamsDelta)
Expand All @@ -54,6 +56,7 @@ import Cardano.Ledger.Credential
)
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.Era (Era)
import qualified Cardano.Ledger.Era as E (Crypto)
import qualified Cardano.Ledger.Era as Era (TxSeq)
import Cardano.Ledger.Keys
( GKeys (..),
Expand All @@ -67,11 +70,9 @@ import Cardano.Ledger.Keys
)
import Cardano.Ledger.SafeHash (SafeHash, extractHash)
import Cardano.Ledger.Shelley.Address.Bootstrap (BootstrapWitness (..), ChainCode (..))
import Cardano.Ledger.Shelley.BlockChain (Block (..))
import Cardano.Ledger.Shelley.CompactAddr (CompactAddr (..), decompactAddr)
import Cardano.Ledger.Shelley.EpochBoundary
( BlocksMade (..),
SnapShot (..),
( SnapShot (..),
SnapShots (..),
Stake (..),
)
Expand Down Expand Up @@ -137,12 +138,9 @@ import Cardano.Ledger.Shelley.TxBody
StakePoolRelay (..),
TxBody (..),
TxBodyRaw (..),
TxId (..),
TxIn (..),
TxOut (..),
Wdrl (..),
WitVKey (..),
viewTxIn,
)
import Cardano.Ledger.Shelley.UTxO (UTxO (..))
import Cardano.Ledger.Slot
Expand All @@ -152,6 +150,7 @@ import Cardano.Ledger.Slot
EpochSize (..),
SlotNo (..),
)
import Cardano.Ledger.TxIn (TxId (..), TxIn (..), viewTxIn)
import Cardano.Protocol.TPraos (IndividualPoolStake (..), PoolDistr (..))
import Cardano.Protocol.TPraos.BHeader
( BHBody (..),
Expand Down Expand Up @@ -436,11 +435,11 @@ ppBHeader (BHeader bh sig) =
("Sig", viaShow sig)
]

ppBlock :: (Era era, PrettyA (Era.TxSeq era)) => Block era -> PDoc
ppBlock (Block' bh seqx _) =
ppBlock :: (PrettyA (Era.TxSeq era), PrettyA (h (E.Crypto era))) => Block h era -> PDoc
ppBlock (UnserialisedBlock bh seqx) =
ppRecord
"Block"
[ ("Header", ppBHeader bh),
[ ("Header", prettyA bh),
("TxSeq", prettyA seqx)
]

Expand All @@ -453,7 +452,7 @@ instance Crypto c => PrettyA (BHeader c) where
instance PrettyA (PrevHash c) where
prettyA = ppPrevHash

instance (Era era, PrettyA (Era.TxSeq era)) => PrettyA (Block era) where
instance (Era era, PrettyA (Era.TxSeq era), PrettyA (h (E.Crypto era))) => PrettyA (Block h era) where
prettyA = ppBlock

-- =================================
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import qualified Cardano.Chain.Common as Byron
import qualified Cardano.Chain.UTxO as Byron
import qualified Cardano.Crypto.Hash as Crypto
import qualified Cardano.Crypto.Hashing as Hashing
import Cardano.Ledger.BaseTypes (BlocksMade (..))
import Cardano.Ledger.Chain (pparamsToChainChecksPParams)
import Cardano.Ledger.Coin (CompactForm (CompactCoin))
import qualified Cardano.Ledger.Crypto as CC
Expand Down
Loading

0 comments on commit 6a73c8a

Please sign in to comment.