{-# 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 #-}

-- | A Proof parameterized equality test, that records the 'sameness' of
--   individual record fields, this way it is possible to know where the
--   equality failed.
module Test.Cardano.Ledger.Generic.Same where

import Cardano.Ledger.Allegra.TxBody (AllegraTxBody (..))
import Cardano.Ledger.Alonzo.Tx (AlonzoTx (..))
import Cardano.Ledger.Alonzo.TxBody (AlonzoTxBody (..))
import Cardano.Ledger.Alonzo.TxSeq (AlonzoTxSeq (..))
import Cardano.Ledger.Alonzo.TxWits (AlonzoTxWits (..), Redeemers (..), TxDats (..))
import Cardano.Ledger.AuxiliaryData (AuxiliaryDataHash (..))
import Cardano.Ledger.Babbage.TxBody (BabbageTxBody (..))
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.TxBody (ConwayTxBody (..))
import Cardano.Ledger.Keys (KeyHash, KeyRole (Genesis))
import Cardano.Ledger.Mary.TxBody (MaryTxBody (..))
import Cardano.Ledger.SafeHash (SafeToHash)
import Cardano.Ledger.Shelley.API.Mempool (ApplyTxError)
import Cardano.Ledger.Shelley.BlockChain (ShelleyTxSeq (..))
import Cardano.Ledger.Shelley.LedgerState (
  CertState (..),
  DState (..),
  EpochState (..),
  LedgerState (..),
  NewEpochState (..),
  PState (..),
  StashedAVVMAddresses,
  UTxOState (..),
  VState (..),
  curPParamsEpochStateL,
  prevPParamsEpochStateL,
 )
import Cardano.Ledger.Shelley.PParams (ProposedPPUpdates (..))
import Cardano.Ledger.Shelley.Translation ()
import Cardano.Ledger.Shelley.Tx (ShelleyTx (..))
import Cardano.Ledger.Shelley.TxBody (ShelleyTxBody (..))
import Cardano.Ledger.Shelley.TxWits (ShelleyTxWits (..))
import Cardano.Ledger.UTxO (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 c) where
  terse :: KeyHash 'Genesis c -> String
terse KeyHash 'Genesis c
x = forall a. Show a => a -> String
show (forall (discriminator :: KeyRole) c.
KeyHash discriminator c -> PDoc
pcKeyHash KeyHash 'Genesis c
x)

instance Terse (PParamsUpdate (ShelleyEra c)) where
  terse :: PParamsUpdate (ShelleyEra c) -> String
terse PParamsUpdate (ShelleyEra c)
x = forall a. Show a => a -> String
show PParamsUpdate (ShelleyEra c)
x

instance Terse (PParamsUpdate (AllegraEra c)) where
  terse :: PParamsUpdate (AllegraEra c) -> String
terse PParamsUpdate (AllegraEra c)
x = forall a. Show a => a -> String
show PParamsUpdate (AllegraEra c)
x

instance Terse (PParamsUpdate (MaryEra c)) where
  terse :: PParamsUpdate (MaryEra c) -> String
terse PParamsUpdate (MaryEra c)
x = forall a. Show a => a -> String
show PParamsUpdate (MaryEra c)
x

instance Terse (PParamsUpdate (AlonzoEra c)) where
  terse :: PParamsUpdate (AlonzoEra c) -> String
terse PParamsUpdate (AlonzoEra c)
x = forall a. Show a => a -> String
show PParamsUpdate (AlonzoEra c)
x

instance Terse (PParamsUpdate (BabbageEra c)) where
  terse :: PParamsUpdate (BabbageEra c) -> String
terse PParamsUpdate (BabbageEra c)
x = forall a. Show a => a -> String
show PParamsUpdate (BabbageEra c)
x

instance Terse (PParamsUpdate (ConwayEra c)) where
  terse :: PParamsUpdate (ConwayEra c) -> String
terse PParamsUpdate (ConwayEra c)
x = forall a. Show a => a -> String
show PParamsUpdate (ConwayEra c)
x

-- ========================================
-- Helper functions

-- | Relabel by appending 's' to the front of the path
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 forall a. [a] -> [a] -> [a]
++ String
n, Maybe x
x) forall a. a -> [a] -> [a]
: forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
s [(String, Maybe x)]
xs

-- | Dispays a difference vertically as
--   x
--     =/=
--   y
notEq :: Doc a -> Doc a -> Doc a
notEq :: forall a. Doc a -> Doc a -> Doc a
notEq Doc a
x Doc a
y = forall ann. [Doc ann] -> Doc ann
vsep [Doc a
x, forall ann. Int -> Doc ann -> Doc ann
indent Int
3 (forall ann. Text -> Doc ann
text Text
"=/="), Doc a
y]

-- | Compare for equality, and display difference using 'show'
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 forall a. Eq a => a -> a -> Bool
== t
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a. Doc a -> Doc a -> Doc a
notEq (forall a. String -> Doc a
ppString (forall a. Show a => a -> String
show t
x)) (forall a. String -> Doc a
ppString (forall a. Show a => a -> String
show t
y)))

-- | Compare for equality, and display differences using 'pcf'
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 forall a. Eq a => a -> a -> Bool
== t
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a. Doc a -> Doc a -> Doc a
notEq (t -> PDoc
pcf t
x) (t -> PDoc
pcf t
y))

-- ==========================================

-- | The Same class is similar to Eq but returns descriptions (paths and
--   non-matching components) for each difference in a large structure.
class Same era t where
  same :: Proof era -> t -> t -> [(String, Maybe PDoc)]

instance Same era (CertState era) where
  same :: Proof era
-> CertState era -> CertState era -> [(String, Maybe PDoc)]
same Proof era
proof (CertState VState era
d1 PState era
p1 DState era
v1) (CertState VState era
d2 PState era
p2 DState era
v2) =
    forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"DState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof VState era
d1 VState era
d2)
      forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"PState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof PState era
p1 PState era
p2)
      forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"VState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof DState era
v1 DState era
v2)

instance Same era (PState era) where
  same :: Proof era -> PState era -> PState era -> [(String, Maybe PDoc)]
