Skip to content

Commit

Permalink
Fixup haddock and constrained instance
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed May 6, 2024
1 parent ec4f332 commit bd0c660
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 25 deletions.
37 changes: 18 additions & 19 deletions libs/cardano-ledger-core/src/Cardano/Ledger/Plutus/CostModels.hs
Original file line number Diff line number Diff line change
Expand Up @@ -248,22 +248,22 @@ decodeCostModels =
decodeCostModelsFailing
{-# INLINEABLE decodeCostModels #-}

-- | Number of parameters in a CostModel for a specific language. Starting with `PlutusV3`
-- we support variable number of parameters.
-- | Initial number of parameters in a CostModel for a specific language when the language was
-- introduced. Starting with Conway we support variable number of parameters, therefore
-- do not expect this number to reflect the reality on the number of supported parameters.
costModelParamsCount :: Language -> Int
costModelParamsCount PlutusV1 = 166
costModelParamsCount PlutusV2 = 175
costModelParamsCount lang = length $ plutusVXParamNames lang

-- | Prior to version 9, each 'CostModel' was expected to be serialized as
-- an array of integers of a specific length (depending on the version of Plutus).
-- Starting in version 9, we allow the decoders to accept lists longer than what they
-- require, so that new fields can be added in the future.
-- For this reason, we must hard code the length expectation into the deserializers
-- prior to version 9.
costModelParamsCount PlutusV3 = 233

-- | Prior to version 9, each 'CostModel' was expected to be serialized as an array of
-- integers of a specific length (depending on the version of Plutus). Starting in
-- version 9, we allow the decoders to accept lists longer or shorter than what they
-- require, so that new fields can be added in the future. For this reason, we must hard
-- code the length expectation into the deserializers prior to version 9.
--
-- Note that the number of elements in the V1 and V2 cost models
-- may change in the future, they are only fixed prior to version 9.
-- Note that the number of elements in the V1 and V2 cost models may change in the future,
-- they are only fixed prior to version 9.
--
-- See https://github.com/intersectmbo/cardano-ledger/issues/2902
-- and https://github.com/intersectmbo/cardano-ledger/blob/master/docs/adr/2022-12-05_006-cost-model-serialization.md
Expand Down Expand Up @@ -354,9 +354,8 @@ mkCostModels cms = CostModels cms mempty
-- | This function attempts to convert a Map with potential cost models into validated
-- 'CostModels'. If it is a valid cost model for a known version of Plutus, it is added
-- to 'costModelsValid'. If it is an invalid cost model for a known version of Plutus, the
-- function will fail witha string version of 'P.CostModelApplyError' and the cost model
-- is stored in 'costModelsUnknown'. Lastly, if the Plutus version is unknown, the cost
-- model is also stored in 'costModelsUnknown'.
-- function will fail with a string version of 'P.CostModelApplyError'. Lastly, if the
-- Plutus version is unknown, the cost model is also stored in 'costModelsUnknown'.
mkCostModelsLenient :: MonadFail m => Map Word8 [Int64] -> m CostModels
mkCostModelsLenient = Map.foldrWithKey addRawCostModel (pure (CostModels mempty mempty))
where
Expand All @@ -370,10 +369,10 @@ mkCostModelsLenient = Map.foldrWithKey addRawCostModel (pure (CostModels mempty
Left err -> fail $ "CostModel contruction failure: " ++ show err
Nothing -> pure $ CostModels validCostModels (Map.insert langW8 cmIds unknownCostModels)

-- | Turn a 'CostModels' into a mapping of potential language versions and
-- cost model values, with no distinction between valid and invalid cost models.
-- This is used for serialization, so that judgements about validity can be made
-- upon deserialization.
-- | Turn a 'CostModels' into a mapping of potential language versions and cost model
-- values, with no distinction between valid and unknown cost models. This is used for
-- serialization, so that judgements about known languages can be made upon
-- deserialization.
flattenCostModels :: CostModels -> Map Word8 [Int64]
flattenCostModels (CostModels validCostModels unknownCostModels) =
Map.foldrWithKey
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -112,7 +112,6 @@ import Cardano.Ledger.Shelley.LedgerState hiding (ptrMap)
import Cardano.Ledger.Shelley.PoolRank
import Cardano.Ledger.Shelley.Rules
import Cardano.Ledger.Shelley.TxAuxData (Metadatum)
import Cardano.Ledger.Tools (boom)
import Cardano.Ledger.TxIn (TxId (..), TxIn (..))
import Cardano.Ledger.UMap
import Cardano.Ledger.UTxO
Expand Down Expand Up @@ -880,12 +879,19 @@ instance IsConwayUniv fn => HasSpec fn CoinPerByte

instance HasSimpleRep CostModels
instance IsConwayUniv fn => HasSpec fn CostModels where
emptySpec =
Cartesian
(constrained $ \m -> size_ (dom_ m) <=. 3)
boom
type TypeSpec fn CostModels = ()
emptySpec = ()
combineSpec _ _ = TrueSpec
genFromTypeSpec _ = pureGen arbitrary
shrinkWithTypeSpec _ = shrink
conformsTo _ _ = True
toPreds _ _ = toPred True

-- (constrained $ \p -> size_ (dom_ (fst_ $ fromGeneric_ p)) <=. 3)
-- FIXME: previous implementation no longer builds
-- emptySpec =
-- Cartesian
-- (constrained $ \m -> size_ (dom_ m) <=. 3)
-- (constrained $ \p -> size_ (dom_ (fst_ $ fromGeneric_ p)) <=. 3)

instance HasSimpleRep PoolVotingThresholds
instance IsConwayUniv fn => HasSpec fn PoolVotingThresholds
Expand Down

0 comments on commit bd0c660

Please sign in to comment.