{-# OPTIONS_GHC -Wno-orphans #-}
module Plutarch.LedgerApi.V1.DCert (
PDCert (..),
) where
import GHC.Generics (Generic)
import Plutarch.LedgerApi.V1.Credential (PStakingCredential)
import Plutarch.LedgerApi.V1.Crypto (PPubKeyHash)
import Plutarch.Prelude
import PlutusLedgerApi.V1 qualified as Plutus
data PDCert (s :: S)
= PDCertDelegRegKey (Term s (PDataRecord '["_0" ':= PStakingCredential]))
| PDCertDelegDeRegKey (Term s (PDataRecord '["_0" ':= PStakingCredential]))
| PDCertDelegDelegate (Term s (PDataRecord '["_0" ':= PStakingCredential, "_1" ':= PPubKeyHash]))
| PDCertPoolRegister (Term s (PDataRecord '["_0" ':= PPubKeyHash, "_1" ':= PPubKeyHash]))
| PDCertPoolRetire (Term s (PDataRecord '["_0" ':= PPubKeyHash, "_1" ':= PInteger]))
| PDCertGenesis (Term s (PDataRecord '[]))
| PDCertMir (Term s (PDataRecord '[]))
deriving stock
(
(forall x. PDCert s -> Rep (PDCert s) x)
-> (forall x. Rep (PDCert s) x -> PDCert s) -> Generic (PDCert s)
forall x. Rep (PDCert s) x -> PDCert s
forall x. PDCert s -> Rep (PDCert s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x. Rep (PDCert s) x -> PDCert s
forall (s :: S) x. PDCert s -> Rep (PDCert s) x
$cfrom :: forall (s :: S) x. PDCert s -> Rep (PDCert s) x
from :: forall x. PDCert s -> Rep (PDCert s) x
$cto :: forall (s :: S) x. Rep (PDCert s) x -> PDCert s
to :: forall x. Rep (PDCert s) x -> PDCert s
Generic
)
deriving anyclass
(
(forall (s :: S). PDCert s -> Term s (PInner PDCert))
-> (forall (s :: S) (b :: PType).
Term s (PInner PDCert) -> (PDCert s -> Term s b) -> Term s b)
-> PlutusType PDCert
forall (s :: S). PDCert s -> Term s (PInner PDCert)
forall (s :: S) (b :: PType).
Term s (PInner PDCert) -> (PDCert s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S). PDCert s -> Term s (PInner PDCert)
pcon' :: forall (s :: S). PDCert s -> Term s (PInner PDCert)
$cpmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PDCert) -> (PDCert s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PDCert) -> (PDCert s -> Term s b) -> Term s b
PlutusType
,
(forall (s :: S). Term s (PAsData PDCert) -> Term s PDCert)
-> (forall (s :: S). Term s PDCert -> Term s PData)
-> PIsData PDCert
forall (s :: S). Term s (PAsData PDCert) -> Term s PDCert
forall (s :: S). Term s PDCert -> Term s PData
forall (a :: PType).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S). Term s (PAsData PDCert) -> Term s PDCert
pfromDataImpl :: forall (s :: S). Term s (PAsData PDCert) -> Term s PDCert
$cpdataImpl :: forall (s :: S). Term s PDCert -> Term s PData
pdataImpl :: forall (s :: S). Term s PDCert -> Term s PData
PIsData
,
(forall (s :: S). Term s PDCert -> Term s PDCert -> Term s PBool)
-> PEq PDCert
forall (s :: S). Term s PDCert -> Term s PDCert -> Term s PBool
forall (t :: PType).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S). Term s PDCert -> Term s PDCert -> Term s PBool
#== :: forall (s :: S). Term s PDCert -> Term s PDCert -> Term s PBool
PEq
,
(forall (s :: S). Bool -> Term s PDCert -> Term s PString)
-> PShow PDCert
forall (s :: S). Bool -> Term s PDCert -> Term s PString
forall (t :: PType).
(forall (s :: S). Bool -> Term s t -> Term s PString) -> PShow t
$cpshow' :: forall (s :: S). Bool -> Term s PDCert -> Term s PString
pshow' :: forall (s :: S). Bool -> Term s PDCert -> Term s PString
PShow
,
PTryFrom PData
)
instance DerivePlutusType PDCert where
type DPTStrat _ = PlutusTypeData
deriving via
DeriveDataPLiftable PDCert Plutus.DCert
instance
PLiftable PDCert
instance PTryFrom PData (PAsData PDCert)