same Proof era
_proof (PState Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
pp1 Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
fpp1 Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
ret1 Map (KeyHash 'StakePool (EraCrypto era)) Coin
d1) (PState Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
pp2 Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
fpp2 Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
ret2 Map (KeyHash 'StakePool (EraCrypto era)) Coin
d2) =
    [ (String
"PoolParams", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
pp1 Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
pp2)
    , (String
"FuturePoolParams", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
fpp1 Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
fpp2)
    , (String
"Retiring", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
ret1 Map (KeyHash 'StakePool (EraCrypto era)) EpochNo
ret2)
    , (String
"Deposits", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (KeyHash 'StakePool (EraCrypto era)) Coin
d1 Map (KeyHash 'StakePool (EraCrypto era)) Coin
d2)
    ]

instance Same era (DState era) where
  same :: Proof era -> DState era -> DState era -> [(String, Maybe PDoc)]
same Proof era
_proof (DState UMap (EraCrypto era)
u1 Map (FutureGenDeleg (EraCrypto era)) (GenDelegPair (EraCrypto era))
fgd1 GenDelegs (EraCrypto era)
gd1 InstantaneousRewards (EraCrypto era)
ir1) (DState UMap (EraCrypto era)
u2 Map (FutureGenDeleg (EraCrypto era)) (GenDelegPair (EraCrypto era))
fgd2 GenDelegs (EraCrypto era)
gd2 InstantaneousRewards (EraCrypto era)
ir2) =
    [ (String
"Unified", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow UMap (EraCrypto era)
u1 UMap (EraCrypto era)
u2)
    , (String
"FutureGenDelegs", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map (FutureGenDeleg (EraCrypto era)) (GenDelegPair (EraCrypto era))
fgd1 Map (FutureGenDeleg (EraCrypto era)) (GenDelegPair (EraCrypto era))
fgd2)
    , (String
"GenDelegs", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow GenDelegs (EraCrypto era)
gd1 GenDelegs (EraCrypto era)
gd2)
    , (String
"InstantaneousRewards", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow InstantaneousRewards (EraCrypto era)
ir1 InstantaneousRewards (EraCrypto era)
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 (EraCrypto era)) (DRepState (EraCrypto era))
dr1 CommitteeState era
cchk1 EpochNo
numDE1) (VState Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dr2 CommitteeState era
cchk2 EpochNo
numDE2) =
    [ (String
"DReps", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dr1 Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dr2)
    , (String
"CC Hot Keys", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow CommitteeState era
cchk1 CommitteeState era
cchk2)
    , (String
"Num Dormant Epochs", 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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", forall era. Proof era -> UTxO era -> UTxO era -> Maybe PDoc
sameUTxO Proof era
proof (forall era. UTxOState era -> UTxO era
utxosUtxo UTxOState era
u1) (forall era. UTxOState era -> UTxO era
utxosUtxo UTxOState era
u2))
    , (String
"Deposited", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. UTxOState era -> Coin
utxosDeposited UTxOState era
u1) (forall era. UTxOState era -> Coin
utxosDeposited UTxOState era
u2))
    , (String
"Fees", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. UTxOState era -> Coin
utxosFees UTxOState era
u1) (forall era. UTxOState era -> Coin
utxosFees UTxOState era
u2))
    ]
      forall a. [a] -> [a] -> [a]
++ [(String, Maybe PDoc)]
ppu
      forall a. [a] -> [a] -> [a]
++ [(String
"StakeDistr", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. UTxOState era -> IncrementalStake (EraCrypto era)
utxosStakeDistr UTxOState era
u1) (forall era. UTxOState era -> IncrementalStake (EraCrypto era)
utxosStakeDistr UTxOState era
u2))]
    where
      ppuPretty :: GovState era ~ ShelleyGovState era => [(String, Maybe PDoc)]
      ppuPretty :: (GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty = [(String
"ShelleyGovState", forall era.
Proof era
-> ShelleyGovState era -> ShelleyGovState era -> Maybe PDoc
samePPUP Proof era
proof (forall era. UTxOState era -> GovState era
utxosGovState UTxOState era
u1) (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 -> (GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
        Proof era
Mary -> (GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
        Proof era
Allegra -> (GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
        Proof era
Alonzo -> (GovState era ~ ShelleyGovState era) => [(String, Maybe PDoc)]
ppuPretty
        Proof era
Babbage -> (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 =
    forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"UTxOState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (forall era. LedgerState era -> UTxOState era
lsUTxOState LedgerState era
x1) (forall era. LedgerState era -> UTxOState era
lsUTxOState LedgerState era
x2))
      forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"CertState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (forall era. LedgerState era -> CertState era
lsCertState LedgerState era
x1) (forall era. LedgerState era -> CertState era
lsCertState LedgerState era
x2))

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
"AccountState", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. EpochState era -> AccountState
esAccountState EpochState era
e1) (forall era. EpochState era -> AccountState
esAccountState EpochState era
e2))
    , (String
"SnapShots", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. EpochState era -> SnapShots (EraCrypto era)
esSnapshots EpochState era
e1) (forall era. EpochState era -> SnapShots (EraCrypto era)
esSnapshots EpochState era
e2))
    , (String
"PrevPP", forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
proof (EpochState era
e1 forall s a. s -> Getting a s a -> a
^. forall era. EraGov era => Lens' (EpochState era) (PParams era)
prevPParamsEpochStateL) (EpochState era
e2 forall s a. s -> Getting a s a -> a
^. forall era. EraGov era => Lens' (EpochState era) (PParams era)
prevPParamsEpochStateL))
    , (String
"CurPP", forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
proof (EpochState era
e1 forall s a. s -> Getting a s a -> a
^. forall era. EraGov era => Lens' (EpochState era) (PParams era)
curPParamsEpochStateL) (EpochState era
e2 forall s a. s -> Getting a s a -> a
^. forall era. EraGov era => Lens' (EpochState era) (PParams era)
curPParamsEpochStateL))
    , (String
"NonMyopic", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. EpochState era -> NonMyopic (EraCrypto era)
esNonMyopic EpochState era
e1) (forall era. EpochState era -> NonMyopic (EraCrypto era)
esNonMyopic EpochState era
e2))
    ]
      forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"LedgerState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (forall era. EpochState era -> LedgerState era
esLState EpochState era
e1) (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 StashedAVVMAddresses era
x forall a. Eq a => a -> a -> Bool
== StashedAVVMAddresses era
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a ann. Show a => a -> Doc ann
viaShow StashedAVVMAddresses era
x)
    Proof era
Allegra -> if StashedAVVMAddresses era
x forall a. Eq a => a -> a -> Bool
== StashedAVVMAddresses era
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a ann. Show a => a -> Doc ann
viaShow StashedAVVMAddresses era
x)
    Proof era
Mary -> if StashedAVVMAddresses era
x forall a. Eq a => a -> a -> Bool
== StashedAVVMAddresses era
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a ann. Show a => a -> Doc ann
viaShow StashedAVVMAddresses era
x)
    Proof era
Alonzo -> if StashedAVVMAddresses era
x forall a. Eq a => a -> a -> Bool
== StashedAVVMAddresses era
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a ann. Show a => a -> Doc ann
viaShow StashedAVVMAddresses era
x)
    Proof era
Babbage -> if StashedAVVMAddresses era
x forall a. Eq a => a -> a -> Bool
== StashedAVVMAddresses era
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (forall a ann. Show a => a -> Doc ann
viaShow StashedAVVMAddresses era
x)
    Proof era
