{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Cardano.Ledger.Generic.Same where
import Cardano.Ledger.Allegra.TxBody (TxBody (..))
import Cardano.Ledger.Alonzo.Tx (AlonzoTx (..))
import Cardano.Ledger.Alonzo.TxBody (TxBody (..))
import Cardano.Ledger.Alonzo.TxSeq (AlonzoTxSeq (..))
import Cardano.Ledger.Alonzo.TxWits (AlonzoTxWits (..), Redeemers (..), TxDats (..))
import Cardano.Ledger.Babbage.TxBody (TxBody (..))
import Cardano.Ledger.Binary (sizedValue)
import Cardano.Ledger.Block (Block (..))
import Cardano.Ledger.Conway.Core
import Cardano.Ledger.Conway.Governance (VotingProcedures (..))
import Cardano.Ledger.Conway.State (VState (..))
import Cardano.Ledger.Conway.TxBody (TxBody (..))
import Cardano.Ledger.Mary (TxBody (..))
import Cardano.Ledger.Shelley.API.Mempool (ApplyTxError)
import Cardano.Ledger.Shelley.BlockChain (ShelleyTxSeq (..))
import Cardano.Ledger.Shelley.LedgerState (
DState (..),
EpochState (..),
LedgerState (..),
NewEpochState (..),
PState (..),
StashedAVVMAddresses,
UTxOState (..),
curPParamsEpochStateL,
prevPParamsEpochStateL,
)
import Cardano.Ledger.Shelley.PParams (ProposedPPUpdates (..))
import Cardano.Ledger.Shelley.Translation ()
import Cardano.Ledger.Shelley.Tx (ShelleyTx (..))
import Cardano.Ledger.Shelley.TxWits (ShelleyTxWits (..))
import Cardano.Ledger.State (EraCertState (..), UTxO (..))
import Data.Foldable (toList)
import Lens.Micro ((^.))
import Prettyprinter (Doc, indent, viaShow, vsep)
import Test.Cardano.Ledger.Generic.PrettyCore
import Test.Cardano.Ledger.Generic.Proof
import Test.Cardano.Ledger.Shelley.Examples.Consensus (
ShelleyLedgerExamples (..),
ShelleyResultExamples (..),
)
import Test.Cardano.Ledger.TerseTools
instance Terse (KeyHash 'Genesis) where
terse :: KeyHash 'Genesis -> String
terse KeyHash 'Genesis
x = PDoc -> String
forall a. Show a => a -> String
show (KeyHash 'Genesis -> PDoc
forall (discriminator :: KeyRole). KeyHash discriminator -> PDoc
pcKeyHash KeyHash 'Genesis
x)
instance Terse (PParamsUpdate ShelleyEra) where
terse :: PParamsUpdate ShelleyEra -> String
terse = PParamsUpdate ShelleyEra -> String
forall a. Show a => a -> String
show
instance Terse (PParamsUpdate AllegraEra) where
terse :: PParamsUpdate AllegraEra -> String
terse = PParamsUpdate AllegraEra -> String
forall a. Show a => a -> String
show
instance Terse (PParamsUpdate MaryEra) where
terse :: PParamsUpdate MaryEra -> String
terse = PParamsUpdate MaryEra -> String
forall a. Show a => a -> String
show
instance Terse (PParamsUpdate AlonzoEra) where
terse :: PParamsUpdate AlonzoEra -> String
terse = PParamsUpdate AlonzoEra -> String
forall a. Show a => a -> String
show
instance Terse (PParamsUpdate BabbageEra) where
terse :: PParamsUpdate BabbageEra -> String
terse = PParamsUpdate BabbageEra -> String
forall a. Show a => a -> String
show
instance Terse (PParamsUpdate ConwayEra) where
terse :: PParamsUpdate ConwayEra -> String
terse = PParamsUpdate ConwayEra -> String
forall a. Show a => a -> String
show
extendLabel :: String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel :: forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
_ [] = []
extendLabel String
s ((String
n, Maybe x
x) : [(String, Maybe x)]
xs) = (String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
n, Maybe x
x) (String, Maybe x) -> [(String, Maybe x)] -> [(String, Maybe x)]
forall a. a -> [a] -> [a]
: String -> [(String, Maybe x)] -> [(String, Maybe x)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
s [(String, Maybe x)]
xs
notEq :: Doc a -> Doc a -> Doc a
notEq :: forall a. Doc a -> Doc a -> Doc a
notEq Doc a
x Doc a
y = [Doc a] -> Doc a
forall ann. [Doc ann] -> Doc ann
vsep [Doc a
x, Int -> Doc a -> Doc a
forall ann. Int -> Doc ann -> Doc ann
indent Int
3 (Text -> Doc a
forall ann. Text -> Doc ann
text Text
"=/="), Doc a
y]
eqByShow :: (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow :: forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow t
x t
y = if t
x t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (PDoc -> PDoc -> PDoc
forall a. Doc a -> Doc a -> Doc a
notEq (String -> PDoc
forall a. String -> Doc a
ppString (t -> String
forall a. Show a => a -> String
show t
x)) (String -> PDoc
forall a. String -> Doc a
ppString (t -> String
forall a. Show a => a -> String
show t
y)))
eqVia :: Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia :: forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia t -> PDoc
pcf t
x t
y = if t
x t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (PDoc -> PDoc -> PDoc
forall a. Doc a -> Doc a -> Doc a
notEq (t -> PDoc
pcf t
x) (t -> PDoc
pcf t
y))
class Same era t where
same :: Proof era -> t -> t -> [(String, Maybe PDoc)]
instance Same era (PState era) where
same :: Proof era -> PState era -> PState era -> [(String, Maybe PDoc)]
same Proof era
_proof (PState Map (KeyHash 'StakePool) PoolParams
pp1 Map (KeyHash 'StakePool) PoolParams
fpp1 Map (KeyHash 'StakePool) EpochNo
ret1 Map (KeyHash 'StakePool) Coin
d1) (PState Map (KeyHash 'StakePool) PoolParams
pp2 Map (KeyHash 'StakePool) PoolParams
fpp2 Map (KeyHash 'StakePool) EpochNo
ret2 Map (KeyHash 'StakePool) Coin
d2) =
[ (String
"PoolParams", Map (KeyHash 'StakePool) PoolParams
-> Map (KeyHash 'StakePool) PoolParams -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (KeyHash 'StakePool) PoolParams
pp1 Map (KeyHash 'StakePool) PoolParams
pp2)
, (String
"FuturePoolParams", Map (KeyHash 'StakePool) PoolParams
-> Map (KeyHash 'StakePool) PoolParams -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (KeyHash 'StakePool) PoolParams
fpp1 Map (KeyHash 'StakePool) PoolParams
fpp2)
, (String
"Retiring", Map (KeyHash 'StakePool) EpochNo
-> Map (KeyHash 'StakePool) EpochNo -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (KeyHash 'StakePool) EpochNo
ret1 Map (KeyHash 'StakePool) EpochNo
ret2)
, (String
"Deposits", Map (KeyHash 'StakePool) Coin
-> Map (KeyHash 'StakePool) Coin -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (KeyHash 'StakePool) Coin
d1 Map (KeyHash 'StakePool) Coin
d2)
]
instance Same era (DState era) where
same :: Proof era -> DState era -> DState era -> [(String, Maybe PDoc)]
same Proof era
_proof (DState UMap
u1 Map FutureGenDeleg GenDelegPair
fgd1 GenDelegs
gd1 InstantaneousRewards
ir1) (DState UMap
u2 Map FutureGenDeleg GenDelegPair
fgd2 GenDelegs
gd2 InstantaneousRewards
ir2) =
[ (String
"Unified", UMap -> UMap -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UMap
u1 UMap
u2)
, (String
"FutureGenDelegs", Map FutureGenDeleg GenDelegPair
-> Map FutureGenDeleg GenDelegPair -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map FutureGenDeleg GenDelegPair
fgd1 Map FutureGenDeleg GenDelegPair
fgd2)
, (String
"GenDelegs", GenDelegs -> GenDelegs -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow GenDelegs
gd1 GenDelegs
gd2)
, (String
"InstantaneousRewards", InstantaneousRewards -> InstantaneousRewards -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow InstantaneousRewards
ir1 InstantaneousRewards
ir2)
]
instance Same era (VState era) where
same :: Proof era -> VState era -> VState era -> [(String, Maybe PDoc)]
same Proof era
_proof (VState Map (Credential 'DRepRole) DRepState
dr1 CommitteeState era
cchk1 EpochNo
numDE1) (VState Map (Credential 'DRepRole) DRepState
dr2 CommitteeState era
cchk2 EpochNo
numDE2) =
[ (String
"DReps", Map (Credential 'DRepRole) DRepState
-> Map (Credential 'DRepRole) DRepState -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (Credential 'DRepRole) DRepState
dr1 Map (Credential 'DRepRole) DRepState
dr2)
, (String
"CC Hot Keys", CommitteeState era -> CommitteeState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CommitteeState era
cchk1 CommitteeState era
cchk2)
, (String
"Num Dormant Epochs", EpochNo -> EpochNo -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow EpochNo
numDE1 EpochNo
numDE2)
]
sameUTxO :: Proof era -> UTxO era -> UTxO era -> Maybe PDoc
sameUTxO :: forall era. Proof era -> UTxO era -> UTxO era -> Maybe PDoc
sameUTxO Proof era
Shelley UTxO era
x UTxO era
y = UTxO era -> UTxO era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UTxO era
x UTxO era
y
sameUTxO Proof era
Allegra UTxO era
x UTxO era
y = UTxO era -> UTxO era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UTxO era
x UTxO era
y
sameUTxO Proof era
Mary UTxO era
x UTxO era
y = UTxO era -> UTxO era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UTxO era
x UTxO era
y
sameUTxO Proof era
Alonzo UTxO era
x UTxO era
y = UTxO era -> UTxO era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UTxO era
x UTxO era
y
sameUTxO Proof era
Babbage UTxO era
x UTxO era
y = UTxO era -> UTxO era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UTxO era
x UTxO era
y
sameUTxO Proof era
Conway UTxO era
x UTxO era
y = UTxO era -> UTxO era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UTxO era
x UTxO era
y
{-# NOINLINE sameUTxO #-}
samePPUP :: Proof era -> ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
samePPUP :: forall era.
Proof era
-> ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
samePPUP Proof era
Shelley ShelleyGovState era
x ShelleyGovState era
y = ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ShelleyGovState era
x ShelleyGovState era
y
samePPUP Proof era
Allegra ShelleyGovState era
x ShelleyGovState era
y = ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ShelleyGovState era
x ShelleyGovState era
y
samePPUP Proof era
Mary ShelleyGovState era
x ShelleyGovState era
y = ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ShelleyGovState era
x ShelleyGovState era
y
samePPUP Proof era
Alonzo ShelleyGovState era
x ShelleyGovState era
y = ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ShelleyGovState era
x ShelleyGovState era
y
samePPUP Proof era
Babbage ShelleyGovState era
x ShelleyGovState era
y = ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ShelleyGovState era
x ShelleyGovState era
y
samePPUP Proof era
Conway ShelleyGovState era
x ShelleyGovState era
y = ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ShelleyGovState era
x ShelleyGovState era
y
{-# NOINLINE samePPUP #-}
instance Reflect era => Same era (UTxOState era) where
same :: Proof era
-> UTxOState era -> UTxOState era -> [(String, Maybe PDoc)]
same Proof era
proof UTxOState era
u1 UTxOState era
u2 =
[ (String
"UTxO", Proof era -> UTxO era -> UTxO era -> Maybe PDoc
forall era. Proof era -> UTxO era -> UTxO era -> Maybe PDoc
sameUTxO Proof era
proof (UTxOState era -> UTxO era
forall era. UTxOState era -> UTxO era
utxosUtxo UTxOState era
u1) (UTxOState era -> UTxO era
forall era. UTxOState era -> UTxO era
utxosUtxo UTxOState era
u2))
, (String
"Deposited", Coin -> Coin -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (UTxOState era -> Coin
forall era. UTxOState era -> Coin
utxosDeposited UTxOState era
u1) (UTxOState era -> Coin
forall era. UTxOState era -> Coin
utxosDeposited UTxOState era
u2))
, (String
"Fees", Coin -> Coin -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (UTxOState era -> Coin
forall era. UTxOState era -> Coin
utxosFees UTxOState era
u1) (UTxOState era -> Coin
forall era. UTxOState era -> Coin
utxosFees UTxOState era
u2))
]
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [(String, Maybe PDoc)]
ppu
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [(String
"StakeDistr", InstantStake era -> InstantStake era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (UTxOState era -> InstantStake era
forall era. UTxOState era -> InstantStake era
utxosInstantStake UTxOState era
u1) (UTxOState era -> InstantStake era
forall era. UTxOState era -> InstantStake era
utxosInstantStake UTxOState era
u2))]
where
ppuPretty :: GovState era ~ ShelleyGovState era => [(String, Maybe PDoc)]
ppuPretty :: (GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty = [(String
"ShelleyGovState", Proof era
-> ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
forall era.
Proof era
-> ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
samePPUP Proof era
proof (UTxOState era -> GovState era
forall era. UTxOState era -> GovState era
utxosGovState UTxOState era
u1) (UTxOState era -> GovState era
forall era. UTxOState era -> GovState era
utxosGovState UTxOState era
u2))]
ppu :: [(String, Maybe PDoc)]
ppu = case forall era. Reflect era => Proof era
reify @era of
Proof era
Shelley -> [(String, Maybe PDoc)]
(GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
Proof era
Mary -> [(String, Maybe PDoc)]
(GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
Proof era
Allegra -> [(String, Maybe PDoc)]
(GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
Proof era
Alonzo -> [(String, Maybe PDoc)]
(GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
Proof era
Babbage -> [(String, Maybe PDoc)]
(GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
Proof era
Conway -> []
instance Reflect era => Same era (LedgerState era) where
same :: Proof era
-> LedgerState era -> LedgerState era -> [(String, Maybe PDoc)]
same Proof era
proof LedgerState era
x1 LedgerState era
x2 =
String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"UTxOState " (Proof era
-> UTxOState era -> UTxOState era -> [(String, Maybe PDoc)]
forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (LedgerState era -> UTxOState era
forall era. LedgerState era -> UTxOState era
lsUTxOState LedgerState era
x1) (LedgerState era -> UTxOState era
forall era. LedgerState era -> UTxOState era
lsUTxOState LedgerState era
x2))
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [(String, Maybe PDoc)]
certState
where
prettyShelley :: [(String, Maybe PDoc)]
prettyShelley :: [(String, Maybe PDoc)]
prettyShelley = [(String
"ShelleyCertState", CertState era -> CertState era -> Maybe PDoc
forall era.
Reflect era =>
CertState era -> CertState era -> Maybe PDoc
sameCertState (LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
lsCertState LedgerState era
x1) (LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
lsCertState LedgerState era
x2))]
prettyConway :: [(String, Maybe PDoc)]
prettyConway :: [(String, Maybe PDoc)]
prettyConway = [(String
"ConwayCertState", CertState era -> CertState era -> Maybe PDoc
forall era.
Reflect era =>
CertState era -> CertState era -> Maybe PDoc
sameCertState (LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
lsCertState LedgerState era
x1) (LedgerState era -> CertState era
forall era. LedgerState era -> CertState era
lsCertState LedgerState era
x2))]
certState :: [(String, Maybe PDoc)]
certState = case forall era. Reflect era => Proof era
reify @era of
Proof era
Shelley -> [(String, Maybe PDoc)]
prettyShelley
Proof era
Mary -> [(String, Maybe PDoc)]
prettyShelley
Proof era
Allegra -> [(String, Maybe PDoc)]
prettyShelley
Proof era
Alonzo -> [(String, Maybe PDoc)]
prettyShelley
Proof era
Babbage -> [(String, Maybe PDoc)]
prettyShelley
Proof era
Conway -> [(String, Maybe PDoc)]
prettyConway
instance Reflect era => Same era (EpochState era) where
same :: Proof era
-> EpochState era -> EpochState era -> [(String, Maybe PDoc)]
same Proof era
proof EpochState era
e1 EpochState era
e2 =
[ (String
"ChainAccountState", ChainAccountState -> ChainAccountState -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (EpochState era -> ChainAccountState
forall era. EpochState era -> ChainAccountState
esChainAccountState EpochState era
e1) (EpochState era -> ChainAccountState
forall era. EpochState era -> ChainAccountState
esChainAccountState EpochState era
e2))
, (String
"SnapShots", SnapShots -> SnapShots -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (EpochState era -> SnapShots
forall era. EpochState era -> SnapShots
esSnapshots EpochState era
e1) (EpochState era -> SnapShots
forall era. EpochState era -> SnapShots
esSnapshots EpochState era
e2))
, (String
"PrevPP", Proof era -> PParams era -> PParams era -> Maybe PDoc
forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
proof (EpochState era
e1 EpochState era
-> Getting (PParams era) (EpochState era) (PParams era)
-> PParams era
forall s a. s -> Getting a s a -> a
^. Getting (PParams era) (EpochState era) (PParams era)
forall era. EraGov era => Lens' (EpochState era) (PParams era)
Lens' (EpochState era) (PParams era)
prevPParamsEpochStateL) (EpochState era
e2 EpochState era
-> Getting (PParams era) (EpochState era) (PParams era)
-> PParams era
forall s a. s -> Getting a s a -> a
^. Getting (PParams era) (EpochState era) (PParams era)
forall era. EraGov era => Lens' (EpochState era) (PParams era)
Lens' (EpochState era) (PParams era)
prevPParamsEpochStateL))
, (String
"CurPP", Proof era -> PParams era -> PParams era -> Maybe PDoc
forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
proof (EpochState era
e1 EpochState era
-> Getting (PParams era) (EpochState era) (PParams era)
-> PParams era
forall s a. s -> Getting a s a -> a
^. Getting (PParams era) (EpochState era) (PParams era)
forall era. EraGov era => Lens' (EpochState era) (PParams era)
Lens' (EpochState era) (PParams era)
curPParamsEpochStateL) (EpochState era
e2 EpochState era
-> Getting (PParams era) (EpochState era) (PParams era)
-> PParams era
forall s a. s -> Getting a s a -> a
^. Getting (PParams era) (EpochState era) (PParams era)
forall era. EraGov era => Lens' (EpochState era) (PParams era)
Lens' (EpochState era) (PParams era)
curPParamsEpochStateL))
, (String
"NonMyopic", NonMyopic -> NonMyopic -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (EpochState era -> NonMyopic
forall era. EpochState era -> NonMyopic
esNonMyopic EpochState era
e1) (EpochState era -> NonMyopic
forall era. EpochState era -> NonMyopic
esNonMyopic EpochState era
e2))
]
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"LedgerState " (Proof era
-> LedgerState era -> LedgerState era -> [(String, Maybe PDoc)]
forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (EpochState era -> LedgerState era
forall era. EpochState era -> LedgerState era
esLState EpochState era
e1) (EpochState era -> LedgerState era
forall era. EpochState era -> LedgerState era
esLState EpochState era
e2))
sameStashedAVVMAddresses ::
Proof era -> StashedAVVMAddresses era -> StashedAVVMAddresses era -> Maybe PDoc
sameStashedAVVMAddresses :: forall era.
Proof era
-> StashedAVVMAddresses era
-> StashedAVVMAddresses era
-> Maybe PDoc
sameStashedAVVMAddresses Proof era
proof StashedAVVMAddresses era
x StashedAVVMAddresses era
y =
case Proof era
proof of
Proof era
Shelley -> if UTxO ShelleyEra
StashedAVVMAddresses era
x UTxO ShelleyEra -> UTxO ShelleyEra -> Bool
forall a. Eq a => a -> a -> Bool
== UTxO ShelleyEra
StashedAVVMAddresses era
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (UTxO ShelleyEra -> PDoc
forall a ann. Show a => a -> Doc ann
viaShow UTxO ShelleyEra
StashedAVVMAddresses era
x)
Proof era
Allegra -> if ()
StashedAVVMAddresses era
x () -> () -> Bool
forall a. Eq a => a -> a -> Bool
== ()
StashedAVVMAddresses era
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (() -> PDoc
forall a ann. Show a => a -> Doc ann
viaShow ()
StashedAVVMAddresses era
x)
Proof era
Mary -> if ()
StashedAVVMAddresses era
x () -> () -> Bool
forall a. Eq a => a -> a -> Bool
== ()
StashedAVVMAddresses era
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (() -> PDoc
forall a ann. Show a => a -> Doc ann
viaShow ()
StashedAVVMAddresses era
x)
Proof era
Alonzo -> if ()
StashedAVVMAddresses era
x () -> () -> Bool
forall a. Eq a => a -> a -> Bool
== ()
StashedAVVMAddresses era
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (() -> PDoc
forall a ann. Show a => a -> Doc ann
viaShow ()
StashedAVVMAddresses era
x)
Proof era
Babbage -> if ()
StashedAVVMAddresses era
x () -> () -> Bool
forall a. Eq a => a -> a -> Bool
== ()
StashedAVVMAddresses era
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (() -> PDoc
forall a ann. Show a => a -> Doc ann
viaShow ()
StashedAVVMAddresses era
x)
Proof era
Conway -> if ()
StashedAVVMAddresses era
x () -> () -> Bool
forall a. Eq a => a -> a -> Bool
== ()
StashedAVVMAddresses era
y then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (() -> PDoc
forall a ann. Show a => a -> Doc ann
viaShow ()
StashedAVVMAddresses era
x)
instance
Reflect era =>
Same era (NewEpochState era)
where
same :: Proof era
-> NewEpochState era -> NewEpochState era -> [(String, Maybe PDoc)]
same Proof era
proof NewEpochState era
n1 NewEpochState era
n2 =
[ (String
"nesEL", EpochNo -> EpochNo -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (NewEpochState era -> EpochNo
forall era. NewEpochState era -> EpochNo
nesEL NewEpochState era
n1) (NewEpochState era -> EpochNo
forall era. NewEpochState era -> EpochNo
nesEL NewEpochState era
n2))
, (String
"nesBprev", BlocksMade -> BlocksMade -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (NewEpochState era -> BlocksMade
forall era. NewEpochState era -> BlocksMade
nesBprev NewEpochState era
n1) (NewEpochState era -> BlocksMade
forall era. NewEpochState era -> BlocksMade
nesBprev NewEpochState era
n2))
, (String
"nesBcur", BlocksMade -> BlocksMade -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (NewEpochState era -> BlocksMade
forall era. NewEpochState era -> BlocksMade
nesBcur NewEpochState era
n1) (NewEpochState era -> BlocksMade
forall era. NewEpochState era -> BlocksMade
nesBcur NewEpochState era
n2))
, (String
"nesRU", StrictMaybe PulsingRewUpdate
-> StrictMaybe PulsingRewUpdate -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (NewEpochState era -> StrictMaybe PulsingRewUpdate
forall era. NewEpochState era -> StrictMaybe PulsingRewUpdate
nesRu NewEpochState era
n1) (NewEpochState era -> StrictMaybe PulsingRewUpdate
forall era. NewEpochState era -> StrictMaybe PulsingRewUpdate
nesRu NewEpochState era
n2))
, (String
"nesPd", PoolDistr -> PoolDistr -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (NewEpochState era -> PoolDistr
forall era. NewEpochState era -> PoolDistr
nesPd NewEpochState era
n1) (NewEpochState era -> PoolDistr
forall era. NewEpochState era -> PoolDistr
nesPd NewEpochState era
n2))
, (String
"nesStashAVVM", Proof era
-> StashedAVVMAddresses era
-> StashedAVVMAddresses era
-> Maybe PDoc
forall era.
Proof era
-> StashedAVVMAddresses era
-> StashedAVVMAddresses era
-> Maybe PDoc
sameStashedAVVMAddresses Proof era
proof (NewEpochState era -> StashedAVVMAddresses era
forall era. NewEpochState era -> StashedAVVMAddresses era
stashedAVVMAddresses NewEpochState era
n1) (NewEpochState era -> StashedAVVMAddresses era
forall era. NewEpochState era -> StashedAVVMAddresses era
stashedAVVMAddresses NewEpochState era
n2))
]
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"EpochState " (Proof era
-> EpochState era -> EpochState era -> [(String, Maybe PDoc)]
forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
nesEs NewEpochState era
n1) (NewEpochState era -> EpochState era
forall era. NewEpochState era -> EpochState era
nesEs NewEpochState era
n2))
data SomeDepend where
SomeD :: String -> (x -> x -> Maybe PDoc) -> x -> x -> SomeDepend
SomeM :: String -> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
sameWithDependency :: [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency :: [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency [] = []
sameWithDependency (SomeD String
labx x -> x -> Maybe PDoc
actx x
x1 x
x2 : [SomeDepend]
more) =
case x -> x -> Maybe PDoc
actx x
x1 x
x2 of
Maybe PDoc
Nothing -> [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency [SomeDepend]
more
Maybe PDoc
ansx -> (String
labx, Maybe PDoc
ansx) (String, Maybe PDoc)
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. a -> [a] -> [a]
: [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency [SomeDepend]
more
sameWithDependency (SomeM String
labx x -> x -> [(String, Maybe PDoc)]
actx x
x1 x
x2 : [SomeDepend]
more) =
case x -> x -> [(String, Maybe PDoc)]
actx x
x1 x
x2 of
[] -> [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency [SomeDepend]
more
[(String, Maybe PDoc)]
ansx -> String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel (String
labx String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" ") [(String, Maybe PDoc)]
ansx [(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency [SomeDepend]
more
instance
Reflect era =>
Same era (ShelleyLedgerExamples era)
where
same :: Proof era
-> ShelleyLedgerExamples era
-> ShelleyLedgerExamples era
-> [(String, Maybe PDoc)]
same Proof era
proof ShelleyLedgerExamples era
x1 ShelleyLedgerExamples era
x2 = case (ShelleyLedgerExamples era -> Block (BHeader StandardCrypto) era
forall era.
ShelleyLedgerExamples era -> Block (BHeader StandardCrypto) era
sleBlock ShelleyLedgerExamples era
x1, ShelleyLedgerExamples era -> Block (BHeader StandardCrypto) era
forall era.
ShelleyLedgerExamples era -> Block (BHeader StandardCrypto) era
sleBlock ShelleyLedgerExamples era
x2) of
(Block BHeader StandardCrypto
h1 TxSeq era
a1, Block BHeader StandardCrypto
h2 TxSeq era
a2) ->
[SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency
[ String
-> (Tx era -> Tx era -> [(String, Maybe PDoc)])
-> Tx era
-> Tx era
-> SomeDepend
forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM String
"Tx" (Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
forall era. Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx Proof era
proof) (ShelleyLedgerExamples era -> Tx era
forall era. ShelleyLedgerExamples era -> Tx era
sleTx ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era -> Tx era
forall era. ShelleyLedgerExamples era -> Tx era
sleTx ShelleyLedgerExamples era
x2)
, String
-> (TxSeq era -> TxSeq era -> [(String, Maybe PDoc)])
-> TxSeq era
-> TxSeq era
-> SomeDepend
forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM String
"TxSeq" (Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
forall era.
Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
sameTxSeq Proof era
proof) TxSeq era
a1 TxSeq era
a2
]
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [ (String
"BlockHeader", if BHeader StandardCrypto
h1 BHeader StandardCrypto -> BHeader StandardCrypto -> Bool
forall a. Eq a => a -> a -> Bool
== BHeader StandardCrypto
h2 then Maybe PDoc
forall a. Maybe a
Nothing else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (PDoc
"UnequalBlockHeader"))
,
( String
"HashHeader"
, if (ShelleyLedgerExamples era -> HashHeader
forall era. ShelleyLedgerExamples era -> HashHeader
sleHashHeader ShelleyLedgerExamples era
x1) HashHeader -> HashHeader -> Bool
forall a. Eq a => a -> a -> Bool
== (ShelleyLedgerExamples era -> HashHeader
forall era. ShelleyLedgerExamples era -> HashHeader
sleHashHeader ShelleyLedgerExamples era
x2)
then Maybe PDoc
forall a. Maybe a
Nothing
else PDoc -> Maybe PDoc
forall a. a -> Maybe a
Just (PDoc
"UnequalHashHeader")
)
, (String
"ApplyTxError", Proof era -> ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall era.
Proof era -> ApplyTxError era -> ApplyTxError era -> Maybe PDoc
sameLedgerFail Proof era
proof (ShelleyLedgerExamples era -> ApplyTxError era
forall era. ShelleyLedgerExamples era -> ApplyTxError era
sleApplyTxError ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era -> ApplyTxError era
forall era. ShelleyLedgerExamples era -> ApplyTxError era
sleApplyTxError ShelleyLedgerExamples era
x2))
, (String
"RewardsCredentials", Set (Either Coin (Credential 'Staking))
-> Set (Either Coin (Credential 'Staking)) -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (ShelleyLedgerExamples era
-> Set (Either Coin (Credential 'Staking))
forall era.
ShelleyLedgerExamples era
-> Set (Either Coin (Credential 'Staking))
sleRewardsCredentials ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era
-> Set (Either Coin (Credential 'Staking))
forall era.
ShelleyLedgerExamples era
-> Set (Either Coin (Credential 'Staking))
sleRewardsCredentials ShelleyLedgerExamples era
x2))
]
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"Result " (Proof era
-> ShelleyResultExamples era
-> ShelleyResultExamples era
-> [(String, Maybe PDoc)]
forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (ShelleyLedgerExamples era -> ShelleyResultExamples era
forall era. ShelleyLedgerExamples era -> ShelleyResultExamples era
sleResultExamples ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era -> ShelleyResultExamples era
forall era. ShelleyLedgerExamples era -> ShelleyResultExamples era
sleResultExamples ShelleyLedgerExamples era
x2))
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"NewEpochState " (Proof era
-> NewEpochState era -> NewEpochState era -> [(String, Maybe PDoc)]
forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (ShelleyLedgerExamples era -> NewEpochState era
forall era. ShelleyLedgerExamples era -> NewEpochState era
sleNewEpochState ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era -> NewEpochState era
forall era. ShelleyLedgerExamples era -> NewEpochState era
sleNewEpochState ShelleyLedgerExamples era
x2))
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [ (String
"ChainDepState", ChainDepState -> ChainDepState -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (ShelleyLedgerExamples era -> ChainDepState
forall era. ShelleyLedgerExamples era -> ChainDepState
sleChainDepState ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era -> ChainDepState
forall era. ShelleyLedgerExamples era -> ChainDepState
sleChainDepState ShelleyLedgerExamples era
x2))
, (String
"TranslationContext", Proof era
-> TranslationContext era -> TranslationContext era -> Maybe PDoc
forall era.
Proof era
-> TranslationContext era -> TranslationContext era -> Maybe PDoc
sameTransCtx Proof era
proof (ShelleyLedgerExamples era -> TranslationContext era
forall era. ShelleyLedgerExamples era -> TranslationContext era
sleTranslationContext ShelleyLedgerExamples era
x1) (ShelleyLedgerExamples era -> TranslationContext era
forall era. ShelleyLedgerExamples era -> TranslationContext era
sleTranslationContext ShelleyLedgerExamples era
x2))
]
instance Era era => Same era (ShelleyResultExamples era) where
same :: Proof era
-> ShelleyResultExamples era
-> ShelleyResultExamples era
-> [(String, Maybe PDoc)]
same Proof era
proof ShelleyResultExamples era
r1 ShelleyResultExamples era
r2 =
[ (String
"PParams", Proof era -> PParams era -> PParams era -> Maybe PDoc
forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
proof (ShelleyResultExamples era -> PParams era
forall era. ShelleyResultExamples era -> PParams era
srePParams ShelleyResultExamples era
r1) (ShelleyResultExamples era -> PParams era
forall era. ShelleyResultExamples era -> PParams era
srePParams ShelleyResultExamples era
r2))
,
( String
"ProposedPPUpdates"
, case Proof era
proof of
Proof era
Shelley -> ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe PDoc
forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
Proof era
Allegra -> ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe PDoc
forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
Proof era
Mary -> ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe PDoc
forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
Proof era
Alonzo -> ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe PDoc
forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
Proof era
Babbage -> ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe PDoc
forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
Proof era
Conway -> ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe PDoc
forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ProposedPPUpdates era
forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
)
, (String
"poolDistr", PoolDistr -> PoolDistr -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (ShelleyResultExamples era -> PoolDistr
forall era. ShelleyResultExamples era -> PoolDistr
srePoolDistr ShelleyResultExamples era
r1) (ShelleyResultExamples era -> PoolDistr
forall era. ShelleyResultExamples era -> PoolDistr
srePoolDistr ShelleyResultExamples era
r2))
, (String
"NonMyopicRewards", Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
-> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (ShelleyResultExamples era
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
forall era.
ShelleyResultExamples era
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
sreNonMyopicRewards ShelleyResultExamples era
r1) (ShelleyResultExamples era
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
forall era.
ShelleyResultExamples era
-> Map
(Either Coin (Credential 'Staking)) (Map (KeyHash 'StakePool) Coin)
sreNonMyopicRewards ShelleyResultExamples era
r2))
, (String
"ShelleyGenesis", ShelleyGenesis -> ShelleyGenesis -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (ShelleyResultExamples era -> ShelleyGenesis
forall era. ShelleyResultExamples era -> ShelleyGenesis
sreShelleyGenesis ShelleyResultExamples era
r1) (ShelleyResultExamples era -> ShelleyGenesis
forall era. ShelleyResultExamples era -> ShelleyGenesis
sreShelleyGenesis ShelleyResultExamples era
r2))
]
where
getmap :: ProposedPPUpdates era -> Map (KeyHash 'Genesis) (PParamsUpdate era)
getmap (ProposedPPUpdates Map (KeyHash 'Genesis) (PParamsUpdate era)
x) = Map (KeyHash 'Genesis) (PParamsUpdate era)
x
sameProposedPPUpdates :: ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates ProposedPPUpdates era
x ProposedPPUpdates era
y = [Case (KeyHash 'Genesis) (PParamsUpdate era)] -> Maybe (Doc a)
forall {a} {a}. Show a => [a] -> Maybe (Doc a)
ppDiff ([Case (KeyHash 'Genesis) (PParamsUpdate era)] -> Maybe (Doc a))
-> [Case (KeyHash 'Genesis) (PParamsUpdate era)] -> Maybe (Doc a)
forall a b. (a -> b) -> a -> b
$ Map (KeyHash 'Genesis) (PParamsUpdate era)
-> Map (KeyHash 'Genesis) (PParamsUpdate era)
-> [Case (KeyHash 'Genesis) (PParamsUpdate era)]
forall a b. (Ord a, Eq b) => Map a b -> Map a b -> [Case a b]
mapdiffs (ProposedPPUpdates era -> Map (KeyHash 'Genesis) (PParamsUpdate era)
forall {era}.
ProposedPPUpdates era -> Map (KeyHash 'Genesis) (PParamsUpdate era)
getmap ProposedPPUpdates era
x) (ProposedPPUpdates era -> Map (KeyHash 'Genesis) (PParamsUpdate era)
forall {era}.
ProposedPPUpdates era -> Map (KeyHash 'Genesis) (PParamsUpdate era)
getmap ProposedPPUpdates era
y)
where
ppDiff :: [a] -> Maybe (Doc a)
ppDiff [] = Maybe (Doc a)
forall a. Maybe a
Nothing
ppDiff [a]
xs = Doc a -> Maybe (Doc a)
forall a. a -> Maybe a
Just (String -> Doc a
forall a. String -> Doc a
ppString ([a] -> String
forall a. Show a => a -> String
show [a]
xs))
samePParams :: Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams :: forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
Shelley PParams era
x PParams era
y = PParams era -> PParams era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParams era
x PParams era
y
samePParams Proof era
Allegra PParams era
x PParams era
y = PParams era -> PParams era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParams era
x PParams era
y
samePParams Proof era
Mary PParams era
x PParams era
y = PParams era -> PParams era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParams era
x PParams era
y
samePParams Proof era
Alonzo PParams era
x PParams era
y = PParams era -> PParams era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParams era
x PParams era
y
samePParams Proof era
Babbage PParams era
x PParams era
y = PParams era -> PParams era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParams era
x PParams era
y
samePParams Proof era
Conway PParams era
x PParams era
y = PParams era -> PParams era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParams era
x PParams era
y
{-# NOINLINE samePParams #-}
samePParamsUpdate :: Proof era -> PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
samePParamsUpdate :: forall era.
Proof era -> PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
samePParamsUpdate Proof era
Shelley PParamsUpdate era
x PParamsUpdate era
y = PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParamsUpdate era
x PParamsUpdate era
y
samePParamsUpdate Proof era
Allegra PParamsUpdate era
x PParamsUpdate era
y = PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParamsUpdate era
x PParamsUpdate era
y
samePParamsUpdate Proof era
Mary PParamsUpdate era
x PParamsUpdate era
y = PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParamsUpdate era
x PParamsUpdate era
y
samePParamsUpdate Proof era
Alonzo PParamsUpdate era
x PParamsUpdate era
y = PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParamsUpdate era
x PParamsUpdate era
y
samePParamsUpdate Proof era
Babbage PParamsUpdate era
x PParamsUpdate era
y = PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParamsUpdate era
x PParamsUpdate era
y
samePParamsUpdate Proof era
Conway PParamsUpdate era
x PParamsUpdate era
y = PParamsUpdate era -> PParamsUpdate era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow PParamsUpdate era
x PParamsUpdate era
y
{-# NOINLINE samePParamsUpdate #-}
sameTxOut :: Proof era -> TxOut era -> TxOut era -> Maybe PDoc
sameTxOut :: forall era. Proof era -> TxOut era -> TxOut era -> Maybe PDoc
sameTxOut Proof era
Shelley TxOut era
x TxOut era
y = ShelleyTxOut ShelleyEra -> ShelleyTxOut ShelleyEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
ShelleyTxOut ShelleyEra
x TxOut era
ShelleyTxOut ShelleyEra
y
sameTxOut Proof era
Allegra TxOut era
x TxOut era
y = ShelleyTxOut AllegraEra -> ShelleyTxOut AllegraEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
ShelleyTxOut AllegraEra
x TxOut era
ShelleyTxOut AllegraEra
y
sameTxOut Proof era
Mary TxOut era
x TxOut era
y = ShelleyTxOut MaryEra -> ShelleyTxOut MaryEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
ShelleyTxOut MaryEra
x TxOut era
ShelleyTxOut MaryEra
y
sameTxOut Proof era
Alonzo TxOut era
x TxOut era
y = AlonzoTxOut AlonzoEra -> AlonzoTxOut AlonzoEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
AlonzoTxOut AlonzoEra
x TxOut era
AlonzoTxOut AlonzoEra
y
sameTxOut Proof era
Babbage TxOut era
x TxOut era
y = BabbageTxOut BabbageEra -> BabbageTxOut BabbageEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
BabbageTxOut BabbageEra
x TxOut era
BabbageTxOut BabbageEra
y
sameTxOut Proof era
Conway TxOut era
x TxOut era
y = BabbageTxOut ConwayEra -> BabbageTxOut ConwayEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
BabbageTxOut ConwayEra
x TxOut era
BabbageTxOut ConwayEra
y
{-# NOINLINE sameTxOut #-}
sameLedgerFail ::
Proof era ->
ApplyTxError era ->
ApplyTxError era ->
Maybe PDoc
sameLedgerFail :: forall era.
Proof era -> ApplyTxError era -> ApplyTxError era -> Maybe PDoc
sameLedgerFail Proof era
Shelley ApplyTxError era
x ApplyTxError era
y = ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ApplyTxError era
x ApplyTxError era
y
sameLedgerFail Proof era
Allegra ApplyTxError era
x ApplyTxError era
y = ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ApplyTxError era
x ApplyTxError era
y
sameLedgerFail Proof era
Mary ApplyTxError era
x ApplyTxError era
y = ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ApplyTxError era
x ApplyTxError era
y
sameLedgerFail Proof era
Alonzo ApplyTxError era
x ApplyTxError era
y = ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ApplyTxError era
x ApplyTxError era
y
sameLedgerFail Proof era
Babbage ApplyTxError era
x ApplyTxError era
y = ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ApplyTxError era
x ApplyTxError era
y
sameLedgerFail Proof era
Conway ApplyTxError era
x ApplyTxError era
y = ApplyTxError era -> ApplyTxError era -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow ApplyTxError era
x ApplyTxError era
y
{-# NOINLINE sameLedgerFail #-}
sameTransCtx ::
Proof era ->
TranslationContext era ->
TranslationContext era ->
Maybe PDoc
sameTransCtx :: forall era.
Proof era
-> TranslationContext era -> TranslationContext era -> Maybe PDoc
sameTransCtx Proof era
Shelley TranslationContext era
x TranslationContext era
y = FromByronTranslationContext
-> FromByronTranslationContext -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
FromByronTranslationContext
x TranslationContext era
FromByronTranslationContext
y
sameTransCtx Proof era
Allegra TranslationContext era
x TranslationContext era
y = NoGenesis AllegraEra -> NoGenesis AllegraEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
NoGenesis AllegraEra
x TranslationContext era
NoGenesis AllegraEra
y
sameTransCtx Proof era
Mary TranslationContext era
x TranslationContext era
y = NoGenesis MaryEra -> NoGenesis MaryEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
NoGenesis MaryEra
x TranslationContext era
NoGenesis MaryEra
y
sameTransCtx Proof era
Alonzo TranslationContext era
x TranslationContext era
y = AlonzoGenesis -> AlonzoGenesis -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
AlonzoGenesis
x TranslationContext era
AlonzoGenesis
y
sameTransCtx Proof era
Babbage TranslationContext era
x TranslationContext era
y = NoGenesis BabbageEra -> NoGenesis BabbageEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
NoGenesis BabbageEra
x TranslationContext era
NoGenesis BabbageEra
y
sameTransCtx Proof era
Conway TranslationContext era
x TranslationContext era
y = ConwayGenesis -> ConwayGenesis -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
ConwayGenesis
x TranslationContext era
ConwayGenesis
y
{-# NOINLINE sameTransCtx #-}
sameCertState :: forall era. Reflect era => CertState era -> CertState era -> Maybe PDoc
sameCertState :: forall era.
Reflect era =>
CertState era -> CertState era -> Maybe PDoc
sameCertState CertState era
x CertState era
y = case forall era. Reflect era => Proof era
reify @era of
Proof era
Shelley -> ShelleyCertState ShelleyEra
-> ShelleyCertState ShelleyEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CertState era
ShelleyCertState ShelleyEra
x CertState era
ShelleyCertState ShelleyEra
y
Proof era
Allegra -> ShelleyCertState AllegraEra
-> ShelleyCertState AllegraEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CertState era
ShelleyCertState AllegraEra
x CertState era
ShelleyCertState AllegraEra
y
Proof era
Mary -> ShelleyCertState MaryEra -> ShelleyCertState MaryEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CertState era
ShelleyCertState MaryEra
x CertState era
ShelleyCertState MaryEra
y
Proof era
Alonzo -> ShelleyCertState AlonzoEra
-> ShelleyCertState AlonzoEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CertState era
ShelleyCertState AlonzoEra
x CertState era
ShelleyCertState AlonzoEra
y
Proof era
Babbage -> ShelleyCertState BabbageEra
-> ShelleyCertState BabbageEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CertState era
ShelleyCertState BabbageEra
x CertState era
ShelleyCertState BabbageEra
y
Proof era
Conway -> ConwayCertState ConwayEra
-> ConwayCertState ConwayEra -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CertState era
ConwayCertState ConwayEra
x CertState era
ConwayCertState ConwayEra
y
{-# NOINLINE sameCertState #-}
sameShelleyTxWits ::
forall era.
Reflect era =>
Proof era ->
ShelleyTxWits era ->
ShelleyTxWits era ->
[(String, Maybe PDoc)]
sameShelleyTxWits :: forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof (ShelleyTxWits Set (WitVKey 'Witness)
vk1 Map ScriptHash (Script era)
sh1 Set BootstrapWitness
boot1) (ShelleyTxWits Set (WitVKey 'Witness)
vk2 Map ScriptHash (Script era)
sh2 Set BootstrapWitness
boot2) =
[ (String
"VKeyWits", (Set (WitVKey 'Witness) -> PDoc)
-> Set (WitVKey 'Witness) -> Set (WitVKey 'Witness) -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((WitVKey 'Witness -> PDoc) -> Set (WitVKey 'Witness) -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet (Proof era -> WitVKey 'Witness -> PDoc
forall era (keyrole :: KeyRole).
Proof era -> WitVKey keyrole -> PDoc
pcWitVKey Proof era
proof)) Set (WitVKey 'Witness)
vk1 Set (WitVKey 'Witness)
vk2)
, (String
"ScriptWits", (Map ScriptHash (Script era) -> PDoc)
-> Map ScriptHash (Script era)
-> Map ScriptHash (Script era)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ScriptHash -> PDoc)
-> (Script era -> PDoc) -> Map ScriptHash (Script era) -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap ScriptHash -> PDoc
pcScriptHash (Proof era -> Script era -> PDoc
forall era. Reflect era => Proof era -> Script era -> PDoc
pcScript Proof era
proof)) Map ScriptHash (Script era)
sh1 Map ScriptHash (Script era)
sh2)
, (String
"BootWits", (Set BootstrapWitness -> PDoc)
-> Set BootstrapWitness -> Set BootstrapWitness -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\Set BootstrapWitness
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"BOOTWITS") Set BootstrapWitness
boot1 Set BootstrapWitness
boot2)
]
sameAlonzoTxWits ::
forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era ->
AlonzoTxWits era ->
AlonzoTxWits era ->
[(String, Maybe PDoc)]
sameAlonzoTxWits :: forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits
Proof era
proof
(AlonzoTxWits Set (WitVKey 'Witness)
vk1 Set BootstrapWitness
boot1 Map ScriptHash (Script era)
sh1 (TxDats Map DataHash (Data era)
d1) (Redeemers Map (PlutusPurpose AsIx era) (Data era, ExUnits)
r1))
(AlonzoTxWits Set (WitVKey 'Witness)
vk2 Set BootstrapWitness
boot2 Map ScriptHash (Script era)
sh2 (TxDats Map DataHash (Data era)
d2) (Redeemers Map (PlutusPurpose AsIx era) (Data era, ExUnits)
r2)) =
[ (String
"VKeyWits", (Set (WitVKey 'Witness) -> PDoc)
-> Set (WitVKey 'Witness) -> Set (WitVKey 'Witness) -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((WitVKey 'Witness -> PDoc) -> Set (WitVKey 'Witness) -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet (Proof era -> WitVKey 'Witness -> PDoc
forall era (keyrole :: KeyRole).
Proof era -> WitVKey keyrole -> PDoc
pcWitVKey Proof era
proof)) Set (WitVKey 'Witness)
vk1 Set (WitVKey 'Witness)
vk2)
, (String
"BootWits", (Set BootstrapWitness -> PDoc)
-> Set BootstrapWitness -> Set BootstrapWitness -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\Set BootstrapWitness
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"BOOTWITS") Set BootstrapWitness
boot1 Set BootstrapWitness
boot2)
, (String
"ScriptWits", (Map ScriptHash (Script era) -> PDoc)
-> Map ScriptHash (Script era)
-> Map ScriptHash (Script era)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ScriptHash -> PDoc)
-> (Script era -> PDoc) -> Map ScriptHash (Script era) -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap ScriptHash -> PDoc
pcScriptHash (Proof era -> Script era -> PDoc
forall era. Reflect era => Proof era -> Script era -> PDoc
pcScript Proof era
proof)) Map ScriptHash (Script era)
sh1 Map ScriptHash (Script era)
sh2)
, (String
"DataWits", (Map DataHash (Data era) -> PDoc)
-> Map DataHash (Data era) -> Map DataHash (Data era) -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((DataHash -> PDoc)
-> (Data era -> PDoc) -> Map DataHash (Data era) -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap DataHash -> PDoc
pcDataHash Data era -> PDoc
forall era. Era era => Data era -> PDoc
pcData) Map DataHash (Data era)
d1 Map DataHash (Data era)
d2)
, (String
"RedeemerWits", (Map (PlutusPurpose AsIx era) (Data era, ExUnits) -> PDoc)
-> Map (PlutusPurpose AsIx era) (Data era, ExUnits)
-> Map (PlutusPurpose AsIx era) (Data era, ExUnits)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((PlutusPurpose AsIx era -> PDoc)
-> ((Data era, ExUnits) -> PDoc)
-> Map (PlutusPurpose AsIx era) (Data era, ExUnits)
-> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap PlutusPurpose AsIx era -> PDoc
forall era. Reflect era => PlutusPurpose AsIx era -> PDoc
ppPlutusPurposeAsIx ((Data era -> PDoc)
-> (ExUnits -> PDoc) -> (Data era, ExUnits) -> PDoc
forall t1 t2. (t1 -> PDoc) -> (t2 -> PDoc) -> (t1, t2) -> PDoc
pcPair Data era -> PDoc
forall era. Era era => Data era -> PDoc
pcData ExUnits -> PDoc
pcExUnits)) Map (PlutusPurpose AsIx era) (Data era, ExUnits)
r1 Map (PlutusPurpose AsIx era) (Data era, ExUnits)
r2)
]
sameTxWits :: Proof era -> TxWits era -> TxWits era -> [(String, Maybe PDoc)]
sameTxWits :: forall era.
Proof era -> TxWits era -> TxWits era -> [(String, Maybe PDoc)]
sameTxWits proof :: Proof era
proof@Proof era
Shelley TxWits era
x TxWits era
y = Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
ShelleyTxWits era
x TxWits era
ShelleyTxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Allegra TxWits era
x TxWits era
y = Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
ShelleyTxWits era
x TxWits era
ShelleyTxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Mary TxWits era
x TxWits era
y = Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
ShelleyTxWits era
x TxWits era
ShelleyTxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Alonzo TxWits era
x TxWits era
y = Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
AlonzoTxWits era
x TxWits era
AlonzoTxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Babbage TxWits era
x TxWits era
y = Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
AlonzoTxWits era
x TxWits era
AlonzoTxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Conway TxWits era
x TxWits era
y = Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
AlonzoTxWits era
x TxWits era
AlonzoTxWits era
y
sameShelleyTxBody ::
Proof ShelleyEra ->
TxBody ShelleyEra ->
TxBody ShelleyEra ->
[(String, Maybe PDoc)]
sameShelleyTxBody :: Proof ShelleyEra
-> TxBody ShelleyEra -> TxBody ShelleyEra -> [(String, Maybe PDoc)]
sameShelleyTxBody Proof ShelleyEra
proof (ShelleyTxBody Set TxIn
i1 StrictSeq (TxOut ShelleyEra)
o1 StrictSeq (TxCert ShelleyEra)
c1 (Withdrawals Map RewardAccount Coin
w1) Coin
f1 SlotNo
s1 StrictMaybe (Update ShelleyEra)
pu1 StrictMaybe TxAuxDataHash
d1) (ShelleyTxBody Set TxIn
i2 StrictSeq (TxOut ShelleyEra)
o2 StrictSeq (TxCert ShelleyEra)
c2 (Withdrawals Map RewardAccount Coin
w2) Coin
f2 SlotNo
s2 StrictMaybe (Update ShelleyEra)
pu2 StrictMaybe TxAuxDataHash
d2) =
[ (String
"Inputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
i1 Set TxIn
i2)
, (String
"Outputs", (StrictSeq (ShelleyTxOut ShelleyEra) -> PDoc)
-> StrictSeq (ShelleyTxOut ShelleyEra)
-> StrictSeq (ShelleyTxOut ShelleyEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxOut ShelleyEra -> PDoc)
-> [ShelleyTxOut ShelleyEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof ShelleyEra -> TxOut ShelleyEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof ShelleyEra
proof) ([ShelleyTxOut ShelleyEra] -> PDoc)
-> (StrictSeq (ShelleyTxOut ShelleyEra)
-> [ShelleyTxOut ShelleyEra])
-> StrictSeq (ShelleyTxOut ShelleyEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxOut ShelleyEra) -> [ShelleyTxOut ShelleyEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut ShelleyEra)
StrictSeq (ShelleyTxOut ShelleyEra)
o1 StrictSeq (TxOut ShelleyEra)
StrictSeq (ShelleyTxOut ShelleyEra)
o2)
, (String
"TxCert", (StrictSeq (ShelleyTxCert ShelleyEra) -> PDoc)
-> StrictSeq (ShelleyTxCert ShelleyEra)
-> StrictSeq (ShelleyTxCert ShelleyEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxCert ShelleyEra -> PDoc)
-> [ShelleyTxCert ShelleyEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof ShelleyEra -> TxCert ShelleyEra -> PDoc
forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof ShelleyEra
proof) ([ShelleyTxCert ShelleyEra] -> PDoc)
-> (StrictSeq (ShelleyTxCert ShelleyEra)
-> [ShelleyTxCert ShelleyEra])
-> StrictSeq (ShelleyTxCert ShelleyEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxCert ShelleyEra) -> [ShelleyTxCert ShelleyEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert ShelleyEra)
StrictSeq (ShelleyTxCert ShelleyEra)
c1 StrictSeq (TxCert ShelleyEra)
StrictSeq (ShelleyTxCert ShelleyEra)
c2)
, (String
"WDRL", (Map RewardAccount Coin -> PDoc)
-> Map RewardAccount Coin -> Map RewardAccount Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((RewardAccount -> PDoc)
-> (Coin -> PDoc) -> Map RewardAccount Coin -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap RewardAccount -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map RewardAccount Coin
w1 Map RewardAccount Coin
w2)
, (String
"Fee", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
, (String
"TimeToLive", (SlotNo -> PDoc) -> SlotNo -> SlotNo -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia SlotNo -> PDoc
pcSlotNo SlotNo
s1 SlotNo
s2)
, (String
"PPupdate", (StrictMaybe (Update ShelleyEra) -> PDoc)
-> StrictMaybe (Update ShelleyEra)
-> StrictMaybe (Update ShelleyEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update ShelleyEra)
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update ShelleyEra)
pu1 StrictMaybe (Update ShelleyEra)
pu2)
, (String
"TxAuxDataHash", (StrictMaybe TxAuxDataHash -> PDoc)
-> StrictMaybe TxAuxDataHash
-> StrictMaybe TxAuxDataHash
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxAuxDataHash -> PDoc) -> StrictMaybe TxAuxDataHash -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(TxAuxDataHash SafeHash EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (SafeHash EraIndependentTxAuxData -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash SafeHash EraIndependentTxAuxData
h))) StrictMaybe TxAuxDataHash
d1 StrictMaybe TxAuxDataHash
d2)
]
sameAllegraTxBody ::
Proof AllegraEra ->
TxBody AllegraEra ->
TxBody AllegraEra ->
[(String, Maybe PDoc)]
sameAllegraTxBody :: Proof AllegraEra
-> TxBody AllegraEra -> TxBody AllegraEra -> [(String, Maybe PDoc)]
sameAllegraTxBody Proof AllegraEra
proof (AllegraTxBody Set TxIn
i1 StrictSeq (TxOut AllegraEra)
o1 StrictSeq (TxCert AllegraEra)
c1 (Withdrawals Map RewardAccount Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update AllegraEra)
pu1 StrictMaybe TxAuxDataHash
d1) (AllegraTxBody Set TxIn
i2 StrictSeq (TxOut AllegraEra)
o2 StrictSeq (TxCert AllegraEra)
c2 (Withdrawals Map RewardAccount Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update AllegraEra)
pu2 StrictMaybe TxAuxDataHash
d2) =
[ (String
"Inputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
i1 Set TxIn
i2)
, (String
"Outputs", (StrictSeq (ShelleyTxOut AllegraEra) -> PDoc)
-> StrictSeq (ShelleyTxOut AllegraEra)
-> StrictSeq (ShelleyTxOut AllegraEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxOut AllegraEra -> PDoc)
-> [ShelleyTxOut AllegraEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof AllegraEra -> TxOut AllegraEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof AllegraEra
proof) ([ShelleyTxOut AllegraEra] -> PDoc)
-> (StrictSeq (ShelleyTxOut AllegraEra)
-> [ShelleyTxOut AllegraEra])
-> StrictSeq (ShelleyTxOut AllegraEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxOut AllegraEra) -> [ShelleyTxOut AllegraEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut AllegraEra)
StrictSeq (ShelleyTxOut AllegraEra)
o1 StrictSeq (TxOut AllegraEra)
StrictSeq (ShelleyTxOut AllegraEra)
o2)
, (String
"TxCert", (StrictSeq (ShelleyTxCert AllegraEra) -> PDoc)
-> StrictSeq (ShelleyTxCert AllegraEra)
-> StrictSeq (ShelleyTxCert AllegraEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxCert AllegraEra -> PDoc)
-> [ShelleyTxCert AllegraEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof AllegraEra -> TxCert AllegraEra -> PDoc
forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof AllegraEra
proof) ([ShelleyTxCert AllegraEra] -> PDoc)
-> (StrictSeq (ShelleyTxCert AllegraEra)
-> [ShelleyTxCert AllegraEra])
-> StrictSeq (ShelleyTxCert AllegraEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxCert AllegraEra) -> [ShelleyTxCert AllegraEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert AllegraEra)
StrictSeq (ShelleyTxCert AllegraEra)
c1 StrictSeq (TxCert AllegraEra)
StrictSeq (ShelleyTxCert AllegraEra)
c2)
, (String
"WDRL", (Map RewardAccount Coin -> PDoc)
-> Map RewardAccount Coin -> Map RewardAccount Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((RewardAccount -> PDoc)
-> (Coin -> PDoc) -> Map RewardAccount Coin -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap RewardAccount -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map RewardAccount Coin
w1 Map RewardAccount Coin
w2)
, (String
"Fee", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
, (String
"ValidityInterval", (ValidityInterval -> PDoc)
-> ValidityInterval -> ValidityInterval -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
, (String
"PPupdate", (StrictMaybe (Update AllegraEra) -> PDoc)
-> StrictMaybe (Update AllegraEra)
-> StrictMaybe (Update AllegraEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update AllegraEra)
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update AllegraEra)
pu1 StrictMaybe (Update AllegraEra)
pu2)
, (String
"TxAuxDataHash", (StrictMaybe TxAuxDataHash -> PDoc)
-> StrictMaybe TxAuxDataHash
-> StrictMaybe TxAuxDataHash
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxAuxDataHash -> PDoc) -> StrictMaybe TxAuxDataHash -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(TxAuxDataHash SafeHash EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (SafeHash EraIndependentTxAuxData -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash SafeHash EraIndependentTxAuxData
h))) StrictMaybe TxAuxDataHash
d1 StrictMaybe TxAuxDataHash
d2)
]
sameMaryTxBody ::
Proof MaryEra ->
TxBody MaryEra ->
TxBody MaryEra ->
[(String, Maybe PDoc)]
sameMaryTxBody :: Proof MaryEra
-> TxBody MaryEra -> TxBody MaryEra -> [(String, Maybe PDoc)]
sameMaryTxBody Proof MaryEra
proof (MaryTxBody Set TxIn
i1 StrictSeq (TxOut MaryEra)
o1 StrictSeq (TxCert MaryEra)
c1 (Withdrawals Map RewardAccount Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update MaryEra)
pu1 StrictMaybe TxAuxDataHash
d1 MultiAsset
m1) (MaryTxBody Set TxIn
i2 StrictSeq (TxOut MaryEra)
o2 StrictSeq (TxCert MaryEra)
c2 (Withdrawals Map RewardAccount Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update MaryEra)
pu2 StrictMaybe TxAuxDataHash
d2 MultiAsset
m2) =
[ (String
"Inputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
i1 Set TxIn
i2)
, (String
"Outputs", (StrictSeq (ShelleyTxOut MaryEra) -> PDoc)
-> StrictSeq (ShelleyTxOut MaryEra)
-> StrictSeq (ShelleyTxOut MaryEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxOut MaryEra -> PDoc) -> [ShelleyTxOut MaryEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof MaryEra -> TxOut MaryEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof MaryEra
proof) ([ShelleyTxOut MaryEra] -> PDoc)
-> (StrictSeq (ShelleyTxOut MaryEra) -> [ShelleyTxOut MaryEra])
-> StrictSeq (ShelleyTxOut MaryEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxOut MaryEra) -> [ShelleyTxOut MaryEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut MaryEra)
StrictSeq (ShelleyTxOut MaryEra)
o1 StrictSeq (TxOut MaryEra)
StrictSeq (ShelleyTxOut MaryEra)
o2)
, (String
"TxCert", (StrictSeq (ShelleyTxCert MaryEra) -> PDoc)
-> StrictSeq (ShelleyTxCert MaryEra)
-> StrictSeq (ShelleyTxCert MaryEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxCert MaryEra -> PDoc) -> [ShelleyTxCert MaryEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof MaryEra -> TxCert MaryEra -> PDoc
forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof MaryEra
proof) ([ShelleyTxCert MaryEra] -> PDoc)
-> (StrictSeq (ShelleyTxCert MaryEra) -> [ShelleyTxCert MaryEra])
-> StrictSeq (ShelleyTxCert MaryEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxCert MaryEra) -> [ShelleyTxCert MaryEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert MaryEra)
StrictSeq (ShelleyTxCert MaryEra)
c1 StrictSeq (TxCert MaryEra)
StrictSeq (ShelleyTxCert MaryEra)
c2)
, (String
"WDRL", (Map RewardAccount Coin -> PDoc)
-> Map RewardAccount Coin -> Map RewardAccount Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((RewardAccount -> PDoc)
-> (Coin -> PDoc) -> Map RewardAccount Coin -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap RewardAccount -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map RewardAccount Coin
w1 Map RewardAccount Coin
w2)
, (String
"Fee", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
, (String
"ValidityInterval", (ValidityInterval -> PDoc)
-> ValidityInterval -> ValidityInterval -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
, (String
"PPupdate", (StrictMaybe (Update MaryEra) -> PDoc)
-> StrictMaybe (Update MaryEra)
-> StrictMaybe (Update MaryEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update MaryEra)
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update MaryEra)
pu1 StrictMaybe (Update MaryEra)
pu2)
, (String
"TxAuxDataHash", (StrictMaybe TxAuxDataHash -> PDoc)
-> StrictMaybe TxAuxDataHash
-> StrictMaybe TxAuxDataHash
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxAuxDataHash -> PDoc) -> StrictMaybe TxAuxDataHash -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(TxAuxDataHash SafeHash EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (SafeHash EraIndependentTxAuxData -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash SafeHash EraIndependentTxAuxData
h))) StrictMaybe TxAuxDataHash
d1 StrictMaybe TxAuxDataHash
d2)
, (String
"Mint", (MultiAsset -> PDoc) -> MultiAsset -> MultiAsset -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia MultiAsset -> PDoc
multiAssetSummary MultiAsset
m1 MultiAsset
m2)
]
sameAlonzoTxBody ::
Proof AlonzoEra ->
TxBody AlonzoEra ->
TxBody AlonzoEra ->
[(String, Maybe PDoc)]
sameAlonzoTxBody :: Proof AlonzoEra
-> TxBody AlonzoEra -> TxBody AlonzoEra -> [(String, Maybe PDoc)]
sameAlonzoTxBody
Proof AlonzoEra
proof
(AlonzoTxBody Set TxIn
i1 Set TxIn
cl1 StrictSeq (TxOut AlonzoEra)
o1 StrictSeq (TxCert AlonzoEra)
c1 (Withdrawals Map RewardAccount Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update AlonzoEra)
pu1 Set (KeyHash 'Witness)
r1 MultiAsset
m1 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s1 StrictMaybe TxAuxDataHash
d1 StrictMaybe Network
n1)
(AlonzoTxBody Set TxIn
i2 Set TxIn
cl2 StrictSeq (TxOut AlonzoEra)
o2 StrictSeq (TxCert AlonzoEra)
c2 (Withdrawals Map RewardAccount Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update AlonzoEra)
pu2 Set (KeyHash 'Witness)
r2 MultiAsset
m2 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s2 StrictMaybe TxAuxDataHash
d2 StrictMaybe Network
n2) =
[ (String
"Inputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
i1 Set TxIn
i2)
, (String
"Collateral", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
cl1 Set TxIn
cl2)
, (String
"Outputs", (StrictSeq (AlonzoTxOut AlonzoEra) -> PDoc)
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((AlonzoTxOut AlonzoEra -> PDoc) -> [AlonzoTxOut AlonzoEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof AlonzoEra -> TxOut AlonzoEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof AlonzoEra
proof) ([AlonzoTxOut AlonzoEra] -> PDoc)
-> (StrictSeq (AlonzoTxOut AlonzoEra) -> [AlonzoTxOut AlonzoEra])
-> StrictSeq (AlonzoTxOut AlonzoEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (AlonzoTxOut AlonzoEra) -> [AlonzoTxOut AlonzoEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut AlonzoEra)
StrictSeq (AlonzoTxOut AlonzoEra)
o1 StrictSeq (TxOut AlonzoEra)
StrictSeq (AlonzoTxOut AlonzoEra)
o2)
, (String
"Certs", (StrictSeq (ShelleyTxCert AlonzoEra) -> PDoc)
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxCert AlonzoEra -> PDoc)
-> [ShelleyTxCert AlonzoEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof AlonzoEra -> TxCert AlonzoEra -> PDoc
forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof AlonzoEra
proof) ([ShelleyTxCert AlonzoEra] -> PDoc)
-> (StrictSeq (ShelleyTxCert AlonzoEra)
-> [ShelleyTxCert AlonzoEra])
-> StrictSeq (ShelleyTxCert AlonzoEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxCert AlonzoEra) -> [ShelleyTxCert AlonzoEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert AlonzoEra)
StrictSeq (ShelleyTxCert AlonzoEra)
c1 StrictSeq (TxCert AlonzoEra)
StrictSeq (ShelleyTxCert AlonzoEra)
c2)
, (String
"WDRL", (Map RewardAccount Coin -> PDoc)
-> Map RewardAccount Coin -> Map RewardAccount Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((RewardAccount -> PDoc)
-> (Coin -> PDoc) -> Map RewardAccount Coin -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap RewardAccount -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map RewardAccount Coin
w1 Map RewardAccount Coin
w2)
, (String
"Fee", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
, (String
"ValidityInterval", (ValidityInterval -> PDoc)
-> ValidityInterval -> ValidityInterval -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
, (String
"PPupdate", (StrictMaybe (Update AlonzoEra) -> PDoc)
-> StrictMaybe (Update AlonzoEra)
-> StrictMaybe (Update AlonzoEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update AlonzoEra)
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update AlonzoEra)
pu1 StrictMaybe (Update AlonzoEra)
pu2)
, (String
"ReqSignerHashes", (Set (KeyHash 'Witness) -> PDoc)
-> Set (KeyHash 'Witness) -> Set (KeyHash 'Witness) -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((KeyHash 'Witness -> PDoc) -> Set (KeyHash 'Witness) -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet KeyHash 'Witness -> PDoc
forall (discriminator :: KeyRole). KeyHash discriminator -> PDoc
pcKeyHash) Set (KeyHash 'Witness)
r1 Set (KeyHash 'Witness)
r2)
, (String
"Mint", (MultiAsset -> PDoc) -> MultiAsset -> MultiAsset -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia MultiAsset -> PDoc
multiAssetSummary MultiAsset
m1 MultiAsset
m2)
, (String
"ScriptIntegrityHash", (StrictMaybe (SafeHash EraIndependentScriptIntegrity) -> PDoc)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((SafeHash EraIndependentScriptIntegrity -> PDoc)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity) -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (PDoc -> PDoc
trim (PDoc -> PDoc)
-> (SafeHash EraIndependentScriptIntegrity -> PDoc)
-> SafeHash EraIndependentScriptIntegrity
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SafeHash EraIndependentScriptIntegrity -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash)) StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s1 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s2)
, (String
"TxAuxDataHash", (StrictMaybe TxAuxDataHash -> PDoc)
-> StrictMaybe TxAuxDataHash
-> StrictMaybe TxAuxDataHash
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxAuxDataHash -> PDoc) -> StrictMaybe TxAuxDataHash -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(TxAuxDataHash SafeHash EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (SafeHash EraIndependentTxAuxData -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash SafeHash EraIndependentTxAuxData
h))) StrictMaybe TxAuxDataHash
d1 StrictMaybe TxAuxDataHash
d2)
, (String
"NetworkId", (StrictMaybe Network -> PDoc)
-> StrictMaybe Network -> StrictMaybe Network -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Network -> PDoc) -> StrictMaybe Network -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Network -> PDoc
pcNetwork) StrictMaybe Network
n1 StrictMaybe Network
n2)
]
sameBabbageTxBody ::
Proof BabbageEra ->
TxBody BabbageEra ->
TxBody BabbageEra ->
[(String, Maybe PDoc)]
sameBabbageTxBody :: Proof BabbageEra
-> TxBody BabbageEra -> TxBody BabbageEra -> [(String, Maybe PDoc)]
sameBabbageTxBody
Proof BabbageEra
proof
(BabbageTxBody Set TxIn
i1 Set TxIn
cl1 Set TxIn
ri1 StrictSeq (Sized (TxOut BabbageEra))
o1 StrictMaybe (Sized (TxOut BabbageEra))
cr1 StrictMaybe Coin
tc1 StrictSeq (TxCert BabbageEra)
c1 (Withdrawals Map RewardAccount Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update BabbageEra)
pu1 Set (KeyHash 'Witness)
r1 MultiAsset
m1 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s1 StrictMaybe TxAuxDataHash
d1 StrictMaybe Network
n1)
(BabbageTxBody Set TxIn
i2 Set TxIn
cl2 Set TxIn
ri2 StrictSeq (Sized (TxOut BabbageEra))
o2 StrictMaybe (Sized (TxOut BabbageEra))
cr2 StrictMaybe Coin
tc2 StrictSeq (TxCert BabbageEra)
c2 (Withdrawals Map RewardAccount Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update BabbageEra)
pu2 Set (KeyHash 'Witness)
r2 MultiAsset
m2 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s2 StrictMaybe TxAuxDataHash
d2 StrictMaybe Network
n2) =
[ (String
"SpendInputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
i1 Set TxIn
i2)
, (String
"ColInputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
cl1 Set TxIn
cl2)
, (String
"RefInputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
ri1 Set TxIn
ri2)
, (String
"Outputs", (StrictSeq (Sized (BabbageTxOut BabbageEra)) -> PDoc)
-> StrictSeq (Sized (BabbageTxOut BabbageEra))
-> StrictSeq (Sized (BabbageTxOut BabbageEra))
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Sized (BabbageTxOut BabbageEra) -> PDoc)
-> [Sized (BabbageTxOut BabbageEra)] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof BabbageEra -> TxOut BabbageEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof BabbageEra
proof (BabbageTxOut BabbageEra -> PDoc)
-> (Sized (BabbageTxOut BabbageEra) -> BabbageTxOut BabbageEra)
-> Sized (BabbageTxOut BabbageEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized (BabbageTxOut BabbageEra) -> BabbageTxOut BabbageEra
forall a. Sized a -> a
sizedValue) ([Sized (BabbageTxOut BabbageEra)] -> PDoc)
-> (StrictSeq (Sized (BabbageTxOut BabbageEra))
-> [Sized (BabbageTxOut BabbageEra)])
-> StrictSeq (Sized (BabbageTxOut BabbageEra))
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (Sized (BabbageTxOut BabbageEra))
-> [Sized (BabbageTxOut BabbageEra)]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (Sized (TxOut BabbageEra))
StrictSeq (Sized (BabbageTxOut BabbageEra))
o1 StrictSeq (Sized (TxOut BabbageEra))
StrictSeq (Sized (BabbageTxOut BabbageEra))
o2)
, (String
"ColReturn", (StrictMaybe (Sized (BabbageTxOut BabbageEra)) -> PDoc)
-> StrictMaybe (Sized (BabbageTxOut BabbageEra))
-> StrictMaybe (Sized (BabbageTxOut BabbageEra))
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Sized (BabbageTxOut BabbageEra) -> PDoc)
-> StrictMaybe (Sized (BabbageTxOut BabbageEra)) -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (Proof BabbageEra -> TxOut BabbageEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof BabbageEra
proof (BabbageTxOut BabbageEra -> PDoc)
-> (Sized (BabbageTxOut BabbageEra) -> BabbageTxOut BabbageEra)
-> Sized (BabbageTxOut BabbageEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized (BabbageTxOut BabbageEra) -> BabbageTxOut BabbageEra
forall a. Sized a -> a
sizedValue)) StrictMaybe (Sized (TxOut BabbageEra))
StrictMaybe (Sized (BabbageTxOut BabbageEra))
cr1 StrictMaybe (Sized (TxOut BabbageEra))
StrictMaybe (Sized (BabbageTxOut BabbageEra))
cr2)
, (String
"TotalCol", (StrictMaybe Coin -> PDoc)
-> StrictMaybe Coin -> StrictMaybe Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Coin -> PDoc) -> StrictMaybe Coin -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Coin -> PDoc
pcCoin) StrictMaybe Coin
tc1 StrictMaybe Coin
tc2)
, (String
"Certs", (StrictSeq (ShelleyTxCert BabbageEra) -> PDoc)
-> StrictSeq (ShelleyTxCert BabbageEra)
-> StrictSeq (ShelleyTxCert BabbageEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ShelleyTxCert BabbageEra -> PDoc)
-> [ShelleyTxCert BabbageEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof BabbageEra -> TxCert BabbageEra -> PDoc
forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof BabbageEra
proof) ([ShelleyTxCert BabbageEra] -> PDoc)
-> (StrictSeq (ShelleyTxCert BabbageEra)
-> [ShelleyTxCert BabbageEra])
-> StrictSeq (ShelleyTxCert BabbageEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (ShelleyTxCert BabbageEra) -> [ShelleyTxCert BabbageEra]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert BabbageEra)
StrictSeq (ShelleyTxCert BabbageEra)
c1 StrictSeq (TxCert BabbageEra)
StrictSeq (ShelleyTxCert BabbageEra)
c2)
, (String
"WDRL", (Map RewardAccount Coin -> PDoc)
-> Map RewardAccount Coin -> Map RewardAccount Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((RewardAccount -> PDoc)
-> (Coin -> PDoc) -> Map RewardAccount Coin -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap RewardAccount -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map RewardAccount Coin
w1 Map RewardAccount Coin
w2)
, (String
"Fee", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
, (String
"ValidityInterval", (ValidityInterval -> PDoc)
-> ValidityInterval -> ValidityInterval -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
, (String
"PPupdate", (StrictMaybe (Update BabbageEra) -> PDoc)
-> StrictMaybe (Update BabbageEra)
-> StrictMaybe (Update BabbageEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update BabbageEra)
_ -> String -> PDoc
forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update BabbageEra)
pu1 StrictMaybe (Update BabbageEra)
pu2)
, (String
"ReqSignerHashes", (Set (KeyHash 'Witness) -> PDoc)
-> Set (KeyHash 'Witness) -> Set (KeyHash 'Witness) -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((KeyHash 'Witness -> PDoc) -> Set (KeyHash 'Witness) -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet KeyHash 'Witness -> PDoc
forall (discriminator :: KeyRole). KeyHash discriminator -> PDoc
pcKeyHash) Set (KeyHash 'Witness)
r1 Set (KeyHash 'Witness)
r2)
, (String
"Mint", (MultiAsset -> PDoc) -> MultiAsset -> MultiAsset -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia MultiAsset -> PDoc
multiAssetSummary MultiAsset
m1 MultiAsset
m2)
, (String
"ScriptIntegrityHash", (StrictMaybe (SafeHash EraIndependentScriptIntegrity) -> PDoc)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((SafeHash EraIndependentScriptIntegrity -> PDoc)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity) -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (PDoc -> PDoc
trim (PDoc -> PDoc)
-> (SafeHash EraIndependentScriptIntegrity -> PDoc)
-> SafeHash EraIndependentScriptIntegrity
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SafeHash EraIndependentScriptIntegrity -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash)) StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s1 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s2)
, (String
"TxAuxDataHash", (StrictMaybe TxAuxDataHash -> PDoc)
-> StrictMaybe TxAuxDataHash
-> StrictMaybe TxAuxDataHash
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxAuxDataHash -> PDoc) -> StrictMaybe TxAuxDataHash -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(TxAuxDataHash SafeHash EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (SafeHash EraIndependentTxAuxData -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash SafeHash EraIndependentTxAuxData
h))) StrictMaybe TxAuxDataHash
d1 StrictMaybe TxAuxDataHash
d2)
, (String
"NetworkId", (StrictMaybe Network -> PDoc)
-> StrictMaybe Network -> StrictMaybe Network -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Network -> PDoc) -> StrictMaybe Network -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Network -> PDoc
pcNetwork) StrictMaybe Network
n1 StrictMaybe Network
n2)
]
sameConwayTxBody ::
Proof ConwayEra ->
TxBody ConwayEra ->
TxBody ConwayEra ->
[(String, Maybe PDoc)]
sameConwayTxBody :: Proof ConwayEra
-> TxBody ConwayEra -> TxBody ConwayEra -> [(String, Maybe PDoc)]
sameConwayTxBody
Proof ConwayEra
proof
(ConwayTxBody Set TxIn
i1 Set TxIn
cl1 Set TxIn
ri1 StrictSeq (Sized (TxOut ConwayEra))
o1 StrictMaybe (Sized (TxOut ConwayEra))
cr1 StrictMaybe Coin
tc1 OSet (TxCert ConwayEra)
c1 (Withdrawals Map RewardAccount Coin
w1) Coin
f1 ValidityInterval
v1 Set (KeyHash 'Witness)
r1 MultiAsset
m1 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s1 StrictMaybe TxAuxDataHash
d1 StrictMaybe Network
n1 VotingProcedures ConwayEra
vp1 OSet (ProposalProcedure ConwayEra)
pp1 StrictMaybe Coin
ctv1 Coin
td1)
(ConwayTxBody Set TxIn
i2 Set TxIn
cl2 Set TxIn
ri2 StrictSeq (Sized (TxOut ConwayEra))
o2 StrictMaybe (Sized (TxOut ConwayEra))
cr2 StrictMaybe Coin
tc2 OSet (TxCert ConwayEra)
c2 (Withdrawals Map RewardAccount Coin
w2) Coin
f2 ValidityInterval
v2 Set (KeyHash 'Witness)
r2 MultiAsset
m2 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s2 StrictMaybe TxAuxDataHash
d2 StrictMaybe Network
n2 VotingProcedures ConwayEra
vp2 OSet (ProposalProcedure ConwayEra)
pp2 StrictMaybe Coin
ctv2 Coin
td2) =
[ (String
"SpendInputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
i1 Set TxIn
i2)
, (String
"ColInputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
cl1 Set TxIn
cl2)
, (String
"RefInputs", (Set TxIn -> PDoc) -> Set TxIn -> Set TxIn -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxIn -> PDoc) -> Set TxIn -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet TxIn -> PDoc
pcTxIn) Set TxIn
ri1 Set TxIn
ri2)
, (String
"Outputs", (StrictSeq (Sized (BabbageTxOut ConwayEra)) -> PDoc)
-> StrictSeq (Sized (BabbageTxOut ConwayEra))
-> StrictSeq (Sized (BabbageTxOut ConwayEra))
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Sized (BabbageTxOut ConwayEra) -> PDoc)
-> [Sized (BabbageTxOut ConwayEra)] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof ConwayEra -> TxOut ConwayEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof ConwayEra
proof (BabbageTxOut ConwayEra -> PDoc)
-> (Sized (BabbageTxOut ConwayEra) -> BabbageTxOut ConwayEra)
-> Sized (BabbageTxOut ConwayEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized (BabbageTxOut ConwayEra) -> BabbageTxOut ConwayEra
forall a. Sized a -> a
sizedValue) ([Sized (BabbageTxOut ConwayEra)] -> PDoc)
-> (StrictSeq (Sized (BabbageTxOut ConwayEra))
-> [Sized (BabbageTxOut ConwayEra)])
-> StrictSeq (Sized (BabbageTxOut ConwayEra))
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictSeq (Sized (BabbageTxOut ConwayEra))
-> [Sized (BabbageTxOut ConwayEra)]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (Sized (TxOut ConwayEra))
StrictSeq (Sized (BabbageTxOut ConwayEra))
o1 StrictSeq (Sized (TxOut ConwayEra))
StrictSeq (Sized (BabbageTxOut ConwayEra))
o2)
, (String
"ColReturn", (StrictMaybe (Sized (BabbageTxOut ConwayEra)) -> PDoc)
-> StrictMaybe (Sized (BabbageTxOut ConwayEra))
-> StrictMaybe (Sized (BabbageTxOut ConwayEra))
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Sized (BabbageTxOut ConwayEra) -> PDoc)
-> StrictMaybe (Sized (BabbageTxOut ConwayEra)) -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (Proof ConwayEra -> TxOut ConwayEra -> PDoc
forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof ConwayEra
proof (BabbageTxOut ConwayEra -> PDoc)
-> (Sized (BabbageTxOut ConwayEra) -> BabbageTxOut ConwayEra)
-> Sized (BabbageTxOut ConwayEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sized (BabbageTxOut ConwayEra) -> BabbageTxOut ConwayEra
forall a. Sized a -> a
sizedValue)) StrictMaybe (Sized (TxOut ConwayEra))
StrictMaybe (Sized (BabbageTxOut ConwayEra))
cr1 StrictMaybe (Sized (TxOut ConwayEra))
StrictMaybe (Sized (BabbageTxOut ConwayEra))
cr2)
, (String
"TotalCol", (StrictMaybe Coin -> PDoc)
-> StrictMaybe Coin -> StrictMaybe Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Coin -> PDoc) -> StrictMaybe Coin -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Coin -> PDoc
pcCoin) StrictMaybe Coin
tc1 StrictMaybe Coin
tc2)
, (String
"Certs", (OSet (ConwayTxCert ConwayEra) -> PDoc)
-> OSet (ConwayTxCert ConwayEra)
-> OSet (ConwayTxCert ConwayEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ConwayTxCert ConwayEra -> PDoc)
-> [ConwayTxCert ConwayEra] -> PDoc
forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (Proof ConwayEra -> TxCert ConwayEra -> PDoc
forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof ConwayEra
proof) ([ConwayTxCert ConwayEra] -> PDoc)
-> (OSet (ConwayTxCert ConwayEra) -> [ConwayTxCert ConwayEra])
-> OSet (ConwayTxCert ConwayEra)
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OSet (ConwayTxCert ConwayEra) -> [ConwayTxCert ConwayEra]
forall a. OSet a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) OSet (TxCert ConwayEra)
OSet (ConwayTxCert ConwayEra)
c1 OSet (TxCert ConwayEra)
OSet (ConwayTxCert ConwayEra)
c2)
, (String
"WDRL", (Map RewardAccount Coin -> PDoc)
-> Map RewardAccount Coin -> Map RewardAccount Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((RewardAccount -> PDoc)
-> (Coin -> PDoc) -> Map RewardAccount Coin -> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap RewardAccount -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map RewardAccount Coin
w1 Map RewardAccount Coin
w2)
, (String
"Fee", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
, (String
"ValidityInterval", (ValidityInterval -> PDoc)
-> ValidityInterval -> ValidityInterval -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
, (String
"ReqSignerHashes", (Set (KeyHash 'Witness) -> PDoc)
-> Set (KeyHash 'Witness) -> Set (KeyHash 'Witness) -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((KeyHash 'Witness -> PDoc) -> Set (KeyHash 'Witness) -> PDoc
forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet KeyHash 'Witness -> PDoc
forall (discriminator :: KeyRole). KeyHash discriminator -> PDoc
pcKeyHash) Set (KeyHash 'Witness)
r1 Set (KeyHash 'Witness)
r2)
, (String
"Mint", (MultiAsset -> PDoc) -> MultiAsset -> MultiAsset -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia MultiAsset -> PDoc
multiAssetSummary MultiAsset
m1 MultiAsset
m2)
, (String
"ScriptIntegrityHash", (StrictMaybe (SafeHash EraIndependentScriptIntegrity) -> PDoc)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((SafeHash EraIndependentScriptIntegrity -> PDoc)
-> StrictMaybe (SafeHash EraIndependentScriptIntegrity) -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (PDoc -> PDoc
trim (PDoc -> PDoc)
-> (SafeHash EraIndependentScriptIntegrity -> PDoc)
-> SafeHash EraIndependentScriptIntegrity
-> PDoc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SafeHash EraIndependentScriptIntegrity -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash)) StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s1 StrictMaybe (SafeHash EraIndependentScriptIntegrity)
s2)
, (String
"TxAuxDataHash", (StrictMaybe TxAuxDataHash -> PDoc)
-> StrictMaybe TxAuxDataHash
-> StrictMaybe TxAuxDataHash
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((TxAuxDataHash -> PDoc) -> StrictMaybe TxAuxDataHash -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(TxAuxDataHash SafeHash EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (SafeHash EraIndependentTxAuxData -> PDoc
forall index. SafeHash index -> PDoc
ppSafeHash SafeHash EraIndependentTxAuxData
h))) StrictMaybe TxAuxDataHash
d1 StrictMaybe TxAuxDataHash
d2)
, (String
"NetworkId", (StrictMaybe Network -> PDoc)
-> StrictMaybe Network -> StrictMaybe Network -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Network -> PDoc) -> StrictMaybe Network -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Network -> PDoc
pcNetwork) StrictMaybe Network
n1 StrictMaybe Network
n2)
,
( String
"VotingProcedures"
, (Map Voter (Map GovActionId (VotingProcedure ConwayEra)) -> PDoc)
-> Map Voter (Map GovActionId (VotingProcedure ConwayEra))
-> Map Voter (Map GovActionId (VotingProcedure ConwayEra))
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia
((Voter -> PDoc)
-> (Map GovActionId (VotingProcedure ConwayEra) -> PDoc)
-> Map Voter (Map GovActionId (VotingProcedure ConwayEra))
-> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap Voter -> PDoc
pcVoter ((GovActionId -> PDoc)
-> (VotingProcedure ConwayEra -> PDoc)
-> Map GovActionId (VotingProcedure ConwayEra)
-> PDoc
forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap GovActionId -> PDoc
pcGovActionId VotingProcedure ConwayEra -> PDoc
forall era. VotingProcedure era -> PDoc
pcVotingProcedure))
(VotingProcedures ConwayEra
-> Map Voter (Map GovActionId (VotingProcedure ConwayEra))
forall era.
VotingProcedures era
-> Map Voter (Map GovActionId (VotingProcedure era))
unVotingProcedures VotingProcedures ConwayEra
vp1)
(VotingProcedures ConwayEra
-> Map Voter (Map GovActionId (VotingProcedure ConwayEra))
forall era.
VotingProcedures era
-> Map Voter (Map GovActionId (VotingProcedure era))
unVotingProcedures VotingProcedures ConwayEra
vp2)
)
, (String
"ProposalProcedures", (OSet (ProposalProcedure ConwayEra) -> PDoc)
-> OSet (ProposalProcedure ConwayEra)
-> OSet (ProposalProcedure ConwayEra)
-> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((ProposalProcedure ConwayEra -> PDoc)
-> OSet (ProposalProcedure ConwayEra) -> PDoc
forall a ann. (a -> Doc ann) -> OSet a -> Doc ann
ppOSet ProposalProcedure ConwayEra -> PDoc
forall era. ProposalProcedure era -> PDoc
pcProposalProcedure) OSet (ProposalProcedure ConwayEra)
pp1 OSet (ProposalProcedure ConwayEra)
pp2)
, (String
"CurrentTreasuryValue", (StrictMaybe Coin -> PDoc)
-> StrictMaybe Coin -> StrictMaybe Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ((Coin -> PDoc) -> StrictMaybe Coin -> PDoc
forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Coin -> PDoc
pcCoin) StrictMaybe Coin
ctv1 StrictMaybe Coin
ctv2)
, (String
"TreasuryDonation", (Coin -> PDoc) -> Coin -> Coin -> Maybe PDoc
forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
td1 Coin
td2)
]
sameTxBody :: Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody :: forall era.
Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody proof :: Proof era
proof@Proof era
Shelley TxBody era
x TxBody era
y = Proof ShelleyEra
-> TxBody ShelleyEra -> TxBody ShelleyEra -> [(String, Maybe PDoc)]
sameShelleyTxBody Proof era
Proof ShelleyEra
proof TxBody era
TxBody ShelleyEra
x TxBody era
TxBody ShelleyEra
y
sameTxBody proof :: Proof era
proof@Proof era
Allegra TxBody era
x TxBody era
y = Proof AllegraEra
-> TxBody AllegraEra -> TxBody AllegraEra -> [(String, Maybe PDoc)]
sameAllegraTxBody Proof era
Proof AllegraEra
proof TxBody era
TxBody AllegraEra
x TxBody era
TxBody AllegraEra
y
sameTxBody proof :: Proof era
proof@Proof era
Mary TxBody era
x TxBody era
y = Proof MaryEra
-> TxBody MaryEra -> TxBody MaryEra -> [(String, Maybe PDoc)]
sameMaryTxBody Proof era
Proof MaryEra
proof TxBody era
TxBody MaryEra
x TxBody era
TxBody MaryEra
y
sameTxBody proof :: Proof era
proof@Proof era
Alonzo TxBody era
x TxBody era
y = Proof AlonzoEra
-> TxBody AlonzoEra -> TxBody AlonzoEra -> [(String, Maybe PDoc)]
sameAlonzoTxBody Proof era
Proof AlonzoEra
proof TxBody era
TxBody AlonzoEra
x TxBody era
TxBody AlonzoEra
y
sameTxBody proof :: Proof era
proof@Proof era
Babbage TxBody era
x TxBody era
y = Proof BabbageEra
-> TxBody BabbageEra -> TxBody BabbageEra -> [(String, Maybe PDoc)]
sameBabbageTxBody Proof era
Proof BabbageEra
proof TxBody era
TxBody BabbageEra
x TxBody era
TxBody BabbageEra
y
sameTxBody proof :: Proof era
proof@Proof era
Conway TxBody era
x TxBody era
y = Proof ConwayEra
-> TxBody ConwayEra -> TxBody ConwayEra -> [(String, Maybe PDoc)]
sameConwayTxBody Proof era
Proof ConwayEra
proof TxBody era
TxBody ConwayEra
x TxBody era
TxBody ConwayEra
y
sameShelleyTx ::
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era ->
ShelleyTx era ->
ShelleyTx era ->
[(String, Maybe PDoc)]
sameShelleyTx :: forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof (ShelleyTx TxBody era
b1 TxWits era
w1 StrictMaybe (TxAuxData era)
aux1) (ShelleyTx TxBody era
b2 TxWits era
w2 StrictMaybe (TxAuxData era)
aux2) =
String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxBody " (Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
forall era.
Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody Proof era
proof TxBody era
b1 TxBody era
b2)
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxWits " (Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
ShelleyTxWits era
w1 TxWits era
ShelleyTxWits era
w2)
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [ (String
"AuxData", StrictMaybe (TxAuxData era)
-> StrictMaybe (TxAuxData era) -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow StrictMaybe (TxAuxData era)
aux1 StrictMaybe (TxAuxData era)
aux2)
]
sameAlonzoTx ::
( Reflect era
, AlonzoEraScript era
, TxWits era ~ AlonzoTxWits era
) =>
Proof era ->
AlonzoTx era ->
AlonzoTx era ->
[(String, Maybe PDoc)]
sameAlonzoTx :: forall era.
(Reflect era, AlonzoEraScript era,
TxWits era ~ AlonzoTxWits era) =>
Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
sameAlonzoTx Proof era
proof (AlonzoTx TxBody era
b1 TxWits era
w1 IsValid
v1 StrictMaybe (TxAuxData era)
aux1) (AlonzoTx TxBody era
b2 TxWits era
w2 IsValid
v2 StrictMaybe (TxAuxData era)
aux2) =
String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxBody " (Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
forall era.
Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody Proof era
proof TxBody era
b1 TxBody era
b2)
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ String -> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxWits " (Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
AlonzoTxWits era
w1 TxWits era
AlonzoTxWits era
w2)
[(String, Maybe PDoc)]
-> [(String, Maybe PDoc)] -> [(String, Maybe PDoc)]
forall a. [a] -> [a] -> [a]
++ [ (String
"AuxData", StrictMaybe (TxAuxData era)
-> StrictMaybe (TxAuxData era) -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow StrictMaybe (TxAuxData era)
aux1 StrictMaybe (TxAuxData era)
aux2)
, (String
"IsValid", IsValid -> IsValid -> Maybe PDoc
forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow IsValid
v1 IsValid
v2)
]
{-# NOINLINE sameAlonzoTx #-}
sameTx :: Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx :: forall era. Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx proof :: Proof era
proof@Proof era
Shelley Tx era
x Tx era
y = Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof Tx era
ShelleyTx era
x Tx era
ShelleyTx era
y
sameTx proof :: Proof era
proof@Proof era
Allegra Tx era
x Tx era
y = Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof Tx era
ShelleyTx era
x Tx era
ShelleyTx era
y
sameTx proof :: Proof era
proof@Proof era
Mary Tx era
x Tx era
y = Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof Tx era
ShelleyTx era
x Tx era
ShelleyTx era
y
sameTx proof :: Proof era
proof@Proof era
Alonzo Tx era
x Tx era
y = Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era,
TxWits era ~ AlonzoTxWits era) =>
Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
sameAlonzoTx Proof era
proof Tx era
AlonzoTx era
x Tx era
AlonzoTx era
y
sameTx proof :: Proof era
proof@Proof era
Babbage Tx era
x Tx era
y = Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era,
TxWits era ~ AlonzoTxWits era) =>
Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
sameAlonzoTx Proof era
proof Tx era
AlonzoTx era
x Tx era
AlonzoTx era
y
sameTx proof :: Proof era
proof@Proof era
Conway Tx era
x Tx era
y = Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, AlonzoEraScript era,
TxWits era ~ AlonzoTxWits era) =>
Proof era -> AlonzoTx era -> AlonzoTx era -> [(String, Maybe PDoc)]
sameAlonzoTx Proof era
proof Tx era
AlonzoTx era
x Tx era
AlonzoTx era
y
{-# NOINLINE sameTx #-}
ints :: [Int]
ints :: [Int]
ints = [Int
0 ..]
sameShelleyTxSeq ::
( Reflect era
, Tx era ~ ShelleyTx era
, SafeToHash (TxWits era)
) =>
Proof era ->
ShelleyTxSeq era ->
ShelleyTxSeq era ->
[(String, Maybe PDoc)]
sameShelleyTxSeq :: forall era.
(Reflect era, Tx era ~ ShelleyTx era, SafeToHash (TxWits era)) =>
Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
sameShelleyTxSeq Proof era
proof (ShelleyTxSeq StrictSeq (Tx era)
ss1) (ShelleyTxSeq StrictSeq (Tx era)
ss2) =
[SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency ((Int -> ShelleyTx era -> ShelleyTx era -> SomeDepend)
-> [Int] -> [ShelleyTx era] -> [ShelleyTx era] -> [SomeDepend]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Int -> ShelleyTx era -> ShelleyTx era -> SomeDepend
f [Int]
ints (StrictSeq (ShelleyTx era) -> [ShelleyTx era]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
StrictSeq (ShelleyTx era)
ss1) (StrictSeq (ShelleyTx era) -> [ShelleyTx era]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
StrictSeq (ShelleyTx era)
ss2))
where
f :: Int -> ShelleyTx era -> ShelleyTx era -> SomeDepend
f Int
n ShelleyTx era
t1 ShelleyTx era
t2 = String
-> (ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)])
-> ShelleyTx era
-> ShelleyTx era
-> SomeDepend
forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM (Int -> String
forall a. Show a => a -> String
show Int
n) (Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
forall era. Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx Proof era
proof) ShelleyTx era
t1 ShelleyTx era
t2
sameAlonzoTxSeq ::
( AlonzoEraTx era
, SafeToHash (TxWits era)
) =>
Proof era ->
AlonzoTxSeq era ->
AlonzoTxSeq era ->
[(String, Maybe PDoc)]
sameAlonzoTxSeq :: forall era.
(AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof (AlonzoTxSeq StrictSeq (Tx era)
ss1) (AlonzoTxSeq StrictSeq (Tx era)
ss2) =
[SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency ((Int -> Tx era -> Tx era -> SomeDepend)
-> [Int] -> [Tx era] -> [Tx era] -> [SomeDepend]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Int -> Tx era -> Tx era -> SomeDepend
f [Int]
ints (StrictSeq (Tx era) -> [Tx era]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
ss1) (StrictSeq (Tx era) -> [Tx era]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
ss2))
where
f :: Int -> Tx era -> Tx era -> SomeDepend
f Int
n Tx era
t1 Tx era
t2 = String
-> (Tx era -> Tx era -> [(String, Maybe PDoc)])
-> Tx era
-> Tx era
-> SomeDepend
forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM (Int -> String
forall a. Show a => a -> String
show Int
n) (Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
forall era. Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx Proof era
proof) Tx era
t1 Tx era
t2
sameTxSeq :: Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
sameTxSeq :: forall era.
Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
sameTxSeq proof :: Proof era
proof@Proof era
Shelley TxSeq era
x TxSeq era
y = Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, Tx era ~ ShelleyTx era, SafeToHash (TxWits era)) =>
Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
sameShelleyTxSeq Proof era
proof TxSeq era
ShelleyTxSeq era
x TxSeq era
ShelleyTxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Allegra TxSeq era
x TxSeq era
y = Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, Tx era ~ ShelleyTx era, SafeToHash (TxWits era)) =>
Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
sameShelleyTxSeq Proof era
proof TxSeq era
ShelleyTxSeq era
x TxSeq era
ShelleyTxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Mary TxSeq era
x TxSeq era
y = Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
forall era.
(Reflect era, Tx era ~ ShelleyTx era, SafeToHash (TxWits era)) =>
Proof era
-> ShelleyTxSeq era -> ShelleyTxSeq era -> [(String, Maybe PDoc)]
sameShelleyTxSeq Proof era
proof TxSeq era
ShelleyTxSeq era
x TxSeq era
ShelleyTxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Alonzo TxSeq era
x TxSeq era
y = Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
forall era.
(AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof TxSeq era
AlonzoTxSeq era
x TxSeq era
AlonzoTxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Babbage TxSeq era
x TxSeq era
y = Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
forall era.
(AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof TxSeq era
AlonzoTxSeq era
x TxSeq era
AlonzoTxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Conway TxSeq era
x TxSeq era
y = Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
forall era.
(AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof TxSeq era
AlonzoTxSeq era
x TxSeq era
AlonzoTxSeq era
y
{-# NOINLINE sameTxSeq #-}