{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
module Plutus.V1.Ledger.DCert(DCert(..)) where
import Codec.Serialise.Class (Serialise)
import Control.DeepSeq (NFData)
import Data.Aeson (FromJSON, ToJSON)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import Plutus.V1.Ledger.Credential (StakingCredential)
import Plutus.V1.Ledger.Crypto (PubKeyHash)
import PlutusTx qualified as PlutusTx
import PlutusTx.Prelude qualified as P
import Prettyprinter (Pretty (..), viaShow)
data DCert
= DCertDelegRegKey StakingCredential
| DCertDelegDeRegKey StakingCredential
| DCertDelegDelegate
StakingCredential
PubKeyHash
|
DCertPoolRegister
PubKeyHash
PubKeyHash
|
DCertPoolRetire PubKeyHash Integer
|
DCertGenesis
|
DCertMir
deriving stock (DCert -> DCert -> Bool
(DCert -> DCert -> Bool) -> (DCert -> DCert -> Bool) -> Eq DCert
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DCert -> DCert -> Bool
$c/= :: DCert -> DCert -> Bool
== :: DCert -> DCert -> Bool
$c== :: DCert -> DCert -> Bool
Eq, Eq DCert
Eq DCert
-> (DCert -> DCert -> Ordering)
-> (DCert -> DCert -> Bool)
-> (DCert -> DCert -> Bool)
-> (DCert -> DCert -> Bool)
-> (DCert -> DCert -> Bool)
-> (DCert -> DCert -> DCert)
-> (DCert -> DCert -> DCert)
-> Ord DCert
DCert -> DCert -> Bool
DCert -> DCert -> Ordering
DCert -> DCert -> DCert
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
min :: DCert -> DCert -> DCert
$cmin :: DCert -> DCert -> DCert
max :: DCert -> DCert -> DCert
$cmax :: DCert -> DCert -> DCert
>= :: DCert -> DCert -> Bool
$c>= :: DCert -> DCert -> Bool
> :: DCert -> DCert -> Bool
$c> :: DCert -> DCert -> Bool
<= :: DCert -> DCert -> Bool
$c<= :: DCert -> DCert -> Bool
< :: DCert -> DCert -> Bool
$c< :: DCert -> DCert -> Bool
compare :: DCert -> DCert -> Ordering
$ccompare :: DCert -> DCert -> Ordering
$cp1Ord :: Eq DCert
Ord, Int -> DCert -> ShowS
[DCert] -> ShowS
DCert -> String
(Int -> DCert -> ShowS)
-> (DCert -> String) -> ([DCert] -> ShowS) -> Show DCert
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DCert] -> ShowS
$cshowList :: [DCert] -> ShowS
show :: DCert -> String
$cshow :: DCert -> String
showsPrec :: Int -> DCert -> ShowS
$cshowsPrec :: Int -> DCert -> ShowS
Show, (forall x. DCert -> Rep DCert x)
-> (forall x. Rep DCert x -> DCert) -> Generic DCert
forall x. Rep DCert x -> DCert
forall x. DCert -> Rep DCert x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DCert x -> DCert
$cfrom :: forall x. DCert -> Rep DCert x
Generic)
deriving anyclass ([DCert] -> Encoding
[DCert] -> Value
DCert -> Encoding
DCert -> Value
(DCert -> Value)
-> (DCert -> Encoding)
-> ([DCert] -> Value)
-> ([DCert] -> Encoding)
-> ToJSON DCert
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DCert] -> Encoding
$ctoEncodingList :: [DCert] -> Encoding
toJSONList :: [DCert] -> Value
$ctoJSONList :: [DCert] -> Value
toEncoding :: DCert -> Encoding
$ctoEncoding :: DCert -> Encoding
toJSON :: DCert -> Value
$ctoJSON :: DCert -> Value
ToJSON, Value -> Parser [DCert]
Value -> Parser DCert
(Value -> Parser DCert)
-> (Value -> Parser [DCert]) -> FromJSON DCert
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DCert]
$cparseJSONList :: Value -> Parser [DCert]
parseJSON :: Value -> Parser DCert
$cparseJSON :: Value -> Parser DCert
FromJSON, [DCert] -> Encoding
DCert -> Encoding
(DCert -> Encoding)
-> (forall s. Decoder s DCert)
-> ([DCert] -> Encoding)
-> (forall s. Decoder s [DCert])
-> Serialise DCert
forall s. Decoder s [DCert]
forall s. Decoder s DCert
forall a.
(a -> Encoding)
-> (forall s. Decoder s a)
-> ([a] -> Encoding)
-> (forall s. Decoder s [a])
-> Serialise a
decodeList :: Decoder s [DCert]
$cdecodeList :: forall s. Decoder s [DCert]
encodeList :: [DCert] -> Encoding
$cencodeList :: [DCert] -> Encoding
decode :: Decoder s DCert
$cdecode :: forall s. Decoder s DCert
encode :: DCert -> Encoding
$cencode :: DCert -> Encoding
Serialise, Int -> DCert -> Int
DCert -> Int
(Int -> DCert -> Int) -> (DCert -> Int) -> Hashable DCert
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DCert -> Int
$chash :: DCert -> Int
hashWithSalt :: Int -> DCert -> Int
$chashWithSalt :: Int -> DCert -> Int
Hashable, DCert -> ()
(DCert -> ()) -> NFData DCert
forall a. (a -> ()) -> NFData a
rnf :: DCert -> ()
$crnf :: DCert -> ()
NFData)
instance P.Eq DCert where
{-# INLINABLE (==) #-}
DCertDelegRegKey StakingCredential
sc == :: DCert -> DCert -> Bool
== DCertDelegRegKey StakingCredential
sc' = StakingCredential
sc StakingCredential -> StakingCredential -> Bool
forall a. Eq a => a -> a -> Bool
P.== StakingCredential
sc'
DCertDelegDeRegKey StakingCredential
sc == DCertDelegDeRegKey StakingCredential
sc' = StakingCredential
sc StakingCredential -> StakingCredential -> Bool
forall a. Eq a => a -> a -> Bool
P.== StakingCredential
sc'
DCertDelegDelegate StakingCredential
sc PubKeyHash
pkh == DCertDelegDelegate StakingCredential
sc' PubKeyHash
pkh' = StakingCredential
sc StakingCredential -> StakingCredential -> Bool
forall a. Eq a => a -> a -> Bool
P.== StakingCredential
sc' Bool -> Bool -> Bool
&& PubKeyHash
pkh PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
P.== PubKeyHash
pkh'
DCertPoolRegister PubKeyHash
pid PubKeyHash
pvfr == DCertPoolRegister PubKeyHash
pid' PubKeyHash
pvfr' = PubKeyHash
pid PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
P.== PubKeyHash
pid' Bool -> Bool -> Bool
&& PubKeyHash
pvfr PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
P.== PubKeyHash
pvfr'
DCertPoolRetire PubKeyHash
pkh Integer
i == DCertPoolRetire PubKeyHash
pkh' Integer
i' = PubKeyHash
pkh PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
P.== PubKeyHash
pkh' Bool -> Bool -> Bool
&& Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
P.== Integer
i'
DCert
DCertGenesis == DCert
DCertGenesis = Bool
True
DCert
DCertMir == DCert
DCertMir = Bool
True
DCert
_ == DCert
_ = Bool
False
instance Pretty DCert where
pretty :: DCert -> Doc ann
pretty = DCert -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow
PlutusTx.makeIsDataIndexed
''DCert
[ ('DCertDelegRegKey,0)
, ('DCertDelegDeRegKey,1)
, ('DCertDelegDelegate,2)
, ('DCertPoolRegister,3)
, ('DCertPoolRetire,4)
, ('DCertGenesis,5)
, ('DCertMir,6)
]
PlutusTx.makeLift ''DCert