Conway -> if StashedAVVMAddresses era
x forall a. Eq a => a -> a -> Bool
== StashedAVVMAddresses era
y then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (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", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. NewEpochState era -> EpochNo
nesEL NewEpochState era
n1) (forall era. NewEpochState era -> EpochNo
nesEL NewEpochState era
n2))
    , (String
"nesBprev", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. NewEpochState era -> BlocksMade (EraCrypto era)
nesBprev NewEpochState era
n1) (forall era. NewEpochState era -> BlocksMade (EraCrypto era)
nesBprev NewEpochState era
n2))
    , (String
"nesBcur", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. NewEpochState era -> BlocksMade (EraCrypto era)
nesBcur NewEpochState era
n1) (forall era. NewEpochState era -> BlocksMade (EraCrypto era)
nesBcur NewEpochState era
n2))
    , (String
"nesRU", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era.
NewEpochState era -> StrictMaybe (PulsingRewUpdate (EraCrypto era))
nesRu NewEpochState era
n1) (forall era.
NewEpochState era -> StrictMaybe (PulsingRewUpdate (EraCrypto era))
nesRu NewEpochState era
n2))
    , (String
"nesPd", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. NewEpochState era -> PoolDistr (EraCrypto era)
nesPd NewEpochState era
n1) (forall era. NewEpochState era -> PoolDistr (EraCrypto era)
nesPd NewEpochState era
n2))
    , (String
"nesStashAVVM", forall era.
Proof era
-> StashedAVVMAddresses era
-> StashedAVVMAddresses era
-> Maybe PDoc
sameStashedAVVMAddresses Proof era
proof (forall era. NewEpochState era -> StashedAVVMAddresses era
stashedAVVMAddresses NewEpochState era
n1) (forall era. NewEpochState era -> StashedAVVMAddresses era
stashedAVVMAddresses NewEpochState era
n2))
    ]
      forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"EpochState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (forall era. NewEpochState era -> EpochState era
nesEs NewEpochState era
n1) (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

-- | If x occurs in y then a difference in x forces a difference in y,
--   so only return the information on x if it has differences.
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) 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 -> forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel (String
labx forall a. [a] -> [a] -> [a]
++ String
" ") [(String, Maybe PDoc)]
ansx 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 (forall era.
ShelleyLedgerExamples era -> Block (BHeader (EraCrypto era)) era
sleBlock ShelleyLedgerExamples era
x1, forall era.
ShelleyLedgerExamples era -> Block (BHeader (EraCrypto era)) era
sleBlock ShelleyLedgerExamples era
x2) of
    (Block' BHeader StandardCrypto
h1 TxSeq era
a1 ByteString
_, Block' BHeader StandardCrypto
h2 TxSeq era
a2 ByteString
_) ->
      [SomeDepend] -> [(String, Maybe PDoc)]
sameWithDependency
        [ forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM String
"Tx" (forall era.
Reflect era =>
Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx Proof era
proof) (forall era. ShelleyLedgerExamples era -> Tx era
sleTx ShelleyLedgerExamples era
x1) (forall era. ShelleyLedgerExamples era -> Tx era
sleTx ShelleyLedgerExamples era
x2)
        , forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM String
"TxSeq" (forall era.
Reflect era =>
Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
sameTxSeq Proof era
proof) TxSeq era
a1 TxSeq era
a2
        ]
        forall a. [a] -> [a] -> [a]
