Skip to content

Commit

Permalink
Remove SPECIALIZE and redundatn parenthesis
Browse files Browse the repository at this point in the history
  • Loading branch information
lehins committed Dec 10, 2024
1 parent 05ab36c commit 6a283af
Show file tree
Hide file tree
Showing 75 changed files with 378 additions and 448 deletions.
4 changes: 0 additions & 4 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -158,8 +158,6 @@ newtype AlonzoTxUpgradeError = ATUEBodyUpgradeError AlonzoTxBodyUpgradeError
deriving (Show)

instance EraTx AlonzoEra where
{-# SPECIALIZE instance EraTx AlonzoEra #-}

type Tx AlonzoEra = AlonzoTx AlonzoEra
type TxUpgradeError AlonzoEra = AlonzoTxUpgradeError

Expand Down Expand Up @@ -203,8 +201,6 @@ class
isValidTxL :: Lens' (Tx era) IsValid

instance AlonzoEraTx AlonzoEra where
{-# SPECIALIZE instance AlonzoEraTx AlonzoEra #-}

isValidTxL = isValidAlonzoTxL
{-# INLINE isValidTxL #-}

Expand Down
2 changes: 0 additions & 2 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/TxCert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,6 @@ import Cardano.Ledger.Alonzo.PParams ()
import Cardano.Ledger.Shelley.TxCert

instance EraTxCert AlonzoEra where
{-# SPECIALIZE instance EraTxCert AlonzoEra #-}

type TxCert AlonzoEra = ShelleyTxCert AlonzoEra

upgradeTxCert = Right . upgradeShelleyTxCert
Expand Down
4 changes: 2 additions & 2 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/TxOut.hs
Original file line number Diff line number Diff line change
Expand Up @@ -171,7 +171,7 @@ decodeDataHash32 (DataHash32 a b c d) = do
viewCompactTxOut ::
Val (Value era) =>
AlonzoTxOut era ->
(CompactAddr, CompactForm (Value era), StrictMaybe (DataHash))
(CompactAddr, CompactForm (Value era), StrictMaybe DataHash)
viewCompactTxOut txOut = case txOut of
TxOutCompact' addr val -> (addr, val, SNothing)
TxOutCompactDH' addr val dh -> (addr, val, SJust dh)
Expand Down Expand Up @@ -433,7 +433,7 @@ mkTxOutCompact ::
Addr ->
CompactAddr ->
CompactForm (Value era) ->
StrictMaybe (DataHash) ->
StrictMaybe DataHash ->
AlonzoTxOut era
mkTxOutCompact addr cAddr cVal mdh
| isAdaOnlyCompact cVal = AlonzoTxOut addr (fromCompact cVal) mdh
Expand Down
6 changes: 1 addition & 5 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo/TxWits.hs
Original file line number Diff line number Diff line change
Expand Up @@ -296,7 +296,7 @@ isEmptyTxWitness (getMemoRawType -> AlonzoTxWitsRaw a b c d (Redeemers e)) =
Set.null a && Set.null b && Map.null c && nullDats d && Map.null e

-- =====================================================
newtype TxDatsRaw era = TxDatsRaw {unTxDatsRaw :: Map (DataHash) (Data era)}
newtype TxDatsRaw era = TxDatsRaw {unTxDatsRaw :: Map DataHash (Data era)}
deriving (Generic, Typeable, Eq)
deriving newtype (NoThunks, NFData)

Expand Down Expand Up @@ -459,8 +459,6 @@ rdmrsAlonzoTxWitsL =
{-# INLINEABLE rdmrsAlonzoTxWitsL #-}

instance EraScript AlonzoEra => EraTxWits AlonzoEra where
{-# SPECIALIZE instance EraTxWits AlonzoEra #-}

type TxWits AlonzoEra = AlonzoTxWits AlonzoEra

mkBasicTxWits = mempty
Expand All @@ -483,8 +481,6 @@ class (EraTxWits era, AlonzoEraScript era) => AlonzoEraTxWits era where
rdmrsTxWitsL :: Lens' (TxWits era) (Redeemers era)

instance EraScript AlonzoEra => AlonzoEraTxWits AlonzoEra where
{-# SPECIALIZE instance AlonzoEraTxWits AlonzoEra #-}

datsTxWitsL = datsAlonzoTxWitsL
{-# INLINE datsTxWitsL #-}

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ genAlonzoTxBody ::
UTxO AlonzoEra ->
PParams AlonzoEra ->
SlotNo ->
Set.Set (TxIn) ->
Set.Set TxIn ->
StrictSeq (TxOut AlonzoEra) ->
StrictSeq (TxCert AlonzoEra) ->
Withdrawals ->
Expand Down Expand Up @@ -603,7 +603,7 @@ someLeaf _proxy keyHash =
-- | given the "txscripts" field of the TxWits, compute the set of languages used in a transaction
langsUsed ::
AlonzoEraScript era =>
Map.Map (ScriptHash) (Script era) ->
Map.Map ScriptHash (Script era) ->
Set Language
langsUsed hashScriptMap =
Set.fromList
Expand Down
2 changes: 1 addition & 1 deletion eras/babbage/impl/src/Cardano/Ledger/Babbage/Rules/Utxo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -231,7 +231,7 @@ disjointRefInputs ::
Test (BabbageUtxoPredFailure era)
disjointRefInputs pp inputs refInputs =
when
(pvMajor (pp ^. ppProtocolVersionL) > eraProtVerHigh @(BabbageEra))
(pvMajor (pp ^. ppProtocolVersionL) > eraProtVerHigh @BabbageEra)
(failureOnNonEmpty common BabbageNonDisjointRefInputs)
where
common = inputs `Set.intersection` refInputs
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -317,7 +317,6 @@ babbageUtxowTransition ::
, AlonzoEraUTxO era
, ScriptsNeeded era ~ AlonzoScriptsNeeded era
, BabbageEraTxBody era
, Signable (DSIGN) (Hash (HASH) EraIndependentTxBody)
, Environment (EraRule "UTXOW" era) ~ UtxoEnv era
, Signal (EraRule "UTXOW" era) ~ Tx era
, State (EraRule "UTXOW" era) ~ UTxOState era
Expand Down
2 changes: 1 addition & 1 deletion eras/babbage/impl/src/Cardano/Ledger/Babbage/UTxO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ getReferenceScripts ::
BabbageEraTxOut era =>
UTxO era ->
Set TxIn ->
Map.Map (ScriptHash) (Script era)
Map.Map ScriptHash (Script era)
getReferenceScripts utxo ins = Map.fromList (getReferenceScriptsNonDistinct utxo ins)

getReferenceScriptsNonDistinct ::
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,7 @@ txb ::
forall era.
BabbageEraTxBody era =>
TxIn ->
Maybe (TxIn) ->
Maybe TxIn ->
TxOut era ->
TxBody era
txb i mRefInp o =
Expand Down
6 changes: 0 additions & 6 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Scripts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,8 +142,6 @@ instance AlonzoEraScript ConwayEra where
AlonzoRewarding (AsIx ix) -> ConwayRewarding (AsIx ix)

instance ConwayEraScript ConwayEra where
{-# SPECIALIZE instance ConwayEraScript ConwayEra #-}

mkVotingPurpose = ConwayVoting

toVotingPurpose (ConwayVoting i) = Just i
Expand All @@ -155,8 +153,6 @@ instance ConwayEraScript ConwayEra where
toProposingPurpose _ = Nothing

instance ShelleyEraScript ConwayEra where
{-# SPECIALIZE instance ShelleyEraScript ConwayEra #-}

mkRequireSignature = mkRequireSignatureTimelock
getRequireSignature = getRequireSignatureTimelock

Expand All @@ -170,8 +166,6 @@ instance ShelleyEraScript ConwayEra where
getRequireMOf = getRequireMOfTimelock

instance AllegraEraScript ConwayEra where
{-# SPECIALIZE instance AllegraEraScript ConwayEra #-}

mkTimeStart = mkTimeStartTimelock
getTimeStart = getTimeStartTimelock

Expand Down
4 changes: 0 additions & 4 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,6 @@ import GHC.Stack
import Lens.Micro ((^.))

instance EraTx ConwayEra where
{-# SPECIALIZE instance EraTx ConwayEra #-}

type Tx ConwayEra = AlonzoTx ConwayEra
type TxUpgradeError ConwayEra = TxBodyUpgradeError ConwayEra

Expand Down Expand Up @@ -133,8 +131,6 @@ tierRefScriptFee multiplier sizeIncrement
sizeIncrementRational = toInteger sizeIncrement % 1

instance AlonzoEraTx ConwayEra where
{-# SPECIALIZE instance AlonzoEraTx ConwayEra #-}

isValidTxL = isValidAlonzoTxL
{-# INLINE isValidTxL #-}

Expand Down
11 changes: 0 additions & 11 deletions eras/conway/impl/src/Cardano/Ledger/Conway/TxBody/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -347,8 +347,6 @@ data ConwayTxBodyUpgradeError
deriving (Eq, Show)

instance EraTxBody ConwayEra where
{-# SPECIALIZE instance EraTxBody ConwayEra #-}

type TxBody ConwayEra = ConwayTxBody ConwayEra
type TxBodyUpgradeError ConwayEra = ConwayTxBodyUpgradeError

Expand Down Expand Up @@ -457,14 +455,10 @@ conwayProposalsDeposits pp txBody = numProposals <×> depositPerProposal
depositPerProposal = pp ^. ppGovActionDepositL

instance AllegraEraTxBody ConwayEra where
{-# SPECIALIZE instance AllegraEraTxBody ConwayEra #-}

vldtTxBodyL = lensMemoRawType ctbrVldt (\txb x -> txb {ctbrVldt = x})
{-# INLINE vldtTxBodyL #-}

instance MaryEraTxBody ConwayEra where
{-# SPECIALIZE instance MaryEraTxBody ConwayEra #-}

mintTxBodyL = lensMemoRawType ctbrMint (\txb x -> txb {ctbrMint = x})
{-# INLINE mintTxBodyL #-}

Expand All @@ -475,8 +469,6 @@ instance MaryEraTxBody ConwayEra where
{-# INLINE mintedTxBodyF #-}

instance AlonzoEraTxBody ConwayEra where
{-# SPECIALIZE instance AlonzoEraTxBody ConwayEra #-}

collateralInputsTxBodyL =
lensMemoRawType ctbrCollateralInputs (\txb x -> txb {ctbrCollateralInputs = x})
{-# INLINE collateralInputsTxBodyL #-}
Expand All @@ -497,8 +489,6 @@ instance AlonzoEraTxBody ConwayEra where
redeemerPointerInverse = conwayRedeemerPointerInverse

instance BabbageEraTxBody ConwayEra where
{-# SPECIALIZE instance BabbageEraTxBody ConwayEra #-}

sizedOutputsTxBodyL = lensMemoRawType ctbrOutputs (\txb x -> txb {ctbrOutputs = x})
{-# INLINE sizedOutputsTxBodyL #-}

Expand All @@ -524,7 +514,6 @@ instance BabbageEraTxBody ConwayEra where
{-# INLINE allSizedOutputsTxBodyF #-}

instance ConwayEraTxBody ConwayEra where
{-# SPECIALIZE instance ConwayEraTxBody ConwayEra #-}
votingProceduresTxBodyL =
lensMemoRawType ctbrVotingProcedures (\txb x -> txb {ctbrVotingProcedures = x})
{-# INLINE votingProceduresTxBodyL #-}
Expand Down
2 changes: 1 addition & 1 deletion eras/conway/impl/src/Cardano/Ledger/Conway/TxCert.hs
Original file line number Diff line number Diff line change
Expand Up @@ -719,7 +719,7 @@ getScriptWitnessConwayTxCert = \case
ConwayTxCertPool {} -> Nothing
ConwayTxCertGov govCert -> govWitness govCert
where
govWitness :: ConwayGovCert -> Maybe (ScriptHash)
govWitness :: ConwayGovCert -> Maybe ScriptHash
govWitness = \case
ConwayAuthCommitteeHotKey coldCred _hotCred -> credScriptHash coldCred
ConwayResignCommitteeColdKey coldCred _ -> credScriptHash coldCred
Expand Down
2 changes: 1 addition & 1 deletion eras/conway/impl/src/Cardano/Ledger/Conway/TxInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -483,7 +483,7 @@ transTxBodyId txBody = PV3.TxId (transSafeHash (hashAnnotated txBody))
transTxIn :: TxIn -> PV3.TxOutRef
transTxIn (TxIn txid txIx) = PV3.TxOutRef (transTxId txid) (toInteger (txIxToInt txIx))

transMintValue :: MultiAsset c -> PV3.MintValue
transMintValue :: MultiAsset -> PV3.MintValue
transMintValue = PV3.UnsafeMintValue . PV1.getValue . Alonzo.transMultiAsset

-- | Translate all `Withdrawal`s from within a `TxBody`
Expand Down
6 changes: 0 additions & 6 deletions eras/conway/impl/src/Cardano/Ledger/Conway/TxOut.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,6 @@ import Data.Maybe.Strict (StrictMaybe (..))
import Lens.Micro

instance EraTxOut ConwayEra where
{-# SPECIALIZE instance EraTxOut ConwayEra #-}

type TxOut ConwayEra = BabbageTxOut ConwayEra

mkBasicTxOut addr vl = BabbageTxOut addr vl NoDatum SNothing
Expand All @@ -50,17 +48,13 @@ instance EraTxOut ConwayEra where
getMinCoinSizedTxOut = babbageMinUTxOValue

instance AlonzoEraTxOut ConwayEra where
{-# SPECIALIZE instance AlonzoEraTxOut ConwayEra #-}

dataHashTxOutL = dataHashBabbageTxOutL
{-# INLINE dataHashTxOutL #-}

datumTxOutF = to getDatumBabbageTxOut
{-# INLINE datumTxOutF #-}

instance BabbageEraTxOut ConwayEra where
{-# SPECIALIZE instance BabbageEraTxOut ConwayEra #-}

dataTxOutL = dataBabbageTxOutL
{-# INLINE dataTxOutL #-}

Expand Down
4 changes: 0 additions & 4 deletions eras/conway/impl/src/Cardano/Ledger/Conway/TxWits.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,6 @@ import Cardano.Ledger.Conway.Scripts ()
import Cardano.Ledger.Core

instance EraTxWits ConwayEra where
{-# SPECIALIZE instance EraTxWits ConwayEra #-}

type TxWits ConwayEra = AlonzoTxWits ConwayEra

mkBasicTxWits = mempty
Expand All @@ -50,8 +48,6 @@ instance EraTxWits ConwayEra where
}

instance AlonzoEraTxWits ConwayEra where
{-# SPECIALIZE instance AlonzoEraTxWits ConwayEra #-}

datsTxWitsL = datsAlonzoTxWitsL
{-# INLINE datsTxWitsL #-}

Expand Down
4 changes: 0 additions & 4 deletions eras/mary/impl/src/Cardano/Ledger/Mary/Scripts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,6 @@ instance EraScript MaryEra where
fromNativeScript = id

instance ShelleyEraScript MaryEra where
{-# SPECIALIZE instance ShelleyEraScript MaryEra #-}

mkRequireSignature = mkRequireSignatureTimelock
getRequireSignature = getRequireSignatureTimelock

Expand All @@ -46,8 +44,6 @@ instance ShelleyEraScript MaryEra where
getRequireMOf = getRequireMOfTimelock

instance AllegraEraScript MaryEra where
{-# SPECIALIZE instance AllegraEraScript MaryEra #-}

mkTimeStart = mkTimeStartTimelock
getTimeStart = getTimeStartTimelock

Expand Down
2 changes: 0 additions & 2 deletions eras/mary/impl/src/Cardano/Ledger/Mary/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,6 @@ import Cardano.Ledger.Shelley.Tx (
-- ========================================

instance EraTx MaryEra where
{-# SPECIALIZE instance EraTx MaryEra #-}

type Tx MaryEra = ShelleyTx MaryEra

mkBasicTx = mkBasicShelleyTx
Expand Down
8 changes: 0 additions & 8 deletions eras/mary/impl/src/Cardano/Ledger/Mary/TxBody/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -233,8 +233,6 @@ lensMaryTxBodyRaw getter setter =
{-# INLINEABLE lensMaryTxBodyRaw #-}

instance EraTxBody MaryEra where
{-# SPECIALIZE instance EraTxBody MaryEra #-}

type TxBody MaryEra = MaryTxBody MaryEra

mkBasicTxBody = mkMemoized $ MaryTxBodyRaw emptyAllegraTxBodyRaw
Expand Down Expand Up @@ -288,8 +286,6 @@ instance EraTxBody MaryEra where
}

instance ShelleyEraTxBody MaryEra where
{-# SPECIALIZE instance ShelleyEraTxBody MaryEra #-}

ttlTxBodyL = notSupportedInThisEraL
{-# INLINEABLE ttlTxBodyL #-}

Expand All @@ -298,16 +294,12 @@ instance ShelleyEraTxBody MaryEra where
{-# INLINEABLE updateTxBodyL #-}

instance AllegraEraTxBody MaryEra where
{-# SPECIALIZE instance AllegraEraTxBody MaryEra #-}

vldtTxBodyL =
lensMaryTxBodyRaw atbrValidityInterval $
\txBodyRaw vldt -> txBodyRaw {atbrValidityInterval = vldt}
{-# INLINEABLE vldtTxBodyL #-}

instance MaryEraTxBody MaryEra where
{-# SPECIALIZE instance MaryEraTxBody MaryEra #-}

mintTxBodyL =
lensMaryTxBodyRaw atbrMint (\txBodyRaw mint -> txBodyRaw {atbrMint = mint})
{-# INLINEABLE mintTxBodyL #-}
Expand Down
2 changes: 0 additions & 2 deletions eras/mary/impl/src/Cardano/Ledger/Mary/TxOut.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,8 +18,6 @@ import Data.Coerce (coerce)
import Lens.Micro ((^.))

instance EraTxOut MaryEra where
{-# SPECIALIZE instance EraTxOut MaryEra #-}

type TxOut MaryEra = ShelleyTxOut MaryEra

mkBasicTxOut = ShelleyTxOut
Expand Down
1 change: 0 additions & 1 deletion eras/mary/impl/src/Cardano/Ledger/Mary/TxSeq.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,6 @@ import Cardano.Ledger.Mary.Tx ()
import Cardano.Ledger.Shelley.BlockChain (ShelleyTxSeq (..), bbHash, txSeqTxns)

instance EraSegWits MaryEra where
{-# SPECIALIZE instance EraSegWits MaryEra #-}
type TxSeq MaryEra = ShelleyTxSeq MaryEra
fromTxSeq = txSeqTxns
toTxSeq = ShelleyTxSeq
Expand Down
2 changes: 0 additions & 2 deletions eras/mary/impl/src/Cardano/Ledger/Mary/TxWits.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,6 @@ import Cardano.Ledger.Shelley.TxWits (
)

instance EraTxWits MaryEra where
{-# SPECIALIZE instance EraTxWits MaryEra #-}

type TxWits MaryEra = ShelleyTxWits MaryEra

mkBasicTxWits = mempty
Expand Down
6 changes: 3 additions & 3 deletions eras/shelley/impl/src/Cardano/Ledger/Shelley/BlockChain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -144,11 +144,11 @@ pattern ShelleyTxSeq xs <-
encodePair metadata = encCBOR index <> encodePreEncoded metadata
in TxSeq'
{ txSeqTxns' = txns
, -- bytes encoding Seq(TxBody era)
, -- bytes encoding "Seq (TxBody era)"
txSeqBodyBytes = serializeFoldable $ coreBodyBytes @era <$> txns
, -- bytes encoding Seq(TxWits era)
, -- bytes encoding "Seq (TxWits era)"
txSeqWitsBytes = serializeFoldable $ coreWitnessBytes @era <$> txns
, -- bytes encoding a (Map Int (TxAuxData))
, -- bytes encoding a "Map Int TxAuxData"
txSeqMetadataBytes =
serialize version . encodeFoldableMapEncoder metaChunk $
coreAuxDataBytes @era <$> txns
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -208,7 +208,7 @@ data FreeVars = FreeVars
, fvAddrsRew :: !(Set (Credential 'Staking))
, fvTotalStake :: !Coin
, fvProtVer :: !ProtVer
, fvPoolRewardInfo :: !(Map (KeyHash 'StakePool) (PoolRewardInfo))
, fvPoolRewardInfo :: !(Map (KeyHash 'StakePool) PoolRewardInfo)
}
deriving (Eq, Show, Generic)
deriving (NoThunks)
Expand Down
Loading

0 comments on commit 6a283af

Please sign in to comment.