-- editorconfig-checker-disable-file
{-# LANGUAGE DeriveAnyClass    #-}
{-# LANGUAGE DerivingVia       #-}
{-# LANGUAGE NamedFieldPuns    #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE ViewPatterns      #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -fno-strictness #-}

module PlutusLedgerApi.V3.Data.Contexts
  ( ColdCommitteeCredential (..)
  , HotCommitteeCredential (..)
  , DRepCredential (..)
  , DRep (..)
  , Delegatee (..)
  , TxCert (..)
  , Voter (..)
  , Vote (..)
  , GovernanceActionId (..)
  , Committee (..)
  , Constitution (..)
  , ProtocolVersion (..)
  , ChangedParameters (..)
  , GovernanceAction (..)
  , ProposalProcedure (..)
  , ScriptPurpose (..)
  , ScriptInfo (..)
  , TxInInfo (..)
  , TxInfo (..)
  , ScriptContext (..)
  , findOwnInput
  , findDatum
  , findDatumHash
  , findTxInByTxOutRef
  , findContinuingOutputs
  , getContinuingOutputs
  , txSignedBy

    -- * Validator functions
  , pubKeyOutputsAt
  , valuePaidTo
  , valueSpent
  , valueProduced
  , ownCurrencySymbol
  , spendsOutput
  ) where

import GHC.Generics (Generic)
import Prettyprinter (nest, vsep, (<+>))
import Prettyprinter.Extras

import PlutusLedgerApi.Data.V2 qualified as V2
import PlutusLedgerApi.V3.Tx qualified as V3
import PlutusTx qualified
import PlutusTx.Data.AssocMap
import PlutusTx.Prelude qualified as PlutusTx
import PlutusTx.Ratio (Rational)

import Prelude qualified as Haskell

newtype ColdCommitteeCredential = ColdCommitteeCredential V2.Credential
  deriving stock ((forall x.
 ColdCommitteeCredential -> Rep ColdCommitteeCredential x)
-> (forall x.
    Rep ColdCommitteeCredential x -> ColdCommitteeCredential)
-> Generic ColdCommitteeCredential
forall x. Rep ColdCommitteeCredential x -> ColdCommitteeCredential
forall x. ColdCommitteeCredential -> Rep ColdCommitteeCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColdCommitteeCredential -> Rep ColdCommitteeCredential x
from :: forall x. ColdCommitteeCredential -> Rep ColdCommitteeCredential x
$cto :: forall x. Rep ColdCommitteeCredential x -> ColdCommitteeCredential
to :: forall x. Rep ColdCommitteeCredential x -> ColdCommitteeCredential
Generic)
  deriving ((forall ann. ColdCommitteeCredential -> Doc ann)
-> (forall ann. [ColdCommitteeCredential] -> Doc ann)
-> Pretty ColdCommitteeCredential
forall ann. [ColdCommitteeCredential] -> Doc ann
forall ann. ColdCommitteeCredential -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. ColdCommitteeCredential -> Doc ann
pretty :: forall ann. ColdCommitteeCredential -> Doc ann
$cprettyList :: forall ann. [ColdCommitteeCredential] -> Doc ann
prettyList :: forall ann. [ColdCommitteeCredential] -> Doc ann
Pretty) via (PrettyShow ColdCommitteeCredential)
  deriving newtype
    ( ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
(ColdCommitteeCredential -> ColdCommitteeCredential -> Bool)
-> (ColdCommitteeCredential -> ColdCommitteeCredential -> Bool)
-> Eq ColdCommitteeCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
$c/= :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
/= :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
Haskell.Eq
    , Int -> ColdCommitteeCredential -> ShowS
[ColdCommitteeCredential] -> ShowS
ColdCommitteeCredential -> String
(Int -> ColdCommitteeCredential -> ShowS)
-> (ColdCommitteeCredential -> String)
-> ([ColdCommitteeCredential] -> ShowS)
-> Show ColdCommitteeCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColdCommitteeCredential -> ShowS
showsPrec :: Int -> ColdCommitteeCredential -> ShowS
$cshow :: ColdCommitteeCredential -> String
show :: ColdCommitteeCredential -> String
$cshowList :: [ColdCommitteeCredential] -> ShowS
showList :: [ColdCommitteeCredential] -> ShowS
Haskell.Show
    , ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
(ColdCommitteeCredential -> ColdCommitteeCredential -> Bool)
-> Eq ColdCommitteeCredential
forall a. (a -> a -> Bool) -> Eq a
$c== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
PlutusTx.Eq
    , ColdCommitteeCredential -> BuiltinData
(ColdCommitteeCredential -> BuiltinData)
-> ToData ColdCommitteeCredential
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: ColdCommitteeCredential -> BuiltinData
toBuiltinData :: ColdCommitteeCredential -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe ColdCommitteeCredential
(BuiltinData -> Maybe ColdCommitteeCredential)
-> FromData ColdCommitteeCredential
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe ColdCommitteeCredential
fromBuiltinData :: BuiltinData -> Maybe ColdCommitteeCredential
PlutusTx.FromData
    , BuiltinData -> ColdCommitteeCredential
(BuiltinData -> ColdCommitteeCredential)
-> UnsafeFromData ColdCommitteeCredential
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> ColdCommitteeCredential
unsafeFromBuiltinData :: BuiltinData -> ColdCommitteeCredential
PlutusTx.UnsafeFromData
    )

newtype HotCommitteeCredential = HotCommitteeCredential V2.Credential
  deriving stock ((forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x)
-> (forall x.
    Rep HotCommitteeCredential x -> HotCommitteeCredential)
-> Generic HotCommitteeCredential
forall x. Rep HotCommitteeCredential x -> HotCommitteeCredential
forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x
from :: forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x
$cto :: forall x. Rep HotCommitteeCredential x -> HotCommitteeCredential
to :: forall x. Rep HotCommitteeCredential x -> HotCommitteeCredential
Generic)
  deriving ((forall ann. HotCommitteeCredential -> Doc ann)
-> (forall ann. [HotCommitteeCredential] -> Doc ann)
-> Pretty HotCommitteeCredential
forall ann. [HotCommitteeCredential] -> Doc ann
forall ann. HotCommitteeCredential -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. HotCommitteeCredential -> Doc ann
pretty :: forall ann. HotCommitteeCredential -> Doc ann
$cprettyList :: forall ann. [HotCommitteeCredential] -> Doc ann
prettyList :: forall ann. [HotCommitteeCredential] -> Doc ann
Pretty) via (PrettyShow HotCommitteeCredential)
  deriving newtype
    ( HotCommitteeCredential -> HotCommitteeCredential -> Bool
(HotCommitteeCredential -> HotCommitteeCredential -> Bool)
-> (HotCommitteeCredential -> HotCommitteeCredential -> Bool)
-> Eq HotCommitteeCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
$c/= :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
/= :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
Haskell.Eq
    , Int -> HotCommitteeCredential -> ShowS
[HotCommitteeCredential] -> ShowS
HotCommitteeCredential -> String
(Int -> HotCommitteeCredential -> ShowS)
-> (HotCommitteeCredential -> String)
-> ([HotCommitteeCredential] -> ShowS)
-> Show HotCommitteeCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HotCommitteeCredential -> ShowS
showsPrec :: Int -> HotCommitteeCredential -> ShowS
$cshow :: HotCommitteeCredential -> String
show :: HotCommitteeCredential -> String
$cshowList :: [HotCommitteeCredential] -> ShowS
showList :: [HotCommitteeCredential] -> ShowS
Haskell.Show
    , HotCommitteeCredential -> HotCommitteeCredential -> Bool
(HotCommitteeCredential -> HotCommitteeCredential -> Bool)
-> Eq HotCommitteeCredential
forall a. (a -> a -> Bool) -> Eq a
$c== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
PlutusTx.Eq
    , HotCommitteeCredential -> BuiltinData
(HotCommitteeCredential -> BuiltinData)
-> ToData HotCommitteeCredential
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: HotCommitteeCredential -> BuiltinData
toBuiltinData :: HotCommitteeCredential -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe HotCommitteeCredential
(BuiltinData -> Maybe HotCommitteeCredential)
-> FromData HotCommitteeCredential
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe HotCommitteeCredential
fromBuiltinData :: BuiltinData -> Maybe HotCommitteeCredential
PlutusTx.FromData
    , BuiltinData -> HotCommitteeCredential
(BuiltinData -> HotCommitteeCredential)
-> UnsafeFromData HotCommitteeCredential
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> HotCommitteeCredential
unsafeFromBuiltinData :: BuiltinData -> HotCommitteeCredential
PlutusTx.UnsafeFromData
    )

newtype DRepCredential = DRepCredential V2.Credential
  deriving stock ((forall x. DRepCredential -> Rep DRepCredential x)
-> (forall x. Rep DRepCredential x -> DRepCredential)
-> Generic DRepCredential
forall x. Rep DRepCredential x -> DRepCredential
forall x. DRepCredential -> Rep DRepCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DRepCredential -> Rep DRepCredential x
from :: forall x. DRepCredential -> Rep DRepCredential x
$cto :: forall x. Rep DRepCredential x -> DRepCredential
to :: forall x. Rep DRepCredential x -> DRepCredential
Generic)
  deriving ((forall ann. DRepCredential -> Doc ann)
-> (forall ann. [DRepCredential] -> Doc ann)
-> Pretty DRepCredential
forall ann. [DRepCredential] -> Doc ann
forall ann. DRepCredential -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. DRepCredential -> Doc ann
pretty :: forall ann. DRepCredential -> Doc ann
$cprettyList :: forall ann. [DRepCredential] -> Doc ann
prettyList :: forall ann. [DRepCredential] -> Doc ann
Pretty) via (PrettyShow DRepCredential)
  deriving newtype
    ( DRepCredential -> DRepCredential -> Bool
(DRepCredential -> DRepCredential -> Bool)
-> (DRepCredential -> DRepCredential -> Bool) -> Eq DRepCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRepCredential -> DRepCredential -> Bool
== :: DRepCredential -> DRepCredential -> Bool
$c/= :: DRepCredential -> DRepCredential -> Bool
/= :: DRepCredential -> DRepCredential -> Bool
Haskell.Eq
    , Int -> DRepCredential -> ShowS
[DRepCredential] -> ShowS
DRepCredential -> String
(Int -> DRepCredential -> ShowS)
-> (DRepCredential -> String)
-> ([DRepCredential] -> ShowS)
-> Show DRepCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepCredential -> ShowS
showsPrec :: Int -> DRepCredential -> ShowS
$cshow :: DRepCredential -> String
show :: DRepCredential -> String
$cshowList :: [DRepCredential] -> ShowS
showList :: [DRepCredential] -> ShowS
Haskell.Show
    , DRepCredential -> DRepCredential -> Bool
(DRepCredential -> DRepCredential -> Bool) -> Eq DRepCredential
forall a. (a -> a -> Bool) -> Eq a
$c== :: DRepCredential -> DRepCredential -> Bool
== :: DRepCredential -> DRepCredential -> Bool
PlutusTx.Eq
    , DRepCredential -> BuiltinData
(DRepCredential -> BuiltinData) -> ToData DRepCredential
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: DRepCredential -> BuiltinData
toBuiltinData :: DRepCredential -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe DRepCredential
(BuiltinData -> Maybe DRepCredential) -> FromData DRepCredential
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe DRepCredential
fromBuiltinData :: BuiltinData -> Maybe DRepCredential
PlutusTx.FromData
    , BuiltinData -> DRepCredential
(BuiltinData -> DRepCredential) -> UnsafeFromData DRepCredential
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> DRepCredential
unsafeFromBuiltinData :: BuiltinData -> DRepCredential
PlutusTx.UnsafeFromData
    )

data DRep
  = DRep DRepCredential
  | DRepAlwaysAbstain
  | DRepAlwaysNoConfidence
  deriving stock ((forall x. DRep -> Rep DRep x)
-> (forall x. Rep DRep x -> DRep) -> Generic DRep
forall x. Rep DRep x -> DRep
forall x. DRep -> Rep DRep x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DRep -> Rep DRep x
from :: forall x. DRep -> Rep DRep x
$cto :: forall x. Rep DRep x -> DRep
to :: forall x. Rep DRep x -> DRep
Generic, Int -> DRep -> ShowS
[DRep] -> ShowS
DRep -> String
(Int -> DRep -> ShowS)
-> (DRep -> String) -> ([DRep] -> ShowS) -> Show DRep
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRep -> ShowS
showsPrec :: Int -> DRep -> ShowS
$cshow :: DRep -> String
show :: DRep -> String
$cshowList :: [DRep] -> ShowS
showList :: [DRep] -> ShowS
Haskell.Show, DRep -> DRep -> Bool
(DRep -> DRep -> Bool) -> (DRep -> DRep -> Bool) -> Eq DRep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRep -> DRep -> Bool
== :: DRep -> DRep -> Bool
$c/= :: DRep -> DRep -> Bool
/= :: DRep -> DRep -> Bool
Haskell.Eq)
  deriving ((forall ann. DRep -> Doc ann)
-> (forall ann. [DRep] -> Doc ann) -> Pretty DRep
forall ann. [DRep] -> Doc ann
forall ann. DRep -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. DRep -> Doc ann
pretty :: forall ann. DRep -> Doc ann
$cprettyList :: forall ann. [DRep] -> Doc ann
prettyList :: forall ann. [DRep] -> Doc ann
Pretty) via (PrettyShow DRep)

instance PlutusTx.Eq DRep where
  {-# INLINEABLE (==) #-}
  DRep DRepCredential
a == :: DRep -> DRep -> Bool
== DRep DRepCredential
a'                                = DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a'
  DRep
DRepAlwaysAbstain == DRep
DRepAlwaysAbstain           = Bool
Haskell.True
  DRep
DRepAlwaysNoConfidence == DRep
DRepAlwaysNoConfidence = Bool
Haskell.True
  DRep
_ == DRep
_                                           = Bool
Haskell.False

data Delegatee
  = DelegStake V2.PubKeyHash
  | DelegVote DRep
  | DelegStakeVote V2.PubKeyHash DRep
  deriving stock ((forall x. Delegatee -> Rep Delegatee x)
-> (forall x. Rep Delegatee x -> Delegatee) -> Generic Delegatee
forall x. Rep Delegatee x -> Delegatee
forall x. Delegatee -> Rep Delegatee x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Delegatee -> Rep Delegatee x
from :: forall x. Delegatee -> Rep Delegatee x
$cto :: forall x. Rep Delegatee x -> Delegatee
to :: forall x. Rep Delegatee x -> Delegatee
Generic, Int -> Delegatee -> ShowS
[Delegatee] -> ShowS
Delegatee -> String
(Int -> Delegatee -> ShowS)
-> (Delegatee -> String)
-> ([Delegatee] -> ShowS)
-> Show Delegatee
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Delegatee -> ShowS
showsPrec :: Int -> Delegatee -> ShowS
$cshow :: Delegatee -> String
show :: Delegatee -> String
$cshowList :: [Delegatee] -> ShowS
showList :: [Delegatee] -> ShowS
Haskell.Show, Delegatee -> Delegatee -> Bool
(Delegatee -> Delegatee -> Bool)
-> (Delegatee -> Delegatee -> Bool) -> Eq Delegatee
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Delegatee -> Delegatee -> Bool
== :: Delegatee -> Delegatee -> Bool
$c/= :: Delegatee -> Delegatee -> Bool
/= :: Delegatee -> Delegatee -> Bool
Haskell.Eq)
  deriving ((forall ann. Delegatee -> Doc ann)
-> (forall ann. [Delegatee] -> Doc ann) -> Pretty Delegatee
forall ann. [Delegatee] -> Doc ann
forall ann. Delegatee -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Delegatee -> Doc ann
pretty :: forall ann. Delegatee -> Doc ann
$cprettyList :: forall ann. [Delegatee] -> Doc ann
prettyList :: forall ann. [Delegatee] -> Doc ann
Pretty) via (PrettyShow Delegatee)

instance PlutusTx.Eq Delegatee where
  {-# INLINEABLE (==) #-}
  DelegStake PubKeyHash
a == :: Delegatee -> Delegatee -> Bool
== DelegStake PubKeyHash
a' = PubKeyHash
a PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
a'
  DelegVote DRep
a == DelegVote DRep
a' = DRep
a DRep -> DRep -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRep
a'
  DelegStakeVote PubKeyHash
a DRep
b == DelegStakeVote PubKeyHash
a' DRep
b' =
    PubKeyHash
a PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
a' Bool -> Bool -> Bool
PlutusTx.&& DRep
b DRep -> DRep -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRep
b'
  Delegatee
_ == Delegatee
_ = Bool
Haskell.False

data TxCert
  = -- | Register staking credential with an optional deposit amount
    TxCertRegStaking V2.Credential (Haskell.Maybe V2.Lovelace)
  | -- | Un-Register staking credential with an optional refund amount
    TxCertUnRegStaking V2.Credential (Haskell.Maybe V2.Lovelace)
  | -- | Delegate staking credential to a Delegatee
    TxCertDelegStaking V2.Credential Delegatee
  | -- | Register and delegate staking credential to a Delegatee in one certificate. Noter that
    -- deposit is mandatory.
    TxCertRegDeleg V2.Credential Delegatee V2.Lovelace
  | -- | Register a DRep with a deposit value. The optional anchor is omitted.
    TxCertRegDRep DRepCredential V2.Lovelace
  | -- | Update a DRep. The optional anchor is omitted.
    TxCertUpdateDRep DRepCredential
  | -- | UnRegister a DRep with mandatory refund value
    TxCertUnRegDRep DRepCredential V2.Lovelace
  | -- | A digest of the PoolParams
    TxCertPoolRegister
      V2.PubKeyHash
      -- ^ poolId
      V2.PubKeyHash
      -- ^ pool VFR
  | -- | The retirement certificate and the Epoch in which the retirement will take place
    TxCertPoolRetire V2.PubKeyHash Haskell.Integer
  | -- | Authorize a Hot credential for a specific Committee member's cold credential
    TxCertAuthHotCommittee ColdCommitteeCredential HotCommitteeCredential
  | TxCertResignColdCommittee ColdCommitteeCredential
  deriving stock ((forall x. TxCert -> Rep TxCert x)
-> (forall x. Rep TxCert x -> TxCert) -> Generic TxCert
forall x. Rep TxCert x -> TxCert
forall x. TxCert -> Rep TxCert x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TxCert -> Rep TxCert x
from :: forall x. TxCert -> Rep TxCert x
$cto :: forall x. Rep TxCert x -> TxCert
to :: forall x. Rep TxCert x -> TxCert
Generic, Int -> TxCert -> ShowS
[TxCert] -> ShowS
TxCert -> String
(Int -> TxCert -> ShowS)
-> (TxCert -> String) -> ([TxCert] -> ShowS) -> Show TxCert
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxCert -> ShowS
showsPrec :: Int -> TxCert -> ShowS
$cshow :: TxCert -> String
show :: TxCert -> String
$cshowList :: [TxCert] -> ShowS
showList :: [TxCert] -> ShowS
Haskell.Show, TxCert -> TxCert -> Bool
(TxCert -> TxCert -> Bool)
-> (TxCert -> TxCert -> Bool) -> Eq TxCert
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxCert -> TxCert -> Bool
== :: TxCert -> TxCert -> Bool
$c/= :: TxCert -> TxCert -> Bool
/= :: TxCert -> TxCert -> Bool
Haskell.Eq)
  deriving ((forall ann. TxCert -> Doc ann)
-> (forall ann. [TxCert] -> Doc ann) -> Pretty TxCert
forall ann. [TxCert] -> Doc ann
forall ann. TxCert -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. TxCert -> Doc ann
pretty :: forall ann. TxCert -> Doc ann
$cprettyList :: forall ann. [TxCert] -> Doc ann
prettyList :: forall ann. [TxCert] -> Doc ann
Pretty) via (PrettyShow TxCert)

instance PlutusTx.Eq TxCert where
  {-# INLINEABLE (==) #-}
  TxCertRegStaking Credential
a Maybe Lovelace
b == :: TxCert -> TxCert -> Bool
== TxCertRegStaking Credential
a' Maybe Lovelace
b' =
    Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Maybe Lovelace
b Maybe Lovelace -> Maybe Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe Lovelace
b'
  TxCertUnRegStaking Credential
a Maybe Lovelace
b == TxCertUnRegStaking Credential
a' Maybe Lovelace
b' =
    Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Maybe Lovelace
b Maybe Lovelace -> Maybe Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe Lovelace
b'
  TxCertDelegStaking Credential
a Delegatee
b == TxCertDelegStaking Credential
a' Delegatee
b' =
    Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Delegatee
b Delegatee -> Delegatee -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Delegatee
b'
  TxCertRegDeleg Credential
a Delegatee
b Lovelace
c == TxCertRegDeleg Credential
a' Delegatee
b' Lovelace
c' =
    Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Delegatee
b Delegatee -> Delegatee -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Delegatee
b' Bool -> Bool -> Bool
PlutusTx.&& Lovelace
c Lovelace -> Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Lovelace
c'
  TxCertRegDRep DRepCredential
a Lovelace
b == TxCertRegDRep DRepCredential
a' Lovelace
b' =
    DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a' Bool -> Bool -> Bool
PlutusTx.&& Lovelace
b Lovelace -> Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Lovelace
b'
  TxCertUpdateDRep DRepCredential
a == TxCertUpdateDRep DRepCredential
a' =
    DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a'
  TxCertUnRegDRep DRepCredential
a Lovelace
b == TxCertUnRegDRep DRepCredential
a' Lovelace
b' =
    DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a' Bool -> Bool -> Bool
PlutusTx.&& Lovelace
b Lovelace -> Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Lovelace
b'
  TxCertAuthHotCommittee ColdCommitteeCredential
a HotCommitteeCredential
b == TxCertAuthHotCommittee ColdCommitteeCredential
a' HotCommitteeCredential
b' =
    ColdCommitteeCredential
a ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== ColdCommitteeCredential
a' Bool -> Bool -> Bool
PlutusTx.&& HotCommitteeCredential
b HotCommitteeCredential -> HotCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== HotCommitteeCredential
b'
  TxCertResignColdCommittee ColdCommitteeCredential
a == TxCertResignColdCommittee ColdCommitteeCredential
a' =
    ColdCommitteeCredential
a ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== ColdCommitteeCredential
a'
  TxCert
_ == TxCert
_ = Bool
Haskell.False

data Voter
  = CommitteeVoter HotCommitteeCredential
  | DRepVoter DRepCredential
  | StakePoolVoter V2.PubKeyHash
  deriving stock ((forall x. Voter -> Rep Voter x)
-> (forall x. Rep Voter x -> Voter) -> Generic Voter
forall x. Rep Voter x -> Voter
forall x. Voter -> Rep Voter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Voter -> Rep Voter x
from :: forall x. Voter -> Rep Voter x
$cto :: forall x. Rep Voter x -> Voter
to :: forall x. Rep Voter x -> Voter
Generic, Int -> Voter -> ShowS
[Voter] -> ShowS
Voter -> String
(Int -> Voter -> ShowS)
-> (Voter -> String) -> ([Voter] -> ShowS) -> Show Voter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Voter -> ShowS
showsPrec :: Int -> Voter -> ShowS
$cshow :: Voter -> String
show :: Voter -> String
$cshowList :: [Voter] -> ShowS
showList :: [Voter] -> ShowS
Haskell.Show, Voter -> Voter -> Bool
(Voter -> Voter -> Bool) -> (Voter -> Voter -> Bool) -> Eq Voter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Voter -> Voter -> Bool
== :: Voter -> Voter -> Bool
$c/= :: Voter -> Voter -> Bool
/= :: Voter -> Voter -> Bool
Haskell.Eq)
  deriving ((forall ann. Voter -> Doc ann)
-> (forall ann. [Voter] -> Doc ann) -> Pretty Voter
forall ann. [Voter] -> Doc ann
forall ann. Voter -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Voter -> Doc ann
pretty :: forall ann. Voter -> Doc ann
$cprettyList :: forall ann. [Voter] -> Doc ann
prettyList :: forall ann. [Voter] -> Doc ann
Pretty) via (PrettyShow Voter)

instance PlutusTx.Eq Voter where
  {-# INLINEABLE (==) #-}
  CommitteeVoter HotCommitteeCredential
a == :: Voter -> Voter -> Bool
== CommitteeVoter HotCommitteeCredential
a' =
    HotCommitteeCredential
a HotCommitteeCredential -> HotCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== HotCommitteeCredential
a'
  DRepVoter DRepCredential
a == DRepVoter DRepCredential
a' =
    DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a'
  StakePoolVoter PubKeyHash
a == StakePoolVoter PubKeyHash
a' =
    PubKeyHash
a PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
a'
  Voter
_ == Voter
_ = Bool
Haskell.False

-- | A vote. The optional anchor is omitted.
data Vote
  = VoteNo
  | VoteYes
  | Abstain
  deriving stock ((forall x. Vote -> Rep Vote x)
-> (forall x. Rep Vote x -> Vote) -> Generic Vote
forall x. Rep Vote x -> Vote
forall x. Vote -> Rep Vote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Vote -> Rep Vote x
from :: forall x. Vote -> Rep Vote x
$cto :: forall x. Rep Vote x -> Vote
to :: forall x. Rep Vote x -> Vote
Generic, Int -> Vote -> ShowS
[Vote] -> ShowS
Vote -> String
(Int -> Vote -> ShowS)
-> (Vote -> String) -> ([Vote] -> ShowS) -> Show Vote
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Vote -> ShowS
showsPrec :: Int -> Vote -> ShowS
$cshow :: Vote -> String
show :: Vote -> String
$cshowList :: [Vote] -> ShowS
showList :: [Vote] -> ShowS
Haskell.Show, Vote -> Vote -> Bool
(Vote -> Vote -> Bool) -> (Vote -> Vote -> Bool) -> Eq Vote
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Vote -> Vote -> Bool
== :: Vote -> Vote -> Bool
$c/= :: Vote -> Vote -> Bool
/= :: Vote -> Vote -> Bool
Haskell.Eq)
  deriving ((forall ann. Vote -> Doc ann)
-> (forall ann. [Vote] -> Doc ann) -> Pretty Vote
forall ann. [Vote] -> Doc ann
forall ann. Vote -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. Vote -> Doc ann
pretty :: forall ann. Vote -> Doc ann
$cprettyList :: forall ann. [Vote] -> Doc ann
prettyList :: forall ann. [Vote] -> Doc ann
Pretty) via (PrettyShow Vote)

instance PlutusTx.Eq Vote where
  {-# INLINEABLE (==) #-}
  Vote
VoteNo == :: Vote -> Vote -> Bool
== Vote
VoteNo   = Bool
Haskell.True
  Vote
VoteYes == Vote
VoteYes = Bool
Haskell.True
  Vote
Abstain == Vote
Abstain = Bool
Haskell.True
  Vote
_ == Vote
_             = Bool
Haskell.False

-- | Similar to TxOutRef, but for GovActions
data GovernanceActionId = GovernanceActionId
  { GovernanceActionId -> TxId
gaidTxId        :: V3.TxId
  , GovernanceActionId -> Integer
gaidGovActionIx :: Haskell.Integer
  }
  deriving stock ((forall x. GovernanceActionId -> Rep GovernanceActionId x)
-> (forall x. Rep GovernanceActionId x -> GovernanceActionId)
-> Generic GovernanceActionId
forall x. Rep GovernanceActionId x -> GovernanceActionId
forall x. GovernanceActionId -> Rep GovernanceActionId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GovernanceActionId -> Rep GovernanceActionId x
from :: forall x. GovernanceActionId -> Rep GovernanceActionId x
$cto :: forall x. Rep GovernanceActionId x -> GovernanceActionId
to :: forall x. Rep GovernanceActionId x -> GovernanceActionId
Generic, Int -> GovernanceActionId -> ShowS
[GovernanceActionId] -> ShowS
GovernanceActionId -> String
(Int -> GovernanceActionId -> ShowS)
-> (GovernanceActionId -> String)
-> ([GovernanceActionId] -> ShowS)
-> Show GovernanceActionId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GovernanceActionId -> ShowS
showsPrec :: Int -> GovernanceActionId -> ShowS
$cshow :: GovernanceActionId -> String
show :: GovernanceActionId -> String
$cshowList :: [GovernanceActionId] -> ShowS
showList :: [GovernanceActionId] -> ShowS
Haskell.Show, GovernanceActionId -> GovernanceActionId -> Bool
(GovernanceActionId -> GovernanceActionId -> Bool)
-> (GovernanceActionId -> GovernanceActionId -> Bool)
-> Eq GovernanceActionId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GovernanceActionId -> GovernanceActionId -> Bool
== :: GovernanceActionId -> GovernanceActionId -> Bool
$c/= :: GovernanceActionId -> GovernanceActionId -> Bool
/= :: GovernanceActionId -> GovernanceActionId -> Bool
Haskell.Eq)

instance Pretty GovernanceActionId where
  pretty :: forall ann. GovernanceActionId -> Doc ann
pretty GovernanceActionId{Integer
TxId
gaidTxId :: GovernanceActionId -> TxId
gaidGovActionIx :: GovernanceActionId -> Integer
gaidTxId :: TxId
gaidGovActionIx :: Integer
..} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"gaidTxId:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxId -> Doc ann
pretty TxId
gaidTxId
      , Doc ann
"gaidGovActionIx:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
gaidGovActionIx
      ]

instance PlutusTx.Eq GovernanceActionId where
  {-# INLINEABLE (==) #-}
  GovernanceActionId TxId
a Integer
b == :: GovernanceActionId -> GovernanceActionId -> Bool
== GovernanceActionId TxId
a' Integer
b' =
    TxId
a TxId -> TxId -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxId
a' Bool -> Bool -> Bool
PlutusTx.&& Integer
b Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Integer
b'

data Committee = Committee
  { Committee -> Map ColdCommitteeCredential Integer
committeeMembers :: Map ColdCommitteeCredential Haskell.Integer
  -- ^ Committee members with epoch number when each of them expires
  , Committee -> Rational
committeeQuorum  :: PlutusTx.Rational
  -- ^ Quorum of the committee that is necessary for a successful vote
  }
  deriving stock ((forall x. Committee -> Rep Committee x)
-> (forall x. Rep Committee x -> Committee) -> Generic Committee
forall x. Rep Committee x -> Committee
forall x. Committee -> Rep Committee x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Committee -> Rep Committee x
from :: forall x. Committee -> Rep Committee x
$cto :: forall x. Rep Committee x -> Committee
to :: forall x. Rep Committee x -> Committee
Generic, Int -> Committee -> ShowS
[Committee] -> ShowS
Committee -> String
(Int -> Committee -> ShowS)
-> (Committee -> String)
-> ([Committee] -> ShowS)
-> Show Committee
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Committee -> ShowS
showsPrec :: Int -> Committee -> ShowS
$cshow :: Committee -> String
show :: Committee -> String
$cshowList :: [Committee] -> ShowS
showList :: [Committee] -> ShowS
Haskell.Show)

instance Pretty Committee where
  pretty :: forall ann. Committee -> Doc ann
pretty Committee{Rational
Map ColdCommitteeCredential Integer
committeeMembers :: Committee -> Map ColdCommitteeCredential Integer
committeeQuorum :: Committee -> Rational
committeeMembers :: Map ColdCommitteeCredential Integer
committeeQuorum :: Rational
..} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"committeeMembers:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map ColdCommitteeCredential Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map ColdCommitteeCredential Integer -> Doc ann
pretty Map ColdCommitteeCredential Integer
committeeMembers
      , Doc ann
"committeeQuorum:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Rational -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Rational -> Doc ann
pretty Rational
committeeQuorum
      ]

-- | A constitution. The optional anchor is omitted.
newtype Constitution = Constitution
  { Constitution -> Maybe ScriptHash
constitutionScript :: Haskell.Maybe V2.ScriptHash
  }
  deriving stock ((forall x. Constitution -> Rep Constitution x)
-> (forall x. Rep Constitution x -> Constitution)
-> Generic Constitution
forall x. Rep Constitution x -> Constitution
forall x. Constitution -> Rep Constitution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Constitution -> Rep Constitution x
from :: forall x. Constitution -> Rep Constitution x
$cto :: forall x. Rep Constitution x -> Constitution
to :: forall x. Rep Constitution x -> Constitution
Generic)
  deriving newtype (Int -> Constitution -> ShowS
[Constitution] -> ShowS
Constitution -> String
(Int -> Constitution -> ShowS)
-> (Constitution -> String)
-> ([Constitution] -> ShowS)
-> Show Constitution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constitution -> ShowS
showsPrec :: Int -> Constitution -> ShowS
$cshow :: Constitution -> String
show :: Constitution -> String
$cshowList :: [Constitution] -> ShowS
showList :: [Constitution] -> ShowS
Haskell.Show, Constitution -> Constitution -> Bool
(Constitution -> Constitution -> Bool)
-> (Constitution -> Constitution -> Bool) -> Eq Constitution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constitution -> Constitution -> Bool
== :: Constitution -> Constitution -> Bool
$c/= :: Constitution -> Constitution -> Bool
/= :: Constitution -> Constitution -> Bool
Haskell.Eq)

instance Pretty Constitution where
  pretty :: forall ann. Constitution -> Doc ann
pretty (Constitution Maybe ScriptHash
script) = Doc ann
"constitutionScript:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe ScriptHash -> Doc ann
forall ann. Maybe ScriptHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe ScriptHash
script

instance PlutusTx.Eq Constitution where
  {-# INLINEABLE (==) #-}
  Constitution Maybe ScriptHash
a == :: Constitution -> Constitution -> Bool
== Constitution Maybe ScriptHash
a' = Maybe ScriptHash
a Maybe ScriptHash -> Maybe ScriptHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe ScriptHash
a'

data ProtocolVersion = ProtocolVersion
  { ProtocolVersion -> Integer
pvMajor :: Haskell.Integer
  , ProtocolVersion -> Integer
pvMinor :: Haskell.Integer
  }
  deriving stock ((forall x. ProtocolVersion -> Rep ProtocolVersion x)
-> (forall x. Rep ProtocolVersion x -> ProtocolVersion)
-> Generic ProtocolVersion
forall x. Rep ProtocolVersion x -> ProtocolVersion
forall x. ProtocolVersion -> Rep ProtocolVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProtocolVersion -> Rep ProtocolVersion x
from :: forall x. ProtocolVersion -> Rep ProtocolVersion x
$cto :: forall x. Rep ProtocolVersion x -> ProtocolVersion
to :: forall x. Rep ProtocolVersion x -> ProtocolVersion
Generic, Int -> ProtocolVersion -> ShowS
[ProtocolVersion] -> ShowS
ProtocolVersion -> String
(Int -> ProtocolVersion -> ShowS)
-> (ProtocolVersion -> String)
-> ([ProtocolVersion] -> ShowS)
-> Show ProtocolVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProtocolVersion -> ShowS
showsPrec :: Int -> ProtocolVersion -> ShowS
$cshow :: ProtocolVersion -> String
show :: ProtocolVersion -> String
$cshowList :: [ProtocolVersion] -> ShowS
showList :: [ProtocolVersion] -> ShowS
Haskell.Show, ProtocolVersion -> ProtocolVersion -> Bool
(ProtocolVersion -> ProtocolVersion -> Bool)
-> (ProtocolVersion -> ProtocolVersion -> Bool)
-> Eq ProtocolVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProtocolVersion -> ProtocolVersion -> Bool
== :: ProtocolVersion -> ProtocolVersion -> Bool
$c/= :: ProtocolVersion -> ProtocolVersion -> Bool
/= :: ProtocolVersion -> ProtocolVersion -> Bool
Haskell.Eq)

instance Pretty ProtocolVersion where
  pretty :: forall ann. ProtocolVersion -> Doc ann
pretty ProtocolVersion{Integer
pvMajor :: ProtocolVersion -> Integer
pvMinor :: ProtocolVersion -> Integer
pvMajor :: Integer
pvMinor :: Integer
..} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"pvMajor:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
pvMajor
      , Doc ann
"pvMinor:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
pvMinor
      ]

instance PlutusTx.Eq ProtocolVersion where
  {-# INLINEABLE (==) #-}
  ProtocolVersion Integer
a Integer
b == :: ProtocolVersion -> ProtocolVersion -> Bool
== ProtocolVersion Integer
a' Integer
b' =
    Integer
a Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Integer
a' Bool -> Bool -> Bool
PlutusTx.&& Integer
b Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Integer
b'

{- | A Plutus Data object containing proposed parameter changes. The Data object contains
a @Map@ with one entry per changed parameter, from the parameter ID to the new value.
Unchanged parameters are not included.

The mapping from parameter IDs to parameters can be found in
[conway.cddl](https://github.com/IntersectMBO/cardano-ledger/blob/master/eras/conway/impl/cddl-files/conway.cddl).

/Invariant:/ This map is non-empty, and the keys are stored in ascending order.
-}
newtype ChangedParameters = ChangedParameters {ChangedParameters -> BuiltinData
getChangedParameters :: PlutusTx.BuiltinData}
  deriving stock ((forall x. ChangedParameters -> Rep ChangedParameters x)
-> (forall x. Rep ChangedParameters x -> ChangedParameters)
-> Generic ChangedParameters
forall x. Rep ChangedParameters x -> ChangedParameters
forall x. ChangedParameters -> Rep ChangedParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChangedParameters -> Rep ChangedParameters x
from :: forall x. ChangedParameters -> Rep ChangedParameters x
$cto :: forall x. Rep ChangedParameters x -> ChangedParameters
to :: forall x. Rep ChangedParameters x -> ChangedParameters
Generic, Int -> ChangedParameters -> ShowS
[ChangedParameters] -> ShowS
ChangedParameters -> String
(Int -> ChangedParameters -> ShowS)
-> (ChangedParameters -> String)
-> ([ChangedParameters] -> ShowS)
-> Show ChangedParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChangedParameters -> ShowS
showsPrec :: Int -> ChangedParameters -> ShowS
$cshow :: ChangedParameters -> String
show :: ChangedParameters -> String
$cshowList :: [ChangedParameters] -> ShowS
showList :: [ChangedParameters] -> ShowS
Haskell.Show)
  deriving newtype
    ( ChangedParameters -> ChangedParameters -> Bool
(ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> Eq ChangedParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChangedParameters -> ChangedParameters -> Bool
== :: ChangedParameters -> ChangedParameters -> Bool
$c/= :: ChangedParameters -> ChangedParameters -> Bool
/= :: ChangedParameters -> ChangedParameters -> Bool
Haskell.Eq
    , Eq ChangedParameters
Eq ChangedParameters =>
(ChangedParameters -> ChangedParameters -> Ordering)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> ChangedParameters)
-> (ChangedParameters -> ChangedParameters -> ChangedParameters)
-> Ord ChangedParameters
ChangedParameters -> ChangedParameters -> Bool
ChangedParameters -> ChangedParameters -> Ordering
ChangedParameters -> ChangedParameters -> ChangedParameters
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ChangedParameters -> ChangedParameters -> Ordering
compare :: ChangedParameters -> ChangedParameters -> Ordering
$c< :: ChangedParameters -> ChangedParameters -> Bool
< :: ChangedParameters -> ChangedParameters -> Bool
$c<= :: ChangedParameters -> ChangedParameters -> Bool
<= :: ChangedParameters -> ChangedParameters -> Bool
$c> :: ChangedParameters -> ChangedParameters -> Bool
> :: ChangedParameters -> ChangedParameters -> Bool
$c>= :: ChangedParameters -> ChangedParameters -> Bool
>= :: ChangedParameters -> ChangedParameters -> Bool
$cmax :: ChangedParameters -> ChangedParameters -> ChangedParameters
max :: ChangedParameters -> ChangedParameters -> ChangedParameters
$cmin :: ChangedParameters -> ChangedParameters -> ChangedParameters
min :: ChangedParameters -> ChangedParameters -> ChangedParameters
Haskell.Ord
    , ChangedParameters -> ChangedParameters -> Bool
(ChangedParameters -> ChangedParameters -> Bool)
-> Eq ChangedParameters
forall a. (a -> a -> Bool) -> Eq a
$c== :: ChangedParameters -> ChangedParameters -> Bool
== :: ChangedParameters -> ChangedParameters -> Bool
PlutusTx.Eq
    , ChangedParameters -> BuiltinData
(ChangedParameters -> BuiltinData) -> ToData ChangedParameters
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: ChangedParameters -> BuiltinData
toBuiltinData :: ChangedParameters -> BuiltinData
PlutusTx.ToData
    , BuiltinData -> Maybe ChangedParameters
(BuiltinData -> Maybe ChangedParameters)
-> FromData ChangedParameters
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe ChangedParameters
fromBuiltinData :: BuiltinData -> Maybe ChangedParameters
PlutusTx.FromData
    , BuiltinData -> ChangedParameters
(BuiltinData -> ChangedParameters)
-> UnsafeFromData ChangedParameters
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> ChangedParameters
unsafeFromBuiltinData :: BuiltinData -> ChangedParameters
PlutusTx.UnsafeFromData
    , (forall ann. ChangedParameters -> Doc ann)
-> (forall ann. [ChangedParameters] -> Doc ann)
-> Pretty ChangedParameters
forall ann. [ChangedParameters] -> Doc ann
forall ann. ChangedParameters -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. ChangedParameters -> Doc ann
pretty :: forall ann. ChangedParameters -> Doc ann
$cprettyList :: forall ann. [ChangedParameters] -> Doc ann
prettyList :: forall ann. [ChangedParameters] -> Doc ann
Pretty
    )

data GovernanceAction
  = ParameterChange
      (Haskell.Maybe GovernanceActionId)
      ChangedParameters
      (Haskell.Maybe V2.ScriptHash) -- ^ Hash of the constitution script
  | -- | proposal to update protocol version
    HardForkInitiation (Haskell.Maybe GovernanceActionId) ProtocolVersion
  | TreasuryWithdrawals
      (Map V2.Credential V2.Lovelace)
      (Haskell.Maybe V2.ScriptHash) -- ^ Hash of the constitution script
  | NoConfidence (Haskell.Maybe GovernanceActionId)
  | UpdateCommittee
      (Haskell.Maybe GovernanceActionId)
      [ColdCommitteeCredential] -- ^ Committee members to be removed
      (Map ColdCommitteeCredential Haskell.Integer) -- ^ Committee members to be added
      Rational -- ^ New quorum
  | NewConstitution (Haskell.Maybe GovernanceActionId) Constitution
  | InfoAction
  deriving stock ((forall x. GovernanceAction -> Rep GovernanceAction x)
-> (forall x. Rep GovernanceAction x -> GovernanceAction)
-> Generic GovernanceAction
forall x. Rep GovernanceAction x -> GovernanceAction
forall x. GovernanceAction -> Rep GovernanceAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GovernanceAction -> Rep GovernanceAction x
from :: forall x. GovernanceAction -> Rep GovernanceAction x
$cto :: forall x. Rep GovernanceAction x -> GovernanceAction
to :: forall x. Rep GovernanceAction x -> GovernanceAction
Generic, Int -> GovernanceAction -> ShowS
[GovernanceAction] -> ShowS
GovernanceAction -> String
(Int -> GovernanceAction -> ShowS)
-> (GovernanceAction -> String)
-> ([GovernanceAction] -> ShowS)
-> Show GovernanceAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GovernanceAction -> ShowS
showsPrec :: Int -> GovernanceAction -> ShowS
$cshow :: GovernanceAction -> String
show :: GovernanceAction -> String
$cshowList :: [GovernanceAction] -> ShowS
showList :: [GovernanceAction] -> ShowS
Haskell.Show)
  deriving ((forall ann. GovernanceAction -> Doc ann)
-> (forall ann. [GovernanceAction] -> Doc ann)
-> Pretty GovernanceAction
forall ann. [GovernanceAction] -> Doc ann
forall ann. GovernanceAction -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. GovernanceAction -> Doc ann
pretty :: forall ann. GovernanceAction -> Doc ann
$cprettyList :: forall ann. [GovernanceAction] -> Doc ann
prettyList :: forall ann. [GovernanceAction] -> Doc ann
Pretty) via (PrettyShow GovernanceAction)

-- | A proposal procedure. The optional anchor is omitted.
data ProposalProcedure = ProposalProcedure
  { ProposalProcedure -> Lovelace
ppDeposit          :: V2.Lovelace
  , ProposalProcedure -> Credential
ppReturnAddr       :: V2.Credential
  , ProposalProcedure -> GovernanceAction
ppGovernanceAction :: GovernanceAction
  }
  deriving stock ((forall x. ProposalProcedure -> Rep ProposalProcedure x)
-> (forall x. Rep ProposalProcedure x -> ProposalProcedure)
-> Generic ProposalProcedure
forall x. Rep ProposalProcedure x -> ProposalProcedure
forall x. ProposalProcedure -> Rep ProposalProcedure x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProposalProcedure -> Rep ProposalProcedure x
from :: forall x. ProposalProcedure -> Rep ProposalProcedure x
$cto :: forall x. Rep ProposalProcedure x -> ProposalProcedure
to :: forall x. Rep ProposalProcedure x -> ProposalProcedure
Generic, Int -> ProposalProcedure -> ShowS
[ProposalProcedure] -> ShowS
ProposalProcedure -> String
(Int -> ProposalProcedure -> ShowS)
-> (ProposalProcedure -> String)
-> ([ProposalProcedure] -> ShowS)
-> Show ProposalProcedure
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProposalProcedure -> ShowS
showsPrec :: Int -> ProposalProcedure -> ShowS
$cshow :: ProposalProcedure -> String
show :: ProposalProcedure -> String
$cshowList :: [ProposalProcedure] -> ShowS
showList :: [ProposalProcedure] -> ShowS
Haskell.Show)

instance Pretty ProposalProcedure where
  pretty :: forall ann. ProposalProcedure -> Doc ann
pretty ProposalProcedure{Credential
Lovelace
GovernanceAction
ppDeposit :: ProposalProcedure -> Lovelace
ppReturnAddr :: ProposalProcedure -> Credential
ppGovernanceAction :: ProposalProcedure -> GovernanceAction
ppDeposit :: Lovelace
ppReturnAddr :: Credential
ppGovernanceAction :: GovernanceAction
..} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"ppDeposit:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Lovelace -> Doc ann
pretty Lovelace
ppDeposit
      , Doc ann
"ppReturnAddr:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Credential -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Credential -> Doc ann
pretty Credential
ppReturnAddr
      , Doc ann
"ppGovernanceAction:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> GovernanceAction -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. GovernanceAction -> Doc ann
pretty GovernanceAction
ppGovernanceAction
      ]

-- | A `ScriptPurpose` uniquely identifies a Plutus script within a transaction.
data ScriptPurpose
  = Minting V2.CurrencySymbol
  | Spending V3.TxOutRef
  | Rewarding V2.Credential
  | Certifying
      Haskell.Integer
      -- ^ 0-based index of the given `TxCert` in `txInfoTxCerts`
      TxCert
  | Voting Voter
  | Proposing
      Haskell.Integer
      -- ^ 0-based index of the given `ProposalProcedure` in `txInfoProposalProcedures`
      ProposalProcedure
  deriving stock ((forall x. ScriptPurpose -> Rep ScriptPurpose x)
-> (forall x. Rep ScriptPurpose x -> ScriptPurpose)
-> Generic ScriptPurpose
forall x. Rep ScriptPurpose x -> ScriptPurpose
forall x. ScriptPurpose -> Rep ScriptPurpose x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScriptPurpose -> Rep ScriptPurpose x
from :: forall x. ScriptPurpose -> Rep ScriptPurpose x
$cto :: forall x. Rep ScriptPurpose x -> ScriptPurpose
to :: forall x. Rep ScriptPurpose x -> ScriptPurpose
Generic, Int -> ScriptPurpose -> ShowS
[ScriptPurpose] -> ShowS
ScriptPurpose -> String
(Int -> ScriptPurpose -> ShowS)
-> (ScriptPurpose -> String)
-> ([ScriptPurpose] -> ShowS)
-> Show ScriptPurpose
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScriptPurpose -> ShowS
showsPrec :: Int -> ScriptPurpose -> ShowS
$cshow :: ScriptPurpose -> String
show :: ScriptPurpose -> String
$cshowList :: [ScriptPurpose] -> ShowS
showList :: [ScriptPurpose] -> ShowS
Haskell.Show)
  deriving ((forall ann. ScriptPurpose -> Doc ann)
-> (forall ann. [ScriptPurpose] -> Doc ann) -> Pretty ScriptPurpose
forall ann. [ScriptPurpose] -> Doc ann
forall ann. ScriptPurpose -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. ScriptPurpose -> Doc ann
pretty :: forall ann. ScriptPurpose -> Doc ann
$cprettyList :: forall ann. [ScriptPurpose] -> Doc ann
prettyList :: forall ann. [ScriptPurpose] -> Doc ann
Pretty) via (PrettyShow ScriptPurpose)

-- | Like `ScriptPurpose` but with an optional datum for spending scripts.
data ScriptInfo
  = MintingScript V2.CurrencySymbol
  | SpendingScript V3.TxOutRef (Haskell.Maybe V2.Datum)
  | RewardingScript V2.Credential
  | CertifyingScript
      Haskell.Integer
      -- ^ 0-based index of the given `TxCert` in `txInfoTxCerts`
      TxCert
  | VotingScript Voter
  | ProposingScript
      Haskell.Integer
      -- ^ 0-based index of the given `ProposalProcedure` in `txInfoProposalProcedures`
      ProposalProcedure
  deriving stock ((forall x. ScriptInfo -> Rep ScriptInfo x)
-> (forall x. Rep ScriptInfo x -> ScriptInfo) -> Generic ScriptInfo
forall x. Rep ScriptInfo x -> ScriptInfo
forall x. ScriptInfo -> Rep ScriptInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScriptInfo -> Rep ScriptInfo x
from :: forall x. ScriptInfo -> Rep ScriptInfo x
$cto :: forall x. Rep ScriptInfo x -> ScriptInfo
to :: forall x. Rep ScriptInfo x -> ScriptInfo
Generic, Int -> ScriptInfo -> ShowS
[ScriptInfo] -> ShowS
ScriptInfo -> String
(Int -> ScriptInfo -> ShowS)
-> (ScriptInfo -> String)
-> ([ScriptInfo] -> ShowS)
-> Show ScriptInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScriptInfo -> ShowS
showsPrec :: Int -> ScriptInfo -> ShowS
$cshow :: ScriptInfo -> String
show :: ScriptInfo -> String
$cshowList :: [ScriptInfo] -> ShowS
showList :: [ScriptInfo] -> ShowS
Haskell.Show)
  deriving ((forall ann. ScriptInfo -> Doc ann)
-> (forall ann. [ScriptInfo] -> Doc ann) -> Pretty ScriptInfo
forall ann. [ScriptInfo] -> Doc ann
forall ann. ScriptInfo -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. ScriptInfo -> Doc ann
pretty :: forall ann. ScriptInfo -> Doc ann
$cprettyList :: forall ann. [ScriptInfo] -> Doc ann
prettyList :: forall ann. [ScriptInfo] -> Doc ann
Pretty) via (PrettyShow ScriptInfo)

-- | An input of a pending transaction.
data TxInInfo = TxInInfo
  { TxInInfo -> TxOutRef
txInInfoOutRef   :: V3.TxOutRef
  , TxInInfo -> TxOut
txInInfoResolved :: V2.TxOut
  }
  deriving stock ((forall x. TxInInfo -> Rep TxInInfo x)
-> (forall x. Rep TxInInfo x -> TxInInfo) -> Generic TxInInfo
forall x. Rep TxInInfo x -> TxInInfo
forall x. TxInInfo -> Rep TxInInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TxInInfo -> Rep TxInInfo x
from :: forall x. TxInInfo -> Rep TxInInfo x
$cto :: forall x. Rep TxInInfo x -> TxInInfo
to :: forall x. Rep TxInInfo x -> TxInInfo
Generic, Int -> TxInInfo -> ShowS
[TxInInfo] -> ShowS
TxInInfo -> String
(Int -> TxInInfo -> ShowS)
-> (TxInInfo -> String) -> ([TxInInfo] -> ShowS) -> Show TxInInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxInInfo -> ShowS
showsPrec :: Int -> TxInInfo -> ShowS
$cshow :: TxInInfo -> String
show :: TxInInfo -> String
$cshowList :: [TxInInfo] -> ShowS
showList :: [TxInInfo] -> ShowS
Haskell.Show, TxInInfo -> TxInInfo -> Bool
(TxInInfo -> TxInInfo -> Bool)
-> (TxInInfo -> TxInInfo -> Bool) -> Eq TxInInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TxInInfo -> TxInInfo -> Bool
== :: TxInInfo -> TxInInfo -> Bool
$c/= :: TxInInfo -> TxInInfo -> Bool
/= :: TxInInfo -> TxInInfo -> Bool
Haskell.Eq)

instance PlutusTx.Eq TxInInfo where
  TxInInfo TxOutRef
ref TxOut
res == :: TxInInfo -> TxInInfo -> Bool
== TxInInfo TxOutRef
ref' TxOut
res' =
    TxOutRef
ref TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef
ref' Bool -> Bool -> Bool
PlutusTx.&& TxOut
res TxOut -> TxOut -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOut
res'

instance Pretty TxInInfo where
  pretty :: forall ann. TxInInfo -> Doc ann
pretty TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef, TxOut
txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved :: TxOut
txInInfoResolved} =
    TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxOutRef -> Doc ann
pretty TxOutRef
txInInfoOutRef Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"->" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxOut -> Doc ann
pretty TxOut
txInInfoResolved

-- | TxInfo for PlutusV3
data TxInfo = TxInfo
  { TxInfo -> [TxInInfo]
txInfoInputs                :: [TxInInfo]
  , TxInfo -> [TxInInfo]
txInfoReferenceInputs       :: [TxInInfo]
  , TxInfo -> [TxOut]
txInfoOutputs               :: [V2.TxOut]
  , TxInfo -> Lovelace
txInfoFee                   :: V2.Lovelace
  , TxInfo -> Value
txInfoMint                  :: V2.Value
  -- ^ The 'Value' minted by this transaction.
  --
  -- /Invariant:/ This field does not contain Ada with zero quantity, unlike
  -- their namesakes in Plutus V1 and V2's ScriptContexts.
  , TxInfo -> [TxCert]
txInfoTxCerts               :: [TxCert]
  , TxInfo -> Map Credential Lovelace
txInfoWdrl                  :: Map V2.Credential V2.Lovelace
  , TxInfo -> POSIXTimeRange
txInfoValidRange            :: V2.POSIXTimeRange
  , TxInfo -> [PubKeyHash]
txInfoSignatories           :: [V2.PubKeyHash]
  , TxInfo -> Map ScriptPurpose Redeemer
txInfoRedeemers             :: Map ScriptPurpose V2.Redeemer
  , TxInfo -> Map DatumHash Datum
txInfoData                  :: Map V2.DatumHash V2.Datum
  , TxInfo -> TxId
txInfoId                    :: V3.TxId
  , TxInfo -> Map Voter (Map GovernanceActionId Vote)
txInfoVotes                 :: Map Voter (Map GovernanceActionId Vote)
  , TxInfo -> [ProposalProcedure]
txInfoProposalProcedures    :: [ProposalProcedure]
  , TxInfo -> Maybe Lovelace
txInfoCurrentTreasuryAmount :: Haskell.Maybe V2.Lovelace
  , TxInfo -> Maybe Lovelace
txInfoTreasuryDonation      :: Haskell.Maybe V2.Lovelace
  }
  deriving stock ((forall x. TxInfo -> Rep TxInfo x)
-> (forall x. Rep TxInfo x -> TxInfo) -> Generic TxInfo
forall x. Rep TxInfo x -> TxInfo
forall x. TxInfo -> Rep TxInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TxInfo -> Rep TxInfo x
from :: forall x. TxInfo -> Rep TxInfo x
$cto :: forall x. Rep TxInfo x -> TxInfo
to :: forall x. Rep TxInfo x -> TxInfo
Generic, Int -> TxInfo -> ShowS
[TxInfo] -> ShowS
TxInfo -> String
(Int -> TxInfo -> ShowS)
-> (TxInfo -> String) -> ([TxInfo] -> ShowS) -> Show TxInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TxInfo -> ShowS
showsPrec :: Int -> TxInfo -> ShowS
$cshow :: TxInfo -> String
show :: TxInfo -> String
$cshowList :: [TxInfo] -> ShowS
showList :: [TxInfo] -> ShowS
Haskell.Show)

-- | The context that the currently-executing script can access.
data ScriptContext = ScriptContext
  { ScriptContext -> TxInfo
scriptContextTxInfo     :: TxInfo
  -- ^ information about the transaction the currently-executing script is included in
  , ScriptContext -> Redeemer
scriptContextRedeemer   :: V2.Redeemer
  -- ^ Redeemer for the currently-executing script
  , ScriptContext -> ScriptInfo
scriptContextScriptInfo :: ScriptInfo
  -- ^ the purpose of the currently-executing script, along with information associated
  -- with the purpose
  }
  deriving stock ((forall x. ScriptContext -> Rep ScriptContext x)
-> (forall x. Rep ScriptContext x -> ScriptContext)
-> Generic ScriptContext
forall x. Rep ScriptContext x -> ScriptContext
forall x. ScriptContext -> Rep ScriptContext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ScriptContext -> Rep ScriptContext x
from :: forall x. ScriptContext -> Rep ScriptContext x
$cto :: forall x. Rep ScriptContext x -> ScriptContext
to :: forall x. Rep ScriptContext x -> ScriptContext
Generic, Int -> ScriptContext -> ShowS
[ScriptContext] -> ShowS
ScriptContext -> String
(Int -> ScriptContext -> ShowS)
-> (ScriptContext -> String)
-> ([ScriptContext] -> ShowS)
-> Show ScriptContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ScriptContext -> ShowS
showsPrec :: Int -> ScriptContext -> ShowS
$cshow :: ScriptContext -> String
show :: ScriptContext -> String
$cshowList :: [ScriptContext] -> ShowS
showList :: [ScriptContext] -> ShowS
Haskell.Show)

{-# INLINEABLE findOwnInput #-}

-- | Find the input currently being validated.
findOwnInput :: ScriptContext -> Haskell.Maybe TxInInfo
findOwnInput :: ScriptContext -> Maybe TxInInfo
findOwnInput
  ScriptContext
    { scriptContextTxInfo :: ScriptContext -> TxInfo
scriptContextTxInfo = TxInfo{[TxInInfo]
txInfoInputs :: TxInfo -> [TxInInfo]
txInfoInputs :: [TxInInfo]
txInfoInputs}
    , scriptContextScriptInfo :: ScriptContext -> ScriptInfo
scriptContextScriptInfo = SpendingScript TxOutRef
txOutRef Maybe Datum
_
    } =
    (TxInInfo -> Bool) -> [TxInInfo] -> Maybe TxInInfo
forall a. (a -> Bool) -> [a] -> Maybe a
PlutusTx.find
      (\TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef} -> TxOutRef
txInInfoOutRef TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef
txOutRef)
      [TxInInfo]
txInfoInputs
findOwnInput ScriptContext
_ = Maybe TxInInfo
forall a. Maybe a
Haskell.Nothing

{-# INLINEABLE findDatum #-}

-- | Find the data corresponding to a data hash, if there is one
findDatum :: V2.DatumHash -> TxInfo -> Haskell.Maybe V2.Datum
findDatum :: DatumHash -> TxInfo -> Maybe Datum
findDatum DatumHash
dsh TxInfo{Map DatumHash Datum
txInfoData :: TxInfo -> Map DatumHash Datum
txInfoData :: Map DatumHash Datum
txInfoData} = DatumHash -> Map DatumHash Datum -> Maybe Datum
forall k a. (ToData k, UnsafeFromData a) => k -> Map k a -> Maybe a
lookup DatumHash
dsh Map DatumHash Datum
txInfoData

{-# INLINEABLE findDatumHash #-}

{- | Find the hash of a datum, if it is part of the pending transaction's
hashes
-}
findDatumHash :: V2.Datum -> TxInfo -> Haskell.Maybe V2.DatumHash
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
findDatumHash Datum
ds TxInfo{Map DatumHash Datum
txInfoData :: TxInfo -> Map DatumHash Datum
txInfoData :: Map DatumHash Datum
txInfoData} =
  (DatumHash, Datum) -> DatumHash
forall a b. (a, b) -> a
PlutusTx.fst ((DatumHash, Datum) -> DatumHash)
-> Maybe (DatumHash, Datum) -> Maybe DatumHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
PlutusTx.<$> ((DatumHash, Datum) -> Bool)
-> [(DatumHash, Datum)] -> Maybe (DatumHash, Datum)
forall a. (a -> Bool) -> [a] -> Maybe a
PlutusTx.find (DatumHash, Datum) -> Bool
forall {a}. (a, Datum) -> Bool
f (Map DatumHash Datum -> [(DatumHash, Datum)]
forall k a.
(UnsafeFromData k, UnsafeFromData a) =>
Map k a -> [(k, a)]
toList Map DatumHash Datum
txInfoData)
  where
    f :: (a, Datum) -> Bool
f (a
_, Datum
ds') = Datum
ds' Datum -> Datum -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Datum
ds

{-# INLINEABLE findTxInByTxOutRef #-}

{- | Given a UTXO reference and a transaction (`TxInfo`), resolve it to one of the
transaction's inputs (`TxInInfo`).

Note: this only searches the true transaction inputs and not the referenced transaction inputs.
-}
findTxInByTxOutRef :: V3.TxOutRef -> TxInfo -> Haskell.Maybe TxInInfo
findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
findTxInByTxOutRef TxOutRef
outRef TxInfo{[TxInInfo]
txInfoInputs :: TxInfo -> [TxInInfo]
txInfoInputs :: [TxInInfo]
txInfoInputs} =
  (TxInInfo -> Bool) -> [TxInInfo] -> Maybe TxInInfo
forall a. (a -> Bool) -> [a] -> Maybe a
PlutusTx.find
    (\TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef} -> TxOutRef
txInInfoOutRef TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef
outRef)
    [TxInInfo]
txInfoInputs

{-# INLINEABLE findContinuingOutputs #-}

{- | Find the indices of all the outputs that pay to the same script address we are
currently spending from, if any.
-}
findContinuingOutputs :: ScriptContext -> [Haskell.Integer]
findContinuingOutputs :: ScriptContext -> [Integer]
findContinuingOutputs ScriptContext
ctx
  | Haskell.Just TxInInfo{txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved = V2.TxOut{Address
txOutAddress :: Address
txOutAddress :: TxOut -> Address
txOutAddress}} <-
      ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext
ctx =
      (TxOut -> Bool) -> [TxOut] -> [Integer]
forall a. (a -> Bool) -> [a] -> [Integer]
PlutusTx.findIndices
        (Address -> TxOut -> Bool
f Address
txOutAddress)
        (TxInfo -> [TxOut]
txInfoOutputs (ScriptContext -> TxInfo
scriptContextTxInfo ScriptContext
ctx))
  where
    f :: Address -> TxOut -> Bool
f Address
addr V2.TxOut{txOutAddress :: TxOut -> Address
txOutAddress = Address
otherAddress} = Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Address
otherAddress
findContinuingOutputs ScriptContext
_ = BuiltinString -> [Integer]
forall a. BuiltinString -> a
PlutusTx.traceError BuiltinString
"Le" -- "Can't find any continuing outputs"

{-# INLINEABLE getContinuingOutputs #-}

{- | Get all the outputs that pay to the same script address we are currently spending
from, if any.
-}
getContinuingOutputs :: ScriptContext -> [V2.TxOut]
getContinuingOutputs :: ScriptContext -> [TxOut]
getContinuingOutputs ScriptContext
ctx
  | Haskell.Just TxInInfo{txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved = V2.TxOut{Address
txOutAddress :: TxOut -> Address
txOutAddress :: Address
txOutAddress}} <-
      ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext
ctx =
      (TxOut -> Bool) -> [TxOut] -> [TxOut]
forall a. (a -> Bool) -> [a] -> [a]
PlutusTx.filter (Address -> TxOut -> Bool
f Address
txOutAddress) (TxInfo -> [TxOut]
txInfoOutputs (ScriptContext -> TxInfo
scriptContextTxInfo ScriptContext
ctx))
  where
    f :: Address -> TxOut -> Bool
f Address
addr V2.TxOut{txOutAddress :: TxOut -> Address
txOutAddress = Address
otherAddress} = Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Address
otherAddress
getContinuingOutputs ScriptContext
_ = BuiltinString -> [TxOut]
forall a. BuiltinString -> a
PlutusTx.traceError BuiltinString
"Lf" -- "Can't get any continuing outputs"

{-# INLINEABLE txSignedBy #-}

-- | Check if a transaction was signed by the given public key.
txSignedBy :: TxInfo -> V2.PubKeyHash -> Haskell.Bool
txSignedBy :: TxInfo -> PubKeyHash -> Bool
txSignedBy TxInfo{[PubKeyHash]
txInfoSignatories :: TxInfo -> [PubKeyHash]
txInfoSignatories :: [PubKeyHash]
txInfoSignatories} PubKeyHash
k = case (PubKeyHash -> Bool) -> [PubKeyHash] -> Maybe PubKeyHash
forall a. (a -> Bool) -> [a] -> Maybe a
PlutusTx.find (PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
(PlutusTx.==) PubKeyHash
k) [PubKeyHash]
txInfoSignatories of
  Haskell.Just PubKeyHash
_  -> Bool
Haskell.True
  Maybe PubKeyHash
Haskell.Nothing -> Bool
Haskell.False

{-# INLINEABLE pubKeyOutputsAt #-}

-- | Get the values paid to a public key address by a pending transaction.
pubKeyOutputsAt :: V2.PubKeyHash -> TxInfo -> [V2.Value]
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value]
pubKeyOutputsAt PubKeyHash
pk TxInfo
p =
  let flt :: TxOut -> Maybe Value
flt V2.TxOut{txOutAddress :: TxOut -> Address
txOutAddress = V2.Address (V2.PubKeyCredential PubKeyHash
pk') Maybe StakingCredential
_, Value
txOutValue :: Value
txOutValue :: TxOut -> Value
txOutValue}
        | PubKeyHash
pk PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
pk' = Value -> Maybe Value
forall a. a -> Maybe a
Haskell.Just Value
txOutValue
      flt TxOut
_ = Maybe Value
forall a. Maybe a
Haskell.Nothing
   in (TxOut -> Maybe Value) -> [TxOut] -> [Value]
forall a b. (a -> Maybe b) -> [a] -> [b]
PlutusTx.mapMaybe TxOut -> Maybe Value
flt (TxInfo -> [TxOut]
txInfoOutputs TxInfo
p)

{-# INLINEABLE valuePaidTo #-}

-- | Get the total value paid to a public key address by a pending transaction.
valuePaidTo :: TxInfo -> V2.PubKeyHash -> V2.Value
valuePaidTo :: TxInfo -> PubKeyHash -> Value
valuePaidTo TxInfo
ptx PubKeyHash
pkh = [Value] -> Value
forall a. Monoid a => [a] -> a
PlutusTx.mconcat (PubKeyHash -> TxInfo -> [Value]
pubKeyOutputsAt PubKeyHash
pkh TxInfo
ptx)

{-# INLINEABLE valueSpent #-}

-- | Get the total value of inputs spent by this transaction.
valueSpent :: TxInfo -> V2.Value
valueSpent :: TxInfo -> Value
valueSpent =
  (TxInInfo -> Value) -> [TxInInfo] -> Value
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
PlutusTx.foldMap (TxOut -> Value
V2.txOutValue (TxOut -> Value) -> (TxInInfo -> TxOut) -> TxInInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
PlutusTx.. TxInInfo -> TxOut
txInInfoResolved) ([TxInInfo] -> Value) -> (TxInfo -> [TxInInfo]) -> TxInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
PlutusTx.. TxInfo -> [TxInInfo]
txInfoInputs

{-# INLINEABLE valueProduced #-}

-- | Get the total value of outputs produced by this transaction.
valueProduced :: TxInfo -> V2.Value
valueProduced :: TxInfo -> Value
valueProduced = (TxOut -> Value) -> [TxOut] -> Value
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
PlutusTx.foldMap TxOut -> Value
V2.txOutValue ([TxOut] -> Value) -> (TxInfo -> [TxOut]) -> TxInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
PlutusTx.. TxInfo -> [TxOut]
txInfoOutputs

{-# INLINEABLE ownCurrencySymbol #-}

-- | The 'CurrencySymbol' of the current validator script.
ownCurrencySymbol :: ScriptContext -> V2.CurrencySymbol
ownCurrencySymbol :: ScriptContext -> CurrencySymbol
ownCurrencySymbol ScriptContext{scriptContextScriptInfo :: ScriptContext -> ScriptInfo
scriptContextScriptInfo = MintingScript CurrencySymbol
cs} = CurrencySymbol
cs
ownCurrencySymbol ScriptContext
_ =
  -- "Can't get currency symbol of the current validator script"
  BuiltinString -> CurrencySymbol
forall a. BuiltinString -> a
PlutusTx.traceError BuiltinString
"Lh"

{-# INLINEABLE spendsOutput #-}

{- | Check if the pending transaction spends a specific transaction output
(identified by the hash of a transaction and an index into that
transactions' outputs)
-}
spendsOutput :: TxInfo -> V3.TxId -> Haskell.Integer -> Haskell.Bool
spendsOutput :: TxInfo -> TxId -> Integer -> Bool
spendsOutput TxInfo
txInfo TxId
txId Integer
i =
  let spendsOutRef :: TxInInfo -> Bool
spendsOutRef TxInInfo
inp =
        let outRef :: TxOutRef
outRef = TxInInfo -> TxOutRef
txInInfoOutRef TxInInfo
inp
         in TxId
txId TxId -> TxId -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef -> TxId
V3.txOutRefId TxOutRef
outRef
              Bool -> Bool -> Bool
PlutusTx.&& Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef -> Integer
V3.txOutRefIdx TxOutRef
outRef
   in (TxInInfo -> Bool) -> [TxInInfo] -> Bool
forall a. (a -> Bool) -> [a] -> Bool
PlutusTx.any TxInInfo -> Bool
spendsOutRef (TxInfo -> [TxInInfo]
txInfoInputs TxInfo
txInfo)

PlutusTx.makeLift ''ColdCommitteeCredential
PlutusTx.makeLift ''HotCommitteeCredential
PlutusTx.makeLift ''DRepCredential

PlutusTx.makeLift ''DRep
PlutusTx.makeIsDataIndexed
  ''DRep
  [ ('DRep, 0)
  , ('DRepAlwaysAbstain, 1)
  , ('DRepAlwaysNoConfidence, 2)
  ]

PlutusTx.makeLift ''Delegatee
PlutusTx.makeIsDataIndexed
  ''Delegatee
  [ ('DelegStake, 0)
  , ('DelegVote, 1)
  , ('DelegStakeVote, 2)
  ]

PlutusTx.makeLift ''TxCert
PlutusTx.makeIsDataIndexed
  ''TxCert
  [ ('TxCertRegStaking, 0)
  , ('TxCertUnRegStaking, 1)
  , ('TxCertDelegStaking, 2)
  , ('TxCertRegDeleg, 3)
  , ('TxCertRegDRep, 4)
  , ('TxCertUpdateDRep, 5)
  , ('TxCertUnRegDRep, 6)
  , ('TxCertPoolRegister, 7)
  , ('TxCertPoolRetire, 8)
  , ('TxCertAuthHotCommittee, 9)
  , ('TxCertResignColdCommittee, 10)
  ]

PlutusTx.makeLift ''Voter
PlutusTx.makeIsDataIndexed
  ''Voter
  [ ('CommitteeVoter, 0)
  , ('DRepVoter, 1)
  , ('StakePoolVoter, 2)
  ]

PlutusTx.makeLift ''Vote
PlutusTx.makeIsDataIndexed
  ''Vote
  [ ('VoteNo, 0)
  , ('VoteYes, 1)
  , ('Abstain, 2)
  ]

PlutusTx.makeLift ''GovernanceActionId
PlutusTx.makeIsDataIndexed ''GovernanceActionId [('GovernanceActionId, 0)]

PlutusTx.makeLift ''Committee
PlutusTx.makeIsDataIndexed ''Committee [('Committee, 0)]

PlutusTx.makeLift ''Constitution
PlutusTx.makeIsDataIndexed ''Constitution [('Constitution, 0)]

PlutusTx.makeLift ''ProtocolVersion
PlutusTx.makeIsDataIndexed ''ProtocolVersion [('ProtocolVersion, 0)]

PlutusTx.makeLift ''ChangedParameters
PlutusTx.makeLift ''GovernanceAction
PlutusTx.makeIsDataIndexed
  ''GovernanceAction
  [ ('ParameterChange, 0)
  , ('HardForkInitiation, 1)
  , ('TreasuryWithdrawals, 2)
  , ('NoConfidence, 3)
  , ('UpdateCommittee, 4)
  , ('NewConstitution, 5)
  , ('InfoAction, 6)
  ]

PlutusTx.makeLift ''ProposalProcedure
PlutusTx.makeIsDataIndexed ''ProposalProcedure [('ProposalProcedure, 0)]

PlutusTx.makeLift ''ScriptPurpose
PlutusTx.makeIsDataIndexed
  ''ScriptPurpose
  [ ('Minting, 0)
  , ('Spending, 1)
  , ('Rewarding, 2)
  , ('Certifying, 3)
  , ('Voting, 4)
  , ('Proposing, 5)
  ]

PlutusTx.makeLift ''TxInInfo
PlutusTx.makeIsDataIndexed ''TxInInfo [('TxInInfo, 0)]

PlutusTx.makeLift ''TxInfo
PlutusTx.makeIsDataIndexed ''TxInfo [('TxInfo, 0)]

PlutusTx.makeLift ''ScriptInfo
PlutusTx.makeIsDataIndexed
  ''ScriptInfo
  [ ('MintingScript, 0)
  , ('SpendingScript, 1)
  , ('RewardingScript, 2)
  , ('CertifyingScript, 3)
  , ('VotingScript, 4)
  , ('ProposingScript, 5)
  ]

PlutusTx.makeLift ''ScriptContext
PlutusTx.makeIsDataIndexed ''ScriptContext [('ScriptContext, 0)]

instance Pretty TxInfo where
  pretty :: forall ann. TxInfo -> Doc ann
pretty TxInfo{[PubKeyHash]
[TxOut]
[TxInInfo]
[ProposalProcedure]
[TxCert]
Maybe Lovelace
Map DatumHash Datum
Map Credential Lovelace
Map ScriptPurpose Redeemer
Map Voter (Map GovernanceActionId Vote)
POSIXTimeRange
TxId
Lovelace
Value
txInfoTxCerts :: TxInfo -> [TxCert]
txInfoProposalProcedures :: TxInfo -> [ProposalProcedure]
txInfoInputs :: TxInfo -> [TxInInfo]
txInfoReferenceInputs :: TxInfo -> [TxInInfo]
txInfoOutputs :: TxInfo -> [TxOut]
txInfoFee :: TxInfo -> Lovelace
txInfoMint :: TxInfo -> Value
txInfoWdrl :: TxInfo -> Map Credential Lovelace
txInfoValidRange :: TxInfo -> POSIXTimeRange
txInfoSignatories :: TxInfo -> [PubKeyHash]
txInfoRedeemers :: TxInfo -> Map ScriptPurpose Redeemer
txInfoData :: TxInfo -> Map DatumHash Datum
txInfoId :: TxInfo -> TxId
txInfoVotes :: TxInfo -> Map Voter (Map GovernanceActionId Vote)
txInfoCurrentTreasuryAmount :: TxInfo -> Maybe Lovelace
txInfoTreasuryDonation :: TxInfo -> Maybe Lovelace
txInfoInputs :: [TxInInfo]
txInfoReferenceInputs :: [TxInInfo]
txInfoOutputs :: [TxOut]
txInfoFee :: Lovelace
txInfoMint :: Value
txInfoTxCerts :: [TxCert]
txInfoWdrl :: Map Credential Lovelace
txInfoValidRange :: POSIXTimeRange
txInfoSignatories :: [PubKeyHash]
txInfoRedeemers :: Map ScriptPurpose Redeemer
txInfoData :: Map DatumHash Datum
txInfoId :: TxId
txInfoVotes :: Map Voter (Map GovernanceActionId Vote)
txInfoProposalProcedures :: [ProposalProcedure]
txInfoCurrentTreasuryAmount :: Maybe Lovelace
txInfoTreasuryDonation :: Maybe Lovelace
..} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"TxId:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxId -> Doc ann
pretty TxId
txInfoId
      , Doc ann
"Inputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [TxInInfo] -> Doc ann
forall ann. [TxInInfo] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxInInfo]
txInfoInputs
      , Doc ann
"Reference inputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [TxInInfo] -> Doc ann
forall ann. [TxInInfo] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxInInfo]
txInfoReferenceInputs
      , Doc ann
"Outputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [TxOut] -> Doc ann
forall ann. [TxOut] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxOut]
txInfoOutputs
      , Doc ann
"Fee:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Lovelace -> Doc ann
pretty Lovelace
txInfoFee
      , Doc ann
"Value minted:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Value -> Doc ann
pretty Value
txInfoMint
      , Doc ann
"TxCerts:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [TxCert] -> Doc ann
forall ann. [TxCert] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [TxCert]
txInfoTxCerts
      , Doc ann
"Wdrl:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map Credential Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map Credential Lovelace -> Doc ann
pretty Map Credential Lovelace
txInfoWdrl
      , Doc ann
"Valid range:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> POSIXTimeRange -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. POSIXTimeRange -> Doc ann
pretty POSIXTimeRange
txInfoValidRange
      , Doc ann
"Signatories:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [PubKeyHash] -> Doc ann
forall ann. [PubKeyHash] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [PubKeyHash]
txInfoSignatories
      , Doc ann
"Redeemers:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map ScriptPurpose Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map ScriptPurpose Redeemer -> Doc ann
pretty Map ScriptPurpose Redeemer
txInfoRedeemers
      , Doc ann
"Datums:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map DatumHash Datum -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map DatumHash Datum -> Doc ann
pretty Map DatumHash Datum
txInfoData
      , Doc ann
"Votes:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map Voter (Map GovernanceActionId Vote) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map Voter (Map GovernanceActionId Vote) -> Doc ann
pretty Map Voter (Map GovernanceActionId Vote)
txInfoVotes
      , Doc ann
"Proposal Procedures:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> [ProposalProcedure] -> Doc ann
forall ann. [ProposalProcedure] -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty [ProposalProcedure]
txInfoProposalProcedures
      , Doc ann
"Current Treasury Amount:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe Lovelace -> Doc ann
forall ann. Maybe Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe Lovelace
txInfoCurrentTreasuryAmount
      , Doc ann
"Treasury Donation:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe Lovelace -> Doc ann
forall ann. Maybe Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe Lovelace
txInfoTreasuryDonation
      ]

instance Pretty ScriptContext where
  pretty :: forall ann. ScriptContext -> Doc ann
pretty ScriptContext{Redeemer
TxInfo
ScriptInfo
scriptContextTxInfo :: ScriptContext -> TxInfo
scriptContextRedeemer :: ScriptContext -> Redeemer
scriptContextScriptInfo :: ScriptContext -> ScriptInfo
scriptContextTxInfo :: TxInfo
scriptContextRedeemer :: Redeemer
scriptContextScriptInfo :: ScriptInfo
..} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"ScriptInfo:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> ScriptInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. ScriptInfo -> Doc ann
pretty ScriptInfo
scriptContextScriptInfo
      , Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"TxInfo:", TxInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxInfo -> Doc ann
pretty TxInfo
scriptContextTxInfo])
      , Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"Redeemer:", Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Redeemer -> Doc ann
pretty Redeemer
scriptContextRedeemer])
      ]