++ [ (String
"BlockHeader", if BHeader StandardCrypto
h1 forall a. Eq a => a -> a -> Bool
== BHeader StandardCrypto
h2 then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just (PDoc
"UnequalBlockHeader"))
           ,
             ( String
"HashHeader"
             , if (forall era. ShelleyLedgerExamples era -> HashHeader (EraCrypto era)
sleHashHeader ShelleyLedgerExamples era
x1) forall a. Eq a => a -> a -> Bool
== (forall era. ShelleyLedgerExamples era -> HashHeader (EraCrypto era)
sleHashHeader ShelleyLedgerExamples era
x2)
                then forall a. Maybe a
Nothing
                else forall a. a -> Maybe a
Just (PDoc
"UnequalHashHeader")
             )
           , (String
"ApplyTxError", forall era.
Proof era -> ApplyTxError era -> ApplyTxError era -> Maybe PDoc
sameLedgerFail Proof era
proof (forall era. ShelleyLedgerExamples era -> ApplyTxError era
sleApplyTxError ShelleyLedgerExamples era
x1) (forall era. ShelleyLedgerExamples era -> ApplyTxError era
sleApplyTxError ShelleyLedgerExamples era
x2))
           , (String
"RewardsCredentials", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era.
ShelleyLedgerExamples era
-> Set (Either Coin (Credential 'Staking (EraCrypto era)))
sleRewardsCredentials ShelleyLedgerExamples era
x1) (forall era.
ShelleyLedgerExamples era
-> Set (Either Coin (Credential 'Staking (EraCrypto era)))
sleRewardsCredentials ShelleyLedgerExamples era
x2))
           ]
        forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"Result " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (forall era. ShelleyLedgerExamples era -> ShelleyResultExamples era
sleResultExamples ShelleyLedgerExamples era
x1) (forall era. ShelleyLedgerExamples era -> ShelleyResultExamples era
sleResultExamples ShelleyLedgerExamples era
x2))
        forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"NewEpochState " (forall era t.
Same era t =>
Proof era -> t -> t -> [(String, Maybe PDoc)]
same Proof era
proof (forall era. ShelleyLedgerExamples era -> NewEpochState era
sleNewEpochState ShelleyLedgerExamples era
x1) (forall era. ShelleyLedgerExamples era -> NewEpochState era
sleNewEpochState ShelleyLedgerExamples era
x2))
        forall a. [a] -> [a] -> [a]
++ [ (String
"ChainDepState", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era.
ShelleyLedgerExamples era -> ChainDepState (EraCrypto era)
sleChainDepState ShelleyLedgerExamples era
x1) (forall era.
ShelleyLedgerExamples era -> ChainDepState (EraCrypto era)
sleChainDepState ShelleyLedgerExamples era
x2))
           , (String
"TranslationContext", forall era.
Proof era
-> TranslationContext era -> TranslationContext era -> Maybe PDoc
sameTransCtx Proof era
proof (forall era. ShelleyLedgerExamples era -> TranslationContext era
sleTranslationContext ShelleyLedgerExamples era
x1) (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", forall era. Proof era -> PParams era -> PParams era -> Maybe PDoc
samePParams Proof era
proof (forall era. ShelleyResultExamples era -> PParams era
srePParams ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> PParams era
srePParams ShelleyResultExamples era
r2))
    ,
      ( String
"ProposedPPUpdates"
      , case Proof era
proof of
          Proof era
Shelley -> forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
          Proof era
Allegra -> forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
          Proof era
Mary -> forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
          Proof era
Alonzo -> forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
          Proof era
Babbage -> forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
          Proof era
Conway -> forall {era} {a}.
(Terse (PParamsUpdate era), Eq (PParamsHKD StrictMaybe era)) =>
ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> ProposedPPUpdates era
sreProposedPPUpdates ShelleyResultExamples era
r2)
      )
    , (String
"poolDistr", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era. ShelleyResultExamples era -> PoolDistr (EraCrypto era)
srePoolDistr ShelleyResultExamples era
r1) (forall era. ShelleyResultExamples era -> PoolDistr (EraCrypto era)
srePoolDistr ShelleyResultExamples era
r2))
    , (String
"NonMyopicRewards", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era.
ShelleyResultExamples era
-> Map
     (Either Coin (Credential 'Staking (EraCrypto era)))
     (Map (KeyHash 'StakePool (EraCrypto era)) Coin)
sreNonMyopicRewards ShelleyResultExamples era
r1) (forall era.
ShelleyResultExamples era
-> Map
     (Either Coin (Credential 'Staking (EraCrypto era)))
     (Map (KeyHash 'StakePool (EraCrypto era)) Coin)
sreNonMyopicRewards ShelleyResultExamples era
r2))
    , (String
"ShelleyGenesis", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow (forall era.
ShelleyResultExamples era -> ShelleyGenesis (EraCrypto era)
sreShelleyGenesis ShelleyResultExamples era
r1) (forall era.
ShelleyResultExamples era -> ShelleyGenesis (EraCrypto era)
sreShelleyGenesis ShelleyResultExamples era
r2))
    ]
    where
      getmap :: ProposedPPUpdates era
-> Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)
getmap (ProposedPPUpdates Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)
x) = Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)
x
      sameProposedPPUpdates :: ProposedPPUpdates era -> ProposedPPUpdates era -> Maybe (Doc a)
sameProposedPPUpdates ProposedPPUpdates era
x ProposedPPUpdates era
y = forall {a} {a}. Show a => [a] -> Maybe (Doc a)
ppDiff forall a b. (a -> b) -> a -> b
$ forall a b. (Ord a, Eq b) => Map a b -> Map a b -> [Case a b]
mapdiffs (forall {era}.
ProposedPPUpdates era
-> Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)
getmap ProposedPPUpdates era
x) (forall {era}.
ProposedPPUpdates era
-> Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)
getmap ProposedPPUpdates era
y)
        where
          ppDiff :: [a] -> Maybe (Doc a)
ppDiff [] = forall a. Maybe a
Nothing
          ppDiff [a]
xs = forall a. a -> Maybe a
Just (forall a. String -> Doc a
ppString (forall a. Show a => a -> String
show [a]
xs))

-- =========================================================================
-- Functions like 'same' from the 'Same' class, but which apply to type families
-- We cannot make them Same instances because they are type families.
-- We also can avoid all extra constraints by pattern matching against all current Proofs.

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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = 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 = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
x TxOut era
y
sameTxOut Proof era
Allegra TxOut era
x TxOut era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
x TxOut era
y
sameTxOut Proof era
Mary TxOut era
x TxOut era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
x TxOut era
y
sameTxOut Proof era
Alonzo TxOut era
x TxOut era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
x TxOut era
y
sameTxOut Proof era
Babbage TxOut era
x TxOut era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
x TxOut era
y
sameTxOut Proof era
Conway TxOut era
x TxOut era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TxOut era
x TxOut era
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 = 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 = 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 = 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 = 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 = 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 = 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 = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
x TranslationContext era
y
sameTransCtx Proof era
Allegra TranslationContext era
x TranslationContext era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
x TranslationContext era
y
sameTransCtx Proof era
Mary TranslationContext era
x TranslationContext era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
x TranslationContext era
y
sameTransCtx Proof era
Alonzo TranslationContext era
x TranslationContext era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
x TranslationContext era
y
sameTransCtx Proof era
Babbage TranslationContext era
x TranslationContext era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
x TranslationContext era
y
sameTransCtx Proof era
Conway TranslationContext era
x TranslationContext era
y = forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow TranslationContext era
x TranslationContext era
y
{-# NOINLINE sameTransCtx #-}

-- ==========================
-- Comparing witnesses for Sameness

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 (EraCrypto era))
vk1 Map (ScriptHash (EraCrypto era)) (Script era)
sh1 Set (BootstrapWitness (EraCrypto era))
boot1) (ShelleyTxWits Set (WitVKey 'Witness (EraCrypto era))
vk2 Map (ScriptHash (EraCrypto era)) (Script era)
sh2 Set (BootstrapWitness (EraCrypto era))
boot2) =
  [ (String
"VKeyWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet (forall era (keyrole :: KeyRole).
(Reflect era, Typeable keyrole) =>
Proof era -> WitVKey keyrole (EraCrypto era) -> PDoc
pcWitVKey Proof era
proof)) Set (WitVKey 'Witness (EraCrypto era))
vk1 Set (WitVKey 'Witness (EraCrypto era))
vk2)
  , (String
"ScriptWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall era. ScriptHash era -> PDoc
pcScriptHash (forall era. Reflect era => Proof era -> Script era -> PDoc
pcScript Proof era
proof)) Map (ScriptHash (EraCrypto era)) (Script era)
sh1 Map (ScriptHash (EraCrypto era)) (Script era)
sh2)
  , (String
"BootWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\Set (BootstrapWitness StandardCrypto)
_ -> forall a. String -> Doc a
ppString String
"BOOTWITS") Set (BootstrapWitness (EraCrypto era))
boot1 Set (BootstrapWitness (EraCrypto era))
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 (EraCrypto era))
vk1 Set (BootstrapWitness (EraCrypto era))
boot1 Map (ScriptHash (EraCrypto era)) (Script era)
sh1 (TxDats Map (DataHash (EraCrypto era)) (Data era)
d1) (Redeemers Map (PlutusPurpose AsIx era) (Data era, ExUnits)
r1))
  (AlonzoTxWits Set (WitVKey 'Witness (EraCrypto era))
vk2 Set (BootstrapWitness (EraCrypto era))
boot2 Map (ScriptHash (EraCrypto era)) (Script era)
sh2 (TxDats Map (DataHash (EraCrypto era)) (Data era)
d2) (Redeemers Map (PlutusPurpose AsIx era) (Data era, ExUnits)
r2)) =
    [ (String
"VKeyWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet (forall era (keyrole :: KeyRole).
(Reflect era, Typeable keyrole) =>
Proof era -> WitVKey keyrole (EraCrypto era) -> PDoc
pcWitVKey Proof era
proof)) Set (WitVKey 'Witness (EraCrypto era))
vk1 Set (WitVKey 'Witness (EraCrypto era))
vk2)
    , (String
"BootWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\Set (BootstrapWitness StandardCrypto)
_ -> forall a. String -> Doc a
ppString String
"BOOTWITS") Set (BootstrapWitness (EraCrypto era))
boot1 Set (BootstrapWitness (EraCrypto era))
boot2)
    , (String
"ScriptWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall era. ScriptHash era -> PDoc
pcScriptHash (forall era. Reflect era => Proof era -> Script era -> PDoc
pcScript Proof era
proof)) Map (ScriptHash (EraCrypto era)) (Script era)
sh1 Map (ScriptHash (EraCrypto era)) (Script era)
sh2)
    , (String
"DataWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall era. DataHash era -> PDoc
pcDataHash forall era. Era era => Data era -> PDoc
pcData) Map (DataHash (EraCrypto era)) (Data era)
d1 Map (DataHash (EraCrypto era)) (Data era)
d2)
    , (String
"RedeemerWits", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall era. Reflect era => PlutusPurpose AsIx era -> PDoc
ppPlutusPurposeAsIx (forall t1 t2. (t1 -> PDoc) -> (t2 -> PDoc) -> (t1, t2) -> PDoc
pcPair 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 :: Reflect era => Proof era -> TxWits era -> TxWits era -> [(String, Maybe PDoc)]
sameTxWits :: forall era.
Reflect era =>
Proof era -> TxWits era -> TxWits era -> [(String, Maybe PDoc)]
sameTxWits proof :: Proof era
proof@Proof era
Shelley TxWits era
x TxWits era
y = forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
x TxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Allegra TxWits era
x TxWits era
y = forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
x TxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Mary TxWits era
x TxWits era
y = forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
x TxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Alonzo TxWits era
x TxWits era
y = forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
x TxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Babbage TxWits era
x TxWits era
y = forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
x TxWits era
y
sameTxWits proof :: Proof era
proof@Proof era
Conway TxWits era
x TxWits era
y = forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
x TxWits era
y

-- =======================
-- Comparing TxBody for Sameness

sameShelleyTxBody ::
  Reflect era =>
  Proof era ->
  ShelleyTxBody era ->
  ShelleyTxBody era ->
  [(String, Maybe PDoc)]
sameShelleyTxBody :: forall era.
Reflect era =>
Proof era
-> ShelleyTxBody era -> ShelleyTxBody era -> [(String, Maybe PDoc)]
sameShelleyTxBody Proof era
proof (ShelleyTxBody Set (TxIn (EraCrypto era))
i1 StrictSeq (TxOut era)
o1 StrictSeq (TxCert era)
c1 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w1) Coin
f1 SlotNo
s1 StrictMaybe (Update era)
pu1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1) (ShelleyTxBody Set (TxIn (EraCrypto era))
i2 StrictSeq (TxOut era)
o2 StrictSeq (TxCert era)
c2 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w2) Coin
f2 SlotNo
s2 StrictMaybe (Update era)
pu2 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2) =
  [ (String
"Inputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
i2)
  , (String
"Outputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut era)
o1 StrictSeq (TxOut era)
o2)
  , (String
"TxCert", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert era)
c1 StrictSeq (TxCert era)
c2)
  , (String
"WDRL", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. RewardAccount c -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map (RewardAcnt (EraCrypto era)) Coin
w1 Map (RewardAcnt (EraCrypto era)) Coin
w2)
  , (String
"Fee", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
  , (String
"TimeToLive", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia SlotNo -> PDoc
pcSlotNo SlotNo
s1 SlotNo
s2)
  , (String
"PPupdate", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update era)
_ -> forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update era)
pu1 StrictMaybe (Update era)
pu2)
  , (String
"AuxDataHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(AuxiliaryDataHash SafeHash StandardCrypto EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (forall c index. SafeHash c index -> PDoc
ppSafeHash SafeHash StandardCrypto EraIndependentTxAuxData
h))) StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2)
  ]

sameAllegraTxBody ::
  Reflect era =>
  Proof era ->
  AllegraTxBody era ->
  AllegraTxBody era ->
  [(String, Maybe PDoc)]
sameAllegraTxBody :: forall era.
Reflect era =>
Proof era
-> AllegraTxBody era -> AllegraTxBody era -> [(String, Maybe PDoc)]
sameAllegraTxBody Proof era
proof (AllegraTxBody Set (TxIn (EraCrypto era))
i1 StrictSeq (TxOut era)
o1 StrictSeq (TxCert era)
c1 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update era)
pu1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1) (AllegraTxBody Set (TxIn (EraCrypto era))
i2 StrictSeq (TxOut era)
o2 StrictSeq (TxCert era)
c2 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update era)
pu2 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2) =
  [ (String
"Inputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
i2)
  , (String
"Outputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut era)
o1 StrictSeq (TxOut era)
o2)
  , (String
"TxCert", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert era)
c1 StrictSeq (TxCert era)
c2)
  , (String
"WDRL", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. RewardAccount c -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map (RewardAcnt (EraCrypto era)) Coin
w1 Map (RewardAcnt (EraCrypto era)) Coin
w2)
  , (String
"Fee", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
  , (String
"ValidityInterval", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
  , (String
"PPupdate", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update era)
_ -> forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update era)
pu1 StrictMaybe (Update era)
pu2)
  , (String
"AuxDataHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(AuxiliaryDataHash SafeHash StandardCrypto EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (forall c index. SafeHash c index -> PDoc
ppSafeHash SafeHash StandardCrypto EraIndependentTxAuxData
h))) StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2)
  ]

sameMaryTxBody ::
  Reflect era =>
  Proof era ->
  MaryTxBody era ->
  MaryTxBody era ->
  [(String, Maybe PDoc)]
sameMaryTxBody :: forall era.
Reflect era =>
Proof era
-> MaryTxBody era -> MaryTxBody era -> [(String, Maybe PDoc)]
sameMaryTxBody Proof era
proof (MaryTxBody Set (TxIn (EraCrypto era))
i1 StrictSeq (TxOut era)
o1 StrictSeq (TxCert era)
c1 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update era)
pu1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 MultiAsset (EraCrypto era)
m1) (MaryTxBody Set (TxIn (EraCrypto era))
i2 StrictSeq (TxOut era)
o2 StrictSeq (TxCert era)
c2 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update era)
pu2 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2 MultiAsset (EraCrypto era)
m2) =
  [ (String
"Inputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
i2)
  , (String
"Outputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut era)
o1 StrictSeq (TxOut era)
o2)
  , (String
"TxCert", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert era)
c1 StrictSeq (TxCert era)
c2)
  , (String
"WDRL", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. RewardAccount c -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map (RewardAcnt (EraCrypto era)) Coin
w1 Map (RewardAcnt (EraCrypto era)) Coin
w2)
  , (String
"Fee", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
  , (String
"ValidityInterval", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
  , (String
"PPupdate", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update era)
_ -> forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update era)
pu1 StrictMaybe (Update era)
pu2)
  , (String
"AuxDataHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(AuxiliaryDataHash SafeHash StandardCrypto EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (forall c index. SafeHash c index -> PDoc
ppSafeHash SafeHash StandardCrypto EraIndependentTxAuxData
h))) StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2)
  , (String
"Mint", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia forall c. MultiAsset c -> PDoc
multiAssetSummary MultiAsset (EraCrypto era)
m1 MultiAsset (EraCrypto era)
m2)
  ]

sameAlonzoTxBody ::
  Reflect era =>
  Proof era ->
  AlonzoTxBody era ->
  AlonzoTxBody era ->
  [(String, Maybe PDoc)]
sameAlonzoTxBody :: forall era.
Reflect era =>
Proof era
-> AlonzoTxBody era -> AlonzoTxBody era -> [(String, Maybe PDoc)]
sameAlonzoTxBody
  Proof era
proof
  (AlonzoTxBody Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
cl1 StrictSeq (TxOut era)
o1 StrictSeq (TxCert era)
c1 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update era)
pu1 Set (KeyHash 'Witness (EraCrypto era))
r1 MultiAsset (EraCrypto era)
m1 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe Network
n1)
  (AlonzoTxBody Set (TxIn (EraCrypto era))
i2 Set (TxIn (EraCrypto era))
cl2 StrictSeq (TxOut era)
o2 StrictSeq (TxCert era)
c2 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update era)
pu2 Set (KeyHash 'Witness (EraCrypto era))
r2 MultiAsset (EraCrypto era)
m2 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s2 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2 StrictMaybe Network
n2) =
    [ (String
"Inputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
i2)
    , (String
"Collateral", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
cl1 Set (TxIn (EraCrypto era))
cl2)
    , (String
"Outputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxOut era)
o1 StrictSeq (TxOut era)
o2)
    , (String
"Certs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert era)
c1 StrictSeq (TxCert era)
c2)
    , (String
"WDRL", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. RewardAccount c -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map (RewardAcnt (EraCrypto era)) Coin
w1 Map (RewardAcnt (EraCrypto era)) Coin
w2)
    , (String
"Fee", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
    , (String
"ValidityInterval", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
    , (String
"PPupdate", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update era)
_ -> forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update era)
pu1 StrictMaybe (Update era)
pu2)
    , (String
"ReqSignerHashes", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall (discriminator :: KeyRole) c.
KeyHash discriminator c -> PDoc
pcKeyHash) Set (KeyHash 'Witness (EraCrypto era))
r1 Set (KeyHash 'Witness (EraCrypto era))
r2)
    , (String
"Mint", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia forall c. MultiAsset c -> PDoc
multiAssetSummary MultiAsset (EraCrypto era)
m1 MultiAsset (EraCrypto era)
m2)
    , (String
"ScriptIntegrityHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (PDoc -> PDoc
trim forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c index. SafeHash c index -> PDoc
ppSafeHash)) StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s1 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s2)
    , (String
"AuxDataHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(AuxiliaryDataHash SafeHash StandardCrypto EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (forall c index. SafeHash c index -> PDoc
ppSafeHash SafeHash StandardCrypto EraIndependentTxAuxData
h))) StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2)
    , (String
"NetworkId", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Network -> PDoc
pcNetwork) StrictMaybe Network
n1 StrictMaybe Network
n2)
    ]

sameBabbageTxBody ::
  ( Reflect era
  , BabbageEraTxBody era
  ) =>
  Proof era ->
  BabbageTxBody era ->
  BabbageTxBody era ->
  [(String, Maybe PDoc)]
sameBabbageTxBody :: forall era.
(Reflect era, BabbageEraTxBody era) =>
Proof era
-> BabbageTxBody era -> BabbageTxBody era -> [(String, Maybe PDoc)]
sameBabbageTxBody
  Proof era
proof
  (BabbageTxBody Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
cl1 Set (TxIn (EraCrypto era))
ri1 StrictSeq (Sized (TxOut era))
o1 StrictMaybe (Sized (TxOut era))
cr1 StrictMaybe Coin
tc1 StrictSeq (TxCert era)
c1 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w1) Coin
f1 ValidityInterval
v1 StrictMaybe (Update era)
pu1 Set (KeyHash 'Witness (EraCrypto era))
r1 MultiAsset (EraCrypto era)
m1 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe Network
n1)
  (BabbageTxBody Set (TxIn (EraCrypto era))
i2 Set (TxIn (EraCrypto era))
cl2 Set (TxIn (EraCrypto era))
ri2 StrictSeq (Sized (TxOut era))
o2 StrictMaybe (Sized (TxOut era))
cr2 StrictMaybe Coin
tc2 StrictSeq (TxCert era)
c2 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w2) Coin
f2 ValidityInterval
v2 StrictMaybe (Update era)
pu2 Set (KeyHash 'Witness (EraCrypto era))
r2 MultiAsset (EraCrypto era)
m2 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s2 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2 StrictMaybe Network
n2) =
    [ (String
"SpendInputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
i2)
    , (String
"ColInputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
cl1 Set (TxIn (EraCrypto era))
cl2)
    , (String
"RefInputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
ri1 Set (TxIn (EraCrypto era))
ri2)
    , (String
"Outputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Sized a -> a
sizedValue) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (Sized (TxOut era))
o1 StrictSeq (Sized (TxOut era))
o2)
    , (String
"ColReturn", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Sized a -> a
sizedValue)) StrictMaybe (Sized (TxOut era))
cr1 StrictMaybe (Sized (TxOut era))
cr2)
    , (String
"TotalCol", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Coin -> PDoc
pcCoin) StrictMaybe Coin
tc1 StrictMaybe Coin
tc2)
    , (String
"Certs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Proof era -> TxCert era -> PDoc
pcTxCert Proof era
proof) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (TxCert era)
c1 StrictSeq (TxCert era)
c2)
    , (String
"WDRL", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. RewardAccount c -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map (RewardAcnt (EraCrypto era)) Coin
w1 Map (RewardAcnt (EraCrypto era)) Coin
w2)
    , (String
"Fee", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
    , (String
"ValidityInterval", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
    , (String
"PPupdate", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (\StrictMaybe (Update era)
_ -> forall a. String -> Doc a
ppString String
"Update") StrictMaybe (Update era)
pu1 StrictMaybe (Update era)
pu2)
    , (String
"ReqSignerHashes", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall (discriminator :: KeyRole) c.
KeyHash discriminator c -> PDoc
pcKeyHash) Set (KeyHash 'Witness (EraCrypto era))
r1 Set (KeyHash 'Witness (EraCrypto era))
r2)
    , (String
"Mint", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia forall c. MultiAsset c -> PDoc
multiAssetSummary MultiAsset (EraCrypto era)
m1 MultiAsset (EraCrypto era)
m2)
    , (String
"ScriptIntegrityHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (PDoc -> PDoc
trim forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c index. SafeHash c index -> PDoc
ppSafeHash)) StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s1 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s2)
    , (String
"AuxDataHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(AuxiliaryDataHash SafeHash StandardCrypto EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (forall c index. SafeHash c index -> PDoc
ppSafeHash SafeHash StandardCrypto EraIndependentTxAuxData
h))) StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2)
    , (String
"NetworkId", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Network -> PDoc
pcNetwork) StrictMaybe Network
n1 StrictMaybe Network
n2)
    ]

sameConwayTxBody ::
  ( ConwayEraTxBody era
  , Reflect era
  ) =>
  Proof era ->
  ConwayTxBody era ->
  ConwayTxBody era ->
  [(String, Maybe PDoc)]
sameConwayTxBody :: forall era.
(ConwayEraTxBody era, Reflect era) =>
Proof era
-> ConwayTxBody era -> ConwayTxBody era -> [(String, Maybe PDoc)]
sameConwayTxBody
  Proof era
proof
  (ConwayTxBody Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
cl1 Set (TxIn (EraCrypto era))
ri1 StrictSeq (Sized (TxOut era))
o1 StrictMaybe (Sized (TxOut era))
cr1 StrictMaybe Coin
tc1 OSet (ConwayTxCert era)
c1 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w1) Coin
f1 ValidityInterval
v1 Set (KeyHash 'Witness (EraCrypto era))
r1 MultiAsset (EraCrypto era)
m1 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe Network
n1 VotingProcedures era
vp1 OSet (ProposalProcedure era)
pp1 StrictMaybe Coin
ctv1 Coin
td1)
  (ConwayTxBody Set (TxIn (EraCrypto era))
i2 Set (TxIn (EraCrypto era))
cl2 Set (TxIn (EraCrypto era))
ri2 StrictSeq (Sized (TxOut era))
o2 StrictMaybe (Sized (TxOut era))
cr2 StrictMaybe Coin
tc2 OSet (ConwayTxCert era)
c2 (Withdrawals Map (RewardAcnt (EraCrypto era)) Coin
w2) Coin
f2 ValidityInterval
v2 Set (KeyHash 'Witness (EraCrypto era))
r2 MultiAsset (EraCrypto era)
m2 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s2 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2 StrictMaybe Network
n2 VotingProcedures era
vp2 OSet (ProposalProcedure era)
pp2 StrictMaybe Coin
ctv2 Coin
td2) =
    [ (String
"SpendInputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
i1 Set (TxIn (EraCrypto era))
i2)
    , (String
"ColInputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
cl1 Set (TxIn (EraCrypto era))
cl2)
    , (String
"RefInputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall c. TxIn c -> PDoc
pcTxIn) Set (TxIn (EraCrypto era))
ri1 Set (TxIn (EraCrypto era))
ri2)
    , (String
"Outputs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Sized a -> a
sizedValue) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) StrictSeq (Sized (TxOut era))
o1 StrictSeq (Sized (TxOut era))
o2)
    , (String
"ColReturn", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (forall era. Reflect era => Proof era -> TxOut era -> PDoc
pcTxOut Proof era
proof forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Sized a -> a
sizedValue)) StrictMaybe (Sized (TxOut era))
cr1 StrictMaybe (Sized (TxOut era))
cr2)
    , (String
"TotalCol", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Coin -> PDoc
pcCoin) StrictMaybe Coin
tc1 StrictMaybe Coin
tc2)
    , (String
"Certs", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> [x] -> Doc ann
ppList forall c. ConwayTxCert c -> PDoc
pcConwayTxCert forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList) OSet (ConwayTxCert era)
c1 OSet (ConwayTxCert era)
c2)
    , (String
"WDRL", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. RewardAccount c -> PDoc
pcRewardAccount Coin -> PDoc
pcCoin) Map (RewardAcnt (EraCrypto era)) Coin
w1 Map (RewardAcnt (EraCrypto era)) Coin
w2)
    , (String
"Fee", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
f1 Coin
f2)
    , (String
"ValidityInterval", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia ValidityInterval -> PDoc
ppValidityInterval ValidityInterval
v1 ValidityInterval
v2)
    , (String
"ReqSignerHashes", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> Set x -> Doc ann
ppSet forall (discriminator :: KeyRole) c.
KeyHash discriminator c -> PDoc
pcKeyHash) Set (KeyHash 'Witness (EraCrypto era))
r1 Set (KeyHash 'Witness (EraCrypto era))
r2)
    , (String
"Mint", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia forall c. MultiAsset c -> PDoc
multiAssetSummary MultiAsset (EraCrypto era)
m1 MultiAsset (EraCrypto era)
m2)
    , (String
"ScriptIntegrityHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (PDoc -> PDoc
trim forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c index. SafeHash c index -> PDoc
ppSafeHash)) StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s1 StrictMaybe (ScriptIntegrityHash (EraCrypto era))
s2)
    , (String
"AuxDataHash", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe (\(AuxiliaryDataHash SafeHash StandardCrypto EraIndependentTxAuxData
h) -> PDoc -> PDoc
trim (forall c index. SafeHash c index -> PDoc
ppSafeHash SafeHash StandardCrypto EraIndependentTxAuxData
h))) StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d1 StrictMaybe (AuxiliaryDataHash (EraCrypto era))
d2)
    , (String
"NetworkId", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Network -> PDoc
pcNetwork) StrictMaybe Network
n1 StrictMaybe Network
n2)
    ,
      ( String
"VotingProcedures"
      , forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia
          (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. Voter c -> PDoc
pcVoter (forall k v. (k -> PDoc) -> (v -> PDoc) -> Map k v -> PDoc
ppMap forall c. GovActionId c -> PDoc
pcGovActionId forall era. VotingProcedure era -> PDoc
pcVotingProcedure))
          (forall era.
VotingProcedures era
-> Map
     (Voter (EraCrypto era))
     (Map (GovActionId (EraCrypto era)) (VotingProcedure era))
unVotingProcedures VotingProcedures era
vp1)
          (forall era.
VotingProcedures era
-> Map
     (Voter (EraCrypto era))
     (Map (GovActionId (EraCrypto era)) (VotingProcedure era))
unVotingProcedures VotingProcedures era
vp2)
      )
    , (String
"ProposalProcedures", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall a ann. (a -> Doc ann) -> OSet a -> Doc ann
ppOSet forall era. ProposalProcedure era -> PDoc
pcProposalProcedure) OSet (ProposalProcedure era)
pp1 OSet (ProposalProcedure era)
pp2)
    , (String
"CurrentTreasuryValue", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia (forall x ann. (x -> Doc ann) -> StrictMaybe x -> Doc ann
ppStrictMaybe Coin -> PDoc
pcCoin) StrictMaybe Coin
ctv1 StrictMaybe Coin
ctv2)
    , (String
"TreasuryDonation", forall t. Eq t => (t -> PDoc) -> t -> t -> Maybe PDoc
eqVia Coin -> PDoc
pcCoin Coin
td1 Coin
td2)
    ]

sameTxBody :: Reflect era => Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody :: forall era.
Reflect era =>
Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody proof :: Proof era
proof@Proof era
Shelley TxBody era
x TxBody era
y = forall era.
Reflect era =>
Proof era
-> ShelleyTxBody era -> ShelleyTxBody era -> [(String, Maybe PDoc)]
sameShelleyTxBody Proof era
proof TxBody era
x TxBody era
y
sameTxBody proof :: Proof era
proof@Proof era
Allegra TxBody era
x TxBody era
y = forall era.
Reflect era =>
Proof era
-> AllegraTxBody era -> AllegraTxBody era -> [(String, Maybe PDoc)]
sameAllegraTxBody Proof era
proof TxBody era
x TxBody era
y
sameTxBody proof :: Proof era
proof@Proof era
Mary TxBody era
x TxBody era
y = forall era.
Reflect era =>
Proof era
-> MaryTxBody era -> MaryTxBody era -> [(String, Maybe PDoc)]
sameMaryTxBody Proof era
proof TxBody era
x TxBody era
y
sameTxBody proof :: Proof era
proof@Proof era
Alonzo TxBody era
x TxBody era
y = forall era.
Reflect era =>
Proof era
-> AlonzoTxBody era -> AlonzoTxBody era -> [(String, Maybe PDoc)]
sameAlonzoTxBody Proof era
proof TxBody era
x TxBody era
y
sameTxBody proof :: Proof era
proof@Proof era
Babbage TxBody era
x TxBody era
y = forall era.
(Reflect era, BabbageEraTxBody era) =>
Proof era
-> BabbageTxBody era -> BabbageTxBody era -> [(String, Maybe PDoc)]
sameBabbageTxBody Proof era
proof TxBody era
x TxBody era
y
sameTxBody proof :: Proof era
proof@Proof era
Conway TxBody era
x TxBody era
y = forall era.
(ConwayEraTxBody era, Reflect era) =>
Proof era
-> ConwayTxBody era -> ConwayTxBody era -> [(String, Maybe PDoc)]
sameConwayTxBody Proof era
proof TxBody era
x TxBody era
y

-- =======================
-- Comparing Tx for Sameness

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) =
  forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxBody " (forall era.
Reflect era =>
Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody Proof era
proof TxBody era
b1 TxBody era
b2)
    forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxWits " (forall era.
Reflect era =>
Proof era
-> ShelleyTxWits era -> ShelleyTxWits era -> [(String, Maybe PDoc)]
sameShelleyTxWits Proof era
proof TxWits era
w1 TxWits era
w2)
    forall a. [a] -> [a] -> [a]
++ [ (String
"AuxData", 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) =
  forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxBody " (forall era.
Reflect era =>
Proof era -> TxBody era -> TxBody era -> [(String, Maybe PDoc)]
sameTxBody Proof era
proof TxBody era
b1 TxBody era
b2)
    forall a. [a] -> [a] -> [a]
++ forall x. String -> [(String, Maybe x)] -> [(String, Maybe x)]
extendLabel String
"TxWits " (forall era.
(Reflect era, AlonzoEraScript era) =>
Proof era
-> AlonzoTxWits era -> AlonzoTxWits era -> [(String, Maybe PDoc)]
sameAlonzoTxWits Proof era
proof TxWits era
w1 TxWits era
w2)
    forall a. [a] -> [a] -> [a]
++ [ (String
"AuxData", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow StrictMaybe (TxAuxData era)
aux1 StrictMaybe (TxAuxData era)
aux2)
       , (String
"IsValid", forall t. (Eq t, Show t) => t -> t -> Maybe PDoc
eqByShow IsValid
v1 IsValid
v2)
       ]
{-# NOINLINE sameAlonzoTx #-}

sameTx :: Reflect era => Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx :: forall era.
Reflect era =>
Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx proof :: Proof era
proof@Proof era
Shelley Tx era
x Tx era
y = forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof Tx era
x Tx era
y
sameTx proof :: Proof era
proof@Proof era
Allegra Tx era
x Tx era
y = forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof Tx era
x Tx era
y
sameTx proof :: Proof era
proof@Proof era
Mary Tx era
x Tx era
y = forall era.
(Reflect era, TxWits era ~ ShelleyTxWits era) =>
Proof era
-> ShelleyTx era -> ShelleyTx era -> [(String, Maybe PDoc)]
sameShelleyTx Proof era
proof Tx era
x Tx era
y
sameTx proof :: Proof era
proof@Proof era
Alonzo Tx era
x Tx era
y = 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
x Tx era
y
sameTx proof :: Proof era
proof@Proof era
Babbage Tx era
x Tx era
y = 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
x Tx era
y
sameTx proof :: Proof era
proof@Proof era
Conway Tx era
x Tx era
y = 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
x Tx era
y
{-# NOINLINE sameTx #-}

-- ==========================
-- Comparing TxSeq for Sameness

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 (forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Int -> ShelleyTx era -> ShelleyTx era -> SomeDepend
f [Int]
ints (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
ss1) (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
ss2))
  where
    f :: Int -> ShelleyTx era -> ShelleyTx era -> SomeDepend
f Int
n ShelleyTx era
t1 ShelleyTx era
t2 = forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM (forall a. Show a => a -> String
show Int
n) (forall era.
Reflect era =>
Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx Proof era
proof) ShelleyTx era
t1 ShelleyTx era
t2

sameAlonzoTxSeq ::
  ( Reflect era
  , AlonzoEraTx era
  , SafeToHash (TxWits era)
  ) =>
  Proof era ->
  AlonzoTxSeq era ->
  AlonzoTxSeq era ->
  [(String, Maybe PDoc)]
sameAlonzoTxSeq :: forall era.
(Reflect 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 (forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 Int -> Tx era -> Tx era -> SomeDepend
f [Int]
ints (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList StrictSeq (Tx era)
ss1) (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 = forall x.
String
-> (x -> x -> [(String, Maybe PDoc)]) -> x -> x -> SomeDepend
SomeM (forall a. Show a => a -> String
show Int
n) (forall era.
Reflect era =>
Proof era -> Tx era -> Tx era -> [(String, Maybe PDoc)]
sameTx Proof era
proof) Tx era
t1 Tx era
t2

sameTxSeq :: Reflect era => Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
sameTxSeq :: forall era.
Reflect era =>
Proof era -> TxSeq era -> TxSeq era -> [(String, Maybe PDoc)]
sameTxSeq proof :: Proof era
proof@Proof era
Shelley TxSeq era
x TxSeq era
y = 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
x TxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Allegra TxSeq era
x TxSeq era
y = 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
x TxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Mary TxSeq era
x TxSeq era
y = 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
x TxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Alonzo TxSeq era
x TxSeq era
y = forall era.
(Reflect era, AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof TxSeq era
x TxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Babbage TxSeq era
x TxSeq era
y = forall era.
(Reflect era, AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof TxSeq era
x TxSeq era
y
sameTxSeq proof :: Proof era
proof@Proof era
Conway TxSeq era
x TxSeq era
y = forall era.
(Reflect era, AlonzoEraTx era, SafeToHash (TxWits era)) =>
Proof era
-> AlonzoTxSeq era -> AlonzoTxSeq era -> [(String, Maybe PDoc)]
sameAlonzoTxSeq Proof era
proof TxSeq era
x TxSeq era
y
{-# NOINLINE sameTxSeq #-}