{-# OPTIONS_GHC -Wno-orphans #-}
module PlutusLedgerApi.V3.Orphans (MintValue, getMintValue) where
import Control.Monad (guard)
import Data.Coerce (coerce)
import Data.Set qualified as Set
import PlutusLedgerApi.Orphans.Common (
Blake2b256Hash (Blake2b256Hash),
)
import PlutusLedgerApi.V1.Orphans.Credential ()
import PlutusLedgerApi.V1.Orphans.Interval ()
import PlutusLedgerApi.V1.Orphans.Time ()
import PlutusLedgerApi.V1.Orphans.Value ()
import PlutusLedgerApi.V2.Orphans.Tx ()
import PlutusLedgerApi.V3 qualified as PLA
import PlutusLedgerApi.V3.Orphans.Value (MintValue, getMintValue)
import PlutusLedgerApi.V3.Orphans.Value qualified as Value
import PlutusTx.AssocMap qualified as AssocMap
import PlutusTx.Builtins qualified as Builtins
import PlutusTx.Prelude qualified as PlutusTx
import PlutusTx.Ratio qualified as Ratio
import Test.QuickCheck (
Arbitrary (arbitrary, shrink),
Arbitrary1 (liftArbitrary, liftShrink),
CoArbitrary (coarbitrary),
Function (function),
NonEmptyList (NonEmpty),
NonNegative (NonNegative),
Positive (Positive),
chooseInt,
elements,
functionMap,
getNonEmpty,
getNonNegative,
getPositive,
oneof,
variant,
)
import Test.QuickCheck.Instances.Containers ()
deriving via PLA.Credential instance Arbitrary PLA.ColdCommitteeCredential
deriving via PLA.Credential instance CoArbitrary PLA.ColdCommitteeCredential
instance Function PLA.ColdCommitteeCredential where
{-# INLINEABLE function #-}
function :: forall b.
(ColdCommitteeCredential -> b) -> ColdCommitteeCredential :-> b
function = (ColdCommitteeCredential -> Credential)
-> (Credential -> ColdCommitteeCredential)
-> (ColdCommitteeCredential -> b)
-> ColdCommitteeCredential :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ColdCommitteeCredential -> Credential
forall a b. Coercible a b => a -> b
coerce Credential -> ColdCommitteeCredential
PLA.ColdCommitteeCredential
deriving via PLA.Credential instance Arbitrary PLA.HotCommitteeCredential
deriving via PLA.Credential instance CoArbitrary PLA.HotCommitteeCredential
instance Function PLA.HotCommitteeCredential where
{-# INLINEABLE function #-}
function :: forall b.
(HotCommitteeCredential -> b) -> HotCommitteeCredential :-> b
function = (HotCommitteeCredential -> Credential)
-> (Credential -> HotCommitteeCredential)
-> (HotCommitteeCredential -> b)
-> HotCommitteeCredential :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap HotCommitteeCredential -> Credential
forall a b. Coercible a b => a -> b
coerce Credential -> HotCommitteeCredential
PLA.HotCommitteeCredential
deriving via PLA.Credential instance Arbitrary PLA.DRepCredential
deriving via PLA.Credential instance CoArbitrary PLA.DRepCredential
instance Function PLA.DRepCredential where
{-# INLINEABLE function #-}
function :: forall b. (DRepCredential -> b) -> DRepCredential :-> b
function = (DRepCredential -> Credential)
-> (Credential -> DRepCredential)
-> (DRepCredential -> b)
-> DRepCredential :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap DRepCredential -> Credential
forall a b. Coercible a b => a -> b
coerce Credential -> DRepCredential
PLA.DRepCredential
instance Arbitrary PLA.DRep where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen DRep
arbitrary =
[Gen DRep] -> Gen DRep
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ DRepCredential -> DRep
PLA.DRep (DRepCredential -> DRep) -> Gen DRepCredential -> Gen DRep
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen DRepCredential
forall a. Arbitrary a => Gen a
arbitrary
, DRep -> Gen DRep
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure DRep
PLA.DRepAlwaysAbstain
, DRep -> Gen DRep
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure DRep
PLA.DRepAlwaysNoConfidence
]
{-# INLINEABLE shrink #-}
shrink :: DRep -> [DRep]
shrink = \case
PLA.DRep DRepCredential
cred -> DRepCredential -> DRep
PLA.DRep (DRepCredential -> DRep) -> [DRepCredential] -> [DRep]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRepCredential -> [DRepCredential]
forall a. Arbitrary a => a -> [a]
shrink DRepCredential
cred
DRep
_ -> []
instance CoArbitrary PLA.DRep where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. DRep -> Gen b -> Gen b
coarbitrary = \case
PLA.DRep DRepCredential
cred -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRepCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRepCredential -> Gen b -> Gen b
coarbitrary DRepCredential
cred
DRep
PLA.DRepAlwaysAbstain -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int)
DRep
PLA.DRepAlwaysNoConfidence -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int)
instance Function PLA.DRep where
{-# INLINEABLE function #-}
function :: forall b. (DRep -> b) -> DRep :-> b
function = (DRep -> Maybe (Maybe DRepCredential))
-> (Maybe (Maybe DRepCredential) -> DRep)
-> (DRep -> b)
-> DRep :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap DRep -> Maybe (Maybe DRepCredential)
into Maybe (Maybe DRepCredential) -> DRep
outOf
where
into :: PLA.DRep -> Maybe (Maybe PLA.DRepCredential)
into :: DRep -> Maybe (Maybe DRepCredential)
into = \case
PLA.DRep DRepCredential
cred -> Maybe DRepCredential -> Maybe (Maybe DRepCredential)
forall a. a -> Maybe a
Just (DRepCredential -> Maybe DRepCredential
forall a. a -> Maybe a
Just DRepCredential
cred)
DRep
PLA.DRepAlwaysAbstain -> Maybe (Maybe DRepCredential)
forall a. Maybe a
Nothing
DRep
PLA.DRepAlwaysNoConfidence -> Maybe DRepCredential -> Maybe (Maybe DRepCredential)
forall a. a -> Maybe a
Just Maybe DRepCredential
forall a. Maybe a
Nothing
outOf :: Maybe (Maybe PLA.DRepCredential) -> PLA.DRep
outOf :: Maybe (Maybe DRepCredential) -> DRep
outOf = \case
Maybe (Maybe DRepCredential)
Nothing -> DRep
PLA.DRepAlwaysAbstain
Just Maybe DRepCredential
Nothing -> DRep
PLA.DRepAlwaysNoConfidence
Just (Just DRepCredential
cred) -> DRepCredential -> DRep
PLA.DRep DRepCredential
cred
instance Arbitrary PLA.Delegatee where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen Delegatee
arbitrary =
[Gen Delegatee] -> Gen Delegatee
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ PubKeyHash -> Delegatee
PLA.DelegStake (PubKeyHash -> Delegatee) -> Gen PubKeyHash -> Gen Delegatee
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen PubKeyHash
forall a. Arbitrary a => Gen a
arbitrary
, DRep -> Delegatee
PLA.DelegVote (DRep -> Delegatee) -> Gen DRep -> Gen Delegatee
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen DRep
forall a. Arbitrary a => Gen a
arbitrary
, PubKeyHash -> DRep -> Delegatee
PLA.DelegStakeVote (PubKeyHash -> DRep -> Delegatee)
-> Gen PubKeyHash -> Gen (DRep -> Delegatee)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen PubKeyHash
forall a. Arbitrary a => Gen a
arbitrary Gen (DRep -> Delegatee) -> Gen DRep -> Gen Delegatee
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen DRep
forall a. Arbitrary a => Gen a
arbitrary
]
{-# INLINEABLE shrink #-}
shrink :: Delegatee -> [Delegatee]
shrink = \case
PLA.DelegStake PubKeyHash
_ -> []
PLA.DelegVote DRep
drep -> DRep -> Delegatee
PLA.DelegVote (DRep -> Delegatee) -> [DRep] -> [Delegatee]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRep -> [DRep]
forall a. Arbitrary a => a -> [a]
shrink DRep
drep
PLA.DelegStakeVote PubKeyHash
pkh DRep
drep -> PubKeyHash -> DRep -> Delegatee
PLA.DelegStakeVote PubKeyHash
pkh (DRep -> Delegatee) -> [DRep] -> [Delegatee]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRep -> [DRep]
forall a. Arbitrary a => a -> [a]
shrink DRep
drep
instance CoArbitrary PLA.Delegatee where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. Delegatee -> Gen b -> Gen b
coarbitrary = \case
PLA.DelegStake PubKeyHash
pkh -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubKeyHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. PubKeyHash -> Gen b -> Gen b
coarbitrary PubKeyHash
pkh
PLA.DelegVote DRep
drep -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRep -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRep -> Gen b -> Gen b
coarbitrary DRep
drep
PLA.DelegStakeVote PubKeyHash
pkh DRep
drep -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubKeyHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. PubKeyHash -> Gen b -> Gen b
coarbitrary PubKeyHash
pkh (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRep -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRep -> Gen b -> Gen b
coarbitrary DRep
drep
instance Function PLA.Delegatee where
{-# INLINEABLE function #-}
function :: forall b. (Delegatee -> b) -> Delegatee :-> b
function = (Delegatee -> Either PubKeyHash (Either DRep (PubKeyHash, DRep)))
-> (Either PubKeyHash (Either DRep (PubKeyHash, DRep))
-> Delegatee)
-> (Delegatee -> b)
-> Delegatee :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Delegatee -> Either PubKeyHash (Either DRep (PubKeyHash, DRep))
into Either PubKeyHash (Either DRep (PubKeyHash, DRep)) -> Delegatee
outOf
where
into ::
PLA.Delegatee ->
Either PLA.PubKeyHash (Either PLA.DRep (PLA.PubKeyHash, PLA.DRep))
into :: Delegatee -> Either PubKeyHash (Either DRep (PubKeyHash, DRep))
into = \case
PLA.DelegStake PubKeyHash
pkh -> PubKeyHash -> Either PubKeyHash (Either DRep (PubKeyHash, DRep))
forall a b. a -> Either a b
Left PubKeyHash
pkh
PLA.DelegVote DRep
drep -> Either DRep (PubKeyHash, DRep)
-> Either PubKeyHash (Either DRep (PubKeyHash, DRep))
forall a b. b -> Either a b
Right (DRep -> Either DRep (PubKeyHash, DRep)
forall a b. a -> Either a b
Left DRep
drep)
PLA.DelegStakeVote PubKeyHash
pkh DRep
drep -> Either DRep (PubKeyHash, DRep)
-> Either PubKeyHash (Either DRep (PubKeyHash, DRep))
forall a b. b -> Either a b
Right ((PubKeyHash, DRep) -> Either DRep (PubKeyHash, DRep)
forall a b. b -> Either a b
Right (PubKeyHash
pkh, DRep
drep))
outOf ::
Either PLA.PubKeyHash (Either PLA.DRep (PLA.PubKeyHash, PLA.DRep)) ->
PLA.Delegatee
outOf :: Either PubKeyHash (Either DRep (PubKeyHash, DRep)) -> Delegatee
outOf = \case
Left PubKeyHash
pkh -> PubKeyHash -> Delegatee
PLA.DelegStake PubKeyHash
pkh
Right (Left DRep
drep) -> DRep -> Delegatee
PLA.DelegVote DRep
drep
Right (Right (PubKeyHash
pkh, DRep
drep)) -> PubKeyHash -> DRep -> Delegatee
PLA.DelegStakeVote PubKeyHash
pkh DRep
drep
instance Arbitrary PLA.TxCert where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen TxCert
arbitrary =
[Gen TxCert] -> Gen TxCert
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ Credential -> Maybe Lovelace -> TxCert
PLA.TxCertRegStaking (Credential -> Maybe Lovelace -> TxCert)
-> Gen Credential -> Gen (Maybe Lovelace -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary Gen (Maybe Lovelace -> TxCert)
-> Gen (Maybe Lovelace) -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen (Maybe Lovelace)
forall a. Arbitrary a => Gen a
arbitrary
, Credential -> Maybe Lovelace -> TxCert
PLA.TxCertUnRegStaking (Credential -> Maybe Lovelace -> TxCert)
-> Gen Credential -> Gen (Maybe Lovelace -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary Gen (Maybe Lovelace -> TxCert)
-> Gen (Maybe Lovelace) -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen (Maybe Lovelace)
forall a. Arbitrary a => Gen a
arbitrary
, Credential -> Delegatee -> TxCert
PLA.TxCertDelegStaking (Credential -> Delegatee -> TxCert)
-> Gen Credential -> Gen (Delegatee -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary Gen (Delegatee -> TxCert) -> Gen Delegatee -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Delegatee
forall a. Arbitrary a => Gen a
arbitrary
, Credential -> Delegatee -> Lovelace -> TxCert
PLA.TxCertRegDeleg (Credential -> Delegatee -> Lovelace -> TxCert)
-> Gen Credential -> Gen (Delegatee -> Lovelace -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary Gen (Delegatee -> Lovelace -> TxCert)
-> Gen Delegatee -> Gen (Lovelace -> TxCert)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Delegatee
forall a. Arbitrary a => Gen a
arbitrary Gen (Lovelace -> TxCert) -> Gen Lovelace -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Lovelace
forall a. Arbitrary a => Gen a
arbitrary
, DRepCredential -> Lovelace -> TxCert
PLA.TxCertRegDRep (DRepCredential -> Lovelace -> TxCert)
-> Gen DRepCredential -> Gen (Lovelace -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen DRepCredential
forall a. Arbitrary a => Gen a
arbitrary Gen (Lovelace -> TxCert) -> Gen Lovelace -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Lovelace
forall a. Arbitrary a => Gen a
arbitrary
, DRepCredential -> TxCert
PLA.TxCertUpdateDRep (DRepCredential -> TxCert) -> Gen DRepCredential -> Gen TxCert
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen DRepCredential
forall a. Arbitrary a => Gen a
arbitrary
, DRepCredential -> Lovelace -> TxCert
PLA.TxCertUnRegDRep (DRepCredential -> Lovelace -> TxCert)
-> Gen DRepCredential -> Gen (Lovelace -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen DRepCredential
forall a. Arbitrary a => Gen a
arbitrary Gen (Lovelace -> TxCert) -> Gen Lovelace -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Lovelace
forall a. Arbitrary a => Gen a
arbitrary
, PubKeyHash -> PubKeyHash -> TxCert
PLA.TxCertPoolRegister (PubKeyHash -> PubKeyHash -> TxCert)
-> Gen PubKeyHash -> Gen (PubKeyHash -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen PubKeyHash
forall a. Arbitrary a => Gen a
arbitrary Gen (PubKeyHash -> TxCert) -> Gen PubKeyHash -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen PubKeyHash
forall a. Arbitrary a => Gen a
arbitrary
,
PubKeyHash -> Integer -> TxCert
PLA.TxCertPoolRetire (PubKeyHash -> Integer -> TxCert)
-> Gen PubKeyHash -> Gen (Integer -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen PubKeyHash
forall a. Arbitrary a => Gen a
arbitrary Gen (Integer -> TxCert) -> Gen Integer -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Positive Integer -> Integer
forall a. Positive a -> a
getPositive (Positive Integer -> Integer)
-> Gen (Positive Integer) -> Gen Integer
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Positive Integer)
forall a. Arbitrary a => Gen a
arbitrary)
, ColdCommitteeCredential -> HotCommitteeCredential -> TxCert
PLA.TxCertAuthHotCommittee (ColdCommitteeCredential -> HotCommitteeCredential -> TxCert)
-> Gen ColdCommitteeCredential
-> Gen (HotCommitteeCredential -> TxCert)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ColdCommitteeCredential
forall a. Arbitrary a => Gen a
arbitrary Gen (HotCommitteeCredential -> TxCert)
-> Gen HotCommitteeCredential -> Gen TxCert
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen HotCommitteeCredential
forall a. Arbitrary a => Gen a
arbitrary
, ColdCommitteeCredential -> TxCert
PLA.TxCertResignColdCommittee (ColdCommitteeCredential -> TxCert)
-> Gen ColdCommitteeCredential -> Gen TxCert
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ColdCommitteeCredential
forall a. Arbitrary a => Gen a
arbitrary
]
{-# INLINEABLE shrink #-}
shrink :: TxCert -> [TxCert]
shrink = \case
PLA.TxCertRegStaking Credential
cred Maybe Lovelace
mLovelace ->
Credential -> Maybe Lovelace -> TxCert
PLA.TxCertRegStaking (Credential -> Maybe Lovelace -> TxCert)
-> [Credential] -> [Maybe Lovelace -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
cred [Maybe Lovelace -> TxCert] -> [Maybe Lovelace] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Maybe Lovelace -> [Maybe Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Maybe Lovelace
mLovelace
PLA.TxCertUnRegStaking Credential
cred Maybe Lovelace
mLovelace ->
Credential -> Maybe Lovelace -> TxCert
PLA.TxCertUnRegStaking (Credential -> Maybe Lovelace -> TxCert)
-> [Credential] -> [Maybe Lovelace -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
cred [Maybe Lovelace -> TxCert] -> [Maybe Lovelace] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Maybe Lovelace -> [Maybe Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Maybe Lovelace
mLovelace
PLA.TxCertDelegStaking Credential
cred Delegatee
deleg ->
Credential -> Delegatee -> TxCert
PLA.TxCertDelegStaking (Credential -> Delegatee -> TxCert)
-> [Credential] -> [Delegatee -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
cred [Delegatee -> TxCert] -> [Delegatee] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Delegatee -> [Delegatee]
forall a. Arbitrary a => a -> [a]
shrink Delegatee
deleg
PLA.TxCertRegDeleg Credential
cred Delegatee
deleg Lovelace
lovelace ->
Credential -> Delegatee -> Lovelace -> TxCert
PLA.TxCertRegDeleg (Credential -> Delegatee -> Lovelace -> TxCert)
-> [Credential] -> [Delegatee -> Lovelace -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
cred [Delegatee -> Lovelace -> TxCert]
-> [Delegatee] -> [Lovelace -> TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Delegatee -> [Delegatee]
forall a. Arbitrary a => a -> [a]
shrink Delegatee
deleg [Lovelace -> TxCert] -> [Lovelace] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Lovelace -> [Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Lovelace
lovelace
PLA.TxCertRegDRep DRepCredential
drepCred Lovelace
lovelace ->
DRepCredential -> Lovelace -> TxCert
PLA.TxCertRegDRep (DRepCredential -> Lovelace -> TxCert)
-> [DRepCredential] -> [Lovelace -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRepCredential -> [DRepCredential]
forall a. Arbitrary a => a -> [a]
shrink DRepCredential
drepCred [Lovelace -> TxCert] -> [Lovelace] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Lovelace -> [Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Lovelace
lovelace
PLA.TxCertUpdateDRep DRepCredential
drepCred -> DRepCredential -> TxCert
PLA.TxCertUpdateDRep (DRepCredential -> TxCert) -> [DRepCredential] -> [TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRepCredential -> [DRepCredential]
forall a. Arbitrary a => a -> [a]
shrink DRepCredential
drepCred
PLA.TxCertUnRegDRep DRepCredential
drepCred Lovelace
lovelace ->
DRepCredential -> Lovelace -> TxCert
PLA.TxCertUnRegDRep (DRepCredential -> Lovelace -> TxCert)
-> [DRepCredential] -> [Lovelace -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRepCredential -> [DRepCredential]
forall a. Arbitrary a => a -> [a]
shrink DRepCredential
drepCred [Lovelace -> TxCert] -> [Lovelace] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Lovelace -> [Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Lovelace
lovelace
PLA.TxCertPoolRegister PubKeyHash
_ PubKeyHash
_ -> []
PLA.TxCertPoolRetire PubKeyHash
pkh Integer
epoch ->
PubKeyHash -> Integer -> TxCert
PLA.TxCertPoolRetire PubKeyHash
pkh (Integer -> TxCert)
-> (Positive Integer -> Integer) -> Positive Integer -> TxCert
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Positive Integer -> Integer
forall a. Positive a -> a
getPositive (Positive Integer -> TxCert) -> [Positive Integer] -> [TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Positive Integer -> [Positive Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> Positive Integer
forall a. a -> Positive a
Positive Integer
epoch)
PLA.TxCertAuthHotCommittee ColdCommitteeCredential
cold HotCommitteeCredential
hot ->
ColdCommitteeCredential -> HotCommitteeCredential -> TxCert
PLA.TxCertAuthHotCommittee (ColdCommitteeCredential -> HotCommitteeCredential -> TxCert)
-> [ColdCommitteeCredential] -> [HotCommitteeCredential -> TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> ColdCommitteeCredential -> [ColdCommitteeCredential]
forall a. Arbitrary a => a -> [a]
shrink ColdCommitteeCredential
cold [HotCommitteeCredential -> TxCert]
-> [HotCommitteeCredential] -> [TxCert]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> HotCommitteeCredential -> [HotCommitteeCredential]
forall a. Arbitrary a => a -> [a]
shrink HotCommitteeCredential
hot
PLA.TxCertResignColdCommittee ColdCommitteeCredential
cold -> ColdCommitteeCredential -> TxCert
PLA.TxCertResignColdCommittee (ColdCommitteeCredential -> TxCert)
-> [ColdCommitteeCredential] -> [TxCert]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> ColdCommitteeCredential -> [ColdCommitteeCredential]
forall a. Arbitrary a => a -> [a]
shrink ColdCommitteeCredential
cold
instance CoArbitrary PLA.TxCert where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. TxCert -> Gen b -> Gen b
coarbitrary = \case
PLA.TxCertRegStaking Credential
cred Maybe Lovelace
mLovelace ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Credential -> Gen b -> Gen b
coarbitrary Credential
cred (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Lovelace -> Gen b -> Gen b
forall b. Maybe Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe Lovelace
mLovelace
PLA.TxCertUnRegStaking Credential
cred Maybe Lovelace
mLovelace ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Credential -> Gen b -> Gen b
coarbitrary Credential
cred (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe Lovelace -> Gen b -> Gen b
forall b. Maybe Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe Lovelace
mLovelace
PLA.TxCertDelegStaking Credential
cred Delegatee
deleg ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Credential -> Gen b -> Gen b
coarbitrary Credential
cred (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Delegatee -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Delegatee -> Gen b -> Gen b
coarbitrary Delegatee
deleg
PLA.TxCertRegDeleg Credential
cred Delegatee
deleg Lovelace
lovelace ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
3 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Credential -> Gen b -> Gen b
coarbitrary Credential
cred (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Delegatee -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Delegatee -> Gen b -> Gen b
coarbitrary Delegatee
deleg (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Lovelace -> Gen b -> Gen b
coarbitrary Lovelace
lovelace
PLA.TxCertRegDRep DRepCredential
drepCred Lovelace
lovelace ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
4 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRepCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRepCredential -> Gen b -> Gen b
coarbitrary DRepCredential
drepCred (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Lovelace -> Gen b -> Gen b
coarbitrary Lovelace
lovelace
PLA.TxCertUpdateDRep DRepCredential
drepCred ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
5 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRepCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRepCredential -> Gen b -> Gen b
coarbitrary DRepCredential
drepCred
PLA.TxCertUnRegDRep DRepCredential
drepCred Lovelace
lovelace ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
6 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRepCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRepCredential -> Gen b -> Gen b
coarbitrary DRepCredential
drepCred (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Lovelace -> Gen b -> Gen b
coarbitrary Lovelace
lovelace
PLA.TxCertPoolRegister PubKeyHash
pkh PubKeyHash
pkh' ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
7 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubKeyHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. PubKeyHash -> Gen b -> Gen b
coarbitrary PubKeyHash
pkh (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubKeyHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. PubKeyHash -> Gen b -> Gen b
coarbitrary PubKeyHash
pkh'
PLA.TxCertPoolRetire PubKeyHash
pkh Integer
epoch ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
8 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubKeyHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. PubKeyHash -> Gen b -> Gen b
coarbitrary PubKeyHash
pkh (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
epoch
PLA.TxCertAuthHotCommittee ColdCommitteeCredential
cold HotCommitteeCredential
hot ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
9 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColdCommitteeCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. ColdCommitteeCredential -> Gen b -> Gen b
coarbitrary ColdCommitteeCredential
cold (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HotCommitteeCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. HotCommitteeCredential -> Gen b -> Gen b
coarbitrary HotCommitteeCredential
hot
PLA.TxCertResignColdCommittee ColdCommitteeCredential
cold ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
10 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColdCommitteeCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. ColdCommitteeCredential -> Gen b -> Gen b
coarbitrary ColdCommitteeCredential
cold
instance Function PLA.TxCert where
{-# INLINEABLE function #-}
function :: forall b. (TxCert -> b) -> TxCert :-> b
function = (TxCert
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))))
-> (Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
-> TxCert)
-> (TxCert -> b)
-> TxCert :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap TxCert
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
into Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
-> TxCert
outOf
where
into ::
PLA.TxCert ->
Either
(PLA.Credential, Maybe PLA.Lovelace)
( Either
(PLA.Credential, Maybe PLA.Lovelace)
( Either
(PLA.Credential, PLA.Delegatee)
( Either
(PLA.Credential, PLA.Delegatee, PLA.Lovelace)
( Either
(PLA.DRepCredential, PLA.Lovelace)
( Either
PLA.DRepCredential
( Either
(PLA.DRepCredential, PLA.Lovelace)
( Either
(PLA.PubKeyHash, PLA.PubKeyHash)
( Either
(PLA.PubKeyHash, Integer)
( Either (PLA.ColdCommitteeCredential, PLA.HotCommitteeCredential) PLA.ColdCommitteeCredential
)
)
)
)
)
)
)
)
)
into :: TxCert
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
into = \case
PLA.TxCertRegStaking Credential
cred Maybe Lovelace
mLovelace ->
(Credential, Maybe Lovelace)
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. a -> Either a b
Left (Credential
cred, Maybe Lovelace
mLovelace)
PLA.TxCertUnRegStaking Credential
cred Maybe Lovelace
mLovelace ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right ((Credential, Maybe Lovelace)
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. a -> Either a b
Left (Credential
cred, Maybe Lovelace
mLovelace))
PLA.TxCertDelegStaking Credential
cred Delegatee
deleg ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right ((Credential, Delegatee)
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. a -> Either a b
Left (Credential
cred, Delegatee
deleg)))
PLA.TxCertRegDeleg Credential
cred Delegatee
deleg Lovelace
lovelace ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right ((Credential, Delegatee, Lovelace)
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. a -> Either a b
Left (Credential
cred, Delegatee
deleg, Lovelace
lovelace))))
PLA.TxCertRegDRep DRepCredential
drepCred Lovelace
lovelace ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right ((DRepCredential, Lovelace)
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. a -> Either a b
Left (DRepCredential
drepCred, Lovelace
lovelace)))))
PLA.TxCertUpdateDRep DRepCredential
drepCred ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right (Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. b -> Either a b
Right (DRepCredential
-> Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
forall a b. a -> Either a b
Left DRepCredential
drepCred)))))
PLA.TxCertUnRegDRep DRepCredential
drepCred Lovelace
lovelace ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right (Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
-> Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
forall a b. b -> Either a b
Right ((DRepCredential, Lovelace)
-> Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
forall a b. a -> Either a b
Left (DRepCredential
drepCred, Lovelace
lovelace)))))))
PLA.TxCertPoolRegister PubKeyHash
pkh PubKeyHash
pkh' ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right (Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
-> Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
-> Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
forall a b. b -> Either a b
Right ((PubKeyHash, PubKeyHash)
-> Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
forall a b. a -> Either a b
Left (PubKeyHash
pkh, PubKeyHash
pkh'))))))))
PLA.TxCertPoolRetire PubKeyHash
pkh Integer
epoch ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right (Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
-> Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
-> Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)
-> Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
forall a b. b -> Either a b
Right ((PubKeyHash, Integer)
-> Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)
forall a b. a -> Either a b
Left (PubKeyHash
pkh, Integer
epoch)))))))))
PLA.TxCertAuthHotCommittee ColdCommitteeCredential
hot HotCommitteeCredential
cold ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right (Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
-> Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
-> Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)
-> Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
forall a b. b -> Either a b
Right (Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential
-> Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)
forall a b. b -> Either a b
Right ((ColdCommitteeCredential, HotCommitteeCredential)
-> Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential
forall a b. a -> Either a b
Left (ColdCommitteeCredential
hot, HotCommitteeCredential
cold))))))))))
PLA.TxCertResignColdCommittee ColdCommitteeCredential
cold ->
Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
-> Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))))
forall a b. b -> Either a b
Right (Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
-> Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
-> Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))))
forall a b. b -> Either a b
Right (Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
-> Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))
forall a b. b -> Either a b
Right (Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
-> Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
-> Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))
forall a b. b -> Either a b
Right (Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)
-> Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential))
forall a b. b -> Either a b
Right (Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential
-> Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)
forall a b. b -> Either a b
Right (ColdCommitteeCredential
-> Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential
forall a b. b -> Either a b
Right ColdCommitteeCredential
cold)))))))))
outOf ::
Either
(PLA.Credential, Maybe PLA.Lovelace)
( Either
(PLA.Credential, Maybe PLA.Lovelace)
( Either
(PLA.Credential, PLA.Delegatee)
( Either
(PLA.Credential, PLA.Delegatee, PLA.Lovelace)
( Either
(PLA.DRepCredential, PLA.Lovelace)
( Either
PLA.DRepCredential
( Either
(PLA.DRepCredential, PLA.Lovelace)
( Either
(PLA.PubKeyHash, PLA.PubKeyHash)
( Either
(PLA.PubKeyHash, Integer)
( Either (PLA.ColdCommitteeCredential, PLA.HotCommitteeCredential) PLA.ColdCommitteeCredential
)
)
)
)
)
)
)
)
) ->
PLA.TxCert
outOf :: Either
(Credential, Maybe Lovelace)
(Either
(Credential, Maybe Lovelace)
(Either
(Credential, Delegatee)
(Either
(Credential, Delegatee, Lovelace)
(Either
(DRepCredential, Lovelace)
(Either
DRepCredential
(Either
(DRepCredential, Lovelace)
(Either
(PubKeyHash, PubKeyHash)
(Either
(PubKeyHash, Integer)
(Either
(ColdCommitteeCredential, HotCommitteeCredential)
ColdCommitteeCredential)))))))))
-> TxCert
outOf = \case
Left (Credential
cred, Maybe Lovelace
mLovelace) ->
Credential -> Maybe Lovelace -> TxCert
PLA.TxCertRegStaking Credential
cred Maybe Lovelace
mLovelace
Right (Left (Credential
cred, Maybe Lovelace
mLovelace)) ->
Credential -> Maybe Lovelace -> TxCert
PLA.TxCertUnRegStaking Credential
cred Maybe Lovelace
mLovelace
Right (Right (Left (Credential
cred, Delegatee
deleg))) ->
Credential -> Delegatee -> TxCert
PLA.TxCertDelegStaking Credential
cred Delegatee
deleg
Right (Right (Right (Left (Credential
cred, Delegatee
deleg, Lovelace
lovelace)))) ->
Credential -> Delegatee -> Lovelace -> TxCert
PLA.TxCertRegDeleg Credential
cred Delegatee
deleg Lovelace
lovelace
Right (Right (Right (Right (Left (DRepCredential
drepCred, Lovelace
lovelace))))) ->
DRepCredential -> Lovelace -> TxCert
PLA.TxCertRegDRep DRepCredential
drepCred Lovelace
lovelace
Right (Right (Right (Right (Right (Left DRepCredential
drepCred))))) ->
DRepCredential -> TxCert
PLA.TxCertUpdateDRep DRepCredential
drepCred
Right (Right (Right (Right (Right (Right (Left (DRepCredential
drepCred, Lovelace
lovelace))))))) ->
DRepCredential -> Lovelace -> TxCert
PLA.TxCertUnRegDRep DRepCredential
drepCred Lovelace
lovelace
Right (Right (Right (Right (Right (Right (Right (Left (PubKeyHash
pkh, PubKeyHash
pkh')))))))) ->
PubKeyHash -> PubKeyHash -> TxCert
PLA.TxCertPoolRegister PubKeyHash
pkh PubKeyHash
pkh'
Right (Right (Right (Right (Right (Right (Right (Right (Left (PubKeyHash
pkh, Integer
epoch))))))))) ->
PubKeyHash -> Integer -> TxCert
PLA.TxCertPoolRetire PubKeyHash
pkh Integer
epoch
Right (Right (Right (Right (Right (Right (Right (Right (Right (Left (ColdCommitteeCredential
hot, HotCommitteeCredential
cold)))))))))) ->
ColdCommitteeCredential -> HotCommitteeCredential -> TxCert
PLA.TxCertAuthHotCommittee ColdCommitteeCredential
hot HotCommitteeCredential
cold
Right (Right (Right (Right (Right (Right (Right (Right (Right (Right ColdCommitteeCredential
cold))))))))) ->
ColdCommitteeCredential -> TxCert
PLA.TxCertResignColdCommittee ColdCommitteeCredential
cold
instance Arbitrary PLA.Voter where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen Voter
arbitrary =
[Gen Voter] -> Gen Voter
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ HotCommitteeCredential -> Voter
PLA.CommitteeVoter (HotCommitteeCredential -> Voter)
-> Gen HotCommitteeCredential -> Gen Voter
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen HotCommitteeCredential
forall a. Arbitrary a => Gen a
arbitrary
, DRepCredential -> Voter
PLA.DRepVoter (DRepCredential -> Voter) -> Gen DRepCredential -> Gen Voter
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen DRepCredential
forall a. Arbitrary a => Gen a
arbitrary
, PubKeyHash -> Voter
PLA.StakePoolVoter (PubKeyHash -> Voter) -> Gen PubKeyHash -> Gen Voter
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen PubKeyHash
forall a. Arbitrary a => Gen a
arbitrary
]
{-# INLINEABLE shrink #-}
shrink :: Voter -> [Voter]
shrink = \case
PLA.CommitteeVoter HotCommitteeCredential
hcc -> HotCommitteeCredential -> Voter
PLA.CommitteeVoter (HotCommitteeCredential -> Voter)
-> [HotCommitteeCredential] -> [Voter]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> HotCommitteeCredential -> [HotCommitteeCredential]
forall a. Arbitrary a => a -> [a]
shrink HotCommitteeCredential
hcc
PLA.DRepVoter DRepCredential
drepCred -> DRepCredential -> Voter
PLA.DRepVoter (DRepCredential -> Voter) -> [DRepCredential] -> [Voter]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> DRepCredential -> [DRepCredential]
forall a. Arbitrary a => a -> [a]
shrink DRepCredential
drepCred
Voter
_ -> []
instance CoArbitrary PLA.Voter where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. Voter -> Gen b -> Gen b
coarbitrary = \case
PLA.CommitteeVoter HotCommitteeCredential
hcc -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HotCommitteeCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. HotCommitteeCredential -> Gen b -> Gen b
coarbitrary HotCommitteeCredential
hcc
PLA.DRepVoter DRepCredential
drepCred -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DRepCredential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. DRepCredential -> Gen b -> Gen b
coarbitrary DRepCredential
drepCred
PLA.StakePoolVoter PubKeyHash
pkh -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PubKeyHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. PubKeyHash -> Gen b -> Gen b
coarbitrary PubKeyHash
pkh
instance Function PLA.Voter where
{-# INLINEABLE function #-}
function :: forall b. (Voter -> b) -> Voter :-> b
function = (Voter
-> Either
HotCommitteeCredential (Either DRepCredential PubKeyHash))
-> (Either
HotCommitteeCredential (Either DRepCredential PubKeyHash)
-> Voter)
-> (Voter -> b)
-> Voter :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Voter
-> Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
into Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
-> Voter
outOf
where
into ::
PLA.Voter ->
Either PLA.HotCommitteeCredential (Either PLA.DRepCredential PLA.PubKeyHash)
into :: Voter
-> Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
into = \case
PLA.CommitteeVoter HotCommitteeCredential
hcc -> HotCommitteeCredential
-> Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
forall a b. a -> Either a b
Left HotCommitteeCredential
hcc
PLA.DRepVoter DRepCredential
drepCred -> Either DRepCredential PubKeyHash
-> Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
forall a b. b -> Either a b
Right (DRepCredential -> Either DRepCredential PubKeyHash
forall a b. a -> Either a b
Left DRepCredential
drepCred)
PLA.StakePoolVoter PubKeyHash
pkh -> Either DRepCredential PubKeyHash
-> Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
forall a b. b -> Either a b
Right (PubKeyHash -> Either DRepCredential PubKeyHash
forall a b. b -> Either a b
Right PubKeyHash
pkh)
outOf ::
Either PLA.HotCommitteeCredential (Either PLA.DRepCredential PLA.PubKeyHash) ->
PLA.Voter
outOf :: Either HotCommitteeCredential (Either DRepCredential PubKeyHash)
-> Voter
outOf = \case
Left HotCommitteeCredential
hcc -> HotCommitteeCredential -> Voter
PLA.CommitteeVoter HotCommitteeCredential
hcc
Right (Left DRepCredential
drepCred) -> DRepCredential -> Voter
PLA.DRepVoter DRepCredential
drepCred
Right (Right PubKeyHash
pkh) -> PubKeyHash -> Voter
PLA.StakePoolVoter PubKeyHash
pkh
instance Arbitrary PLA.Vote where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen Vote
arbitrary = [Vote] -> Gen Vote
forall a. HasCallStack => [a] -> Gen a
elements [Vote
PLA.VoteNo, Vote
PLA.VoteYes, Vote
PLA.Abstain]
instance CoArbitrary PLA.Vote where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. Vote -> Gen b -> Gen b
coarbitrary = \case
Vote
PLA.VoteNo -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int)
Vote
PLA.VoteYes -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int)
Vote
PLA.Abstain -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int)
instance Function PLA.Vote where
{-# INLINEABLE function #-}
function :: forall b. (Vote -> b) -> Vote :-> b
function = (Vote -> Int) -> (Int -> Vote) -> (Vote -> b) -> Vote :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Vote -> Int
into Int -> Vote
outOf
where
into :: PLA.Vote -> Int
into :: Vote -> Int
into = \case
Vote
PLA.VoteNo -> Int
0
Vote
PLA.VoteYes -> Int
1
Vote
_ -> Int
2
outOf :: Int -> PLA.Vote
outOf :: Int -> Vote
outOf = \case
Int
0 -> Vote
PLA.VoteNo
Int
1 -> Vote
PLA.VoteYes
Int
_ -> Vote
PLA.Abstain
deriving via Blake2b256Hash instance Arbitrary PLA.TxId
deriving via Blake2b256Hash instance CoArbitrary PLA.TxId
instance Function PLA.TxId where
{-# INLINEABLE function #-}
function :: forall b. (TxId -> b) -> TxId :-> b
function = (TxId -> BuiltinByteString)
-> (BuiltinByteString -> TxId) -> (TxId -> b) -> TxId :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap TxId -> BuiltinByteString
forall a b. Coercible a b => a -> b
coerce BuiltinByteString -> TxId
PLA.TxId
instance Arbitrary PLA.GovernanceActionId where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen GovernanceActionId
arbitrary =
TxId -> Integer -> GovernanceActionId
PLA.GovernanceActionId
(TxId -> Integer -> GovernanceActionId)
-> Gen TxId -> Gen (Integer -> GovernanceActionId)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxId
forall a. Arbitrary a => Gen a
arbitrary
Gen (Integer -> GovernanceActionId)
-> Gen Integer -> Gen GovernanceActionId
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> Integer)
-> Gen (NonNegative Integer) -> Gen Integer
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary)
{-# INLINEABLE shrink #-}
shrink :: GovernanceActionId -> [GovernanceActionId]
shrink (PLA.GovernanceActionId TxId
tid Integer
ix) =
TxId -> Integer -> GovernanceActionId
PLA.GovernanceActionId TxId
tid (Integer -> GovernanceActionId)
-> (NonNegative Integer -> Integer)
-> NonNegative Integer
-> GovernanceActionId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> GovernanceActionId)
-> [NonNegative Integer] -> [GovernanceActionId]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
ix)
instance CoArbitrary PLA.GovernanceActionId where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. GovernanceActionId -> Gen b -> Gen b
coarbitrary (PLA.GovernanceActionId TxId
tid Integer
ix) =
TxId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. TxId -> Gen b -> Gen b
coarbitrary TxId
tid (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
ix
instance Function PLA.GovernanceActionId where
{-# INLINEABLE function #-}
function :: forall b. (GovernanceActionId -> b) -> GovernanceActionId :-> b
function = (GovernanceActionId -> (TxId, Integer))
-> ((TxId, Integer) -> GovernanceActionId)
-> (GovernanceActionId -> b)
-> GovernanceActionId :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap (\(PLA.GovernanceActionId TxId
tid Integer
ix) -> (TxId
tid, Integer
ix)) ((TxId -> Integer -> GovernanceActionId)
-> (TxId, Integer) -> GovernanceActionId
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry TxId -> Integer -> GovernanceActionId
PLA.GovernanceActionId)
instance Arbitrary PLA.Committee where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen Committee
arbitrary = do
Map ColdCommitteeCredential Integer
committee <- Gen Integer -> Gen (Map ColdCommitteeCredential Integer)
forall a. Gen a -> Gen (Map ColdCommitteeCredential a)
forall (f :: Type -> Type) a. Arbitrary1 f => Gen a -> Gen (f a)
liftArbitrary (Positive Integer -> Integer
forall a. Positive a -> a
getPositive (Positive Integer -> Integer)
-> Gen (Positive Integer) -> Gen Integer
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Positive Integer)
forall a. Arbitrary a => Gen a
arbitrary)
Int
num <- (Int, Int) -> Gen Int
chooseInt (Int
1, Int
100)
let quorum :: Rational
quorum = Integer -> Integer -> Rational
Ratio.unsafeRatio (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
num) Integer
100
Committee -> Gen Committee
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Committee -> Gen Committee)
-> (Rational -> Committee) -> Rational -> Gen Committee
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map ColdCommitteeCredential Integer -> Rational -> Committee
PLA.Committee Map ColdCommitteeCredential Integer
committee (Rational -> Gen Committee) -> Rational -> Gen Committee
forall a b. (a -> b) -> a -> b
$ Rational
quorum
{-# INLINEABLE shrink #-}
shrink :: Committee -> [Committee]
shrink (PLA.Committee Map ColdCommitteeCredential Integer
committee Rational
quorum) = do
Map ColdCommitteeCredential Integer
committee' <- (Integer -> [Integer])
-> Map ColdCommitteeCredential Integer
-> [Map ColdCommitteeCredential Integer]
forall a.
(a -> [a])
-> Map ColdCommitteeCredential a -> [Map ColdCommitteeCredential a]
forall (f :: Type -> Type) a.
Arbitrary1 f =>
(a -> [a]) -> f a -> [f a]
liftShrink ((Positive Integer -> Integer) -> [Positive Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Positive Integer -> Integer
forall a. Positive a -> a
getPositive ([Positive Integer] -> [Integer])
-> (Integer -> [Positive Integer]) -> Integer -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Positive Integer -> [Positive Integer]
forall a. Arbitrary a => a -> [a]
shrink (Positive Integer -> [Positive Integer])
-> (Integer -> Positive Integer) -> Integer -> [Positive Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Positive Integer
forall a. a -> Positive a
Positive) Map ColdCommitteeCredential Integer
committee
Bool -> [()]
forall (f :: Type -> Type). Alternative f => Bool -> f ()
guard (Bool -> Bool
not (Bool -> Bool)
-> (Map ColdCommitteeCredential Integer -> Bool)
-> Map ColdCommitteeCredential Integer
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map ColdCommitteeCredential Integer -> Bool
forall k v. Map k v -> Bool
AssocMap.null (Map ColdCommitteeCredential Integer -> Bool)
-> Map ColdCommitteeCredential Integer -> Bool
forall a b. (a -> b) -> a -> b
$ Map ColdCommitteeCredential Integer
committee')
Committee -> [Committee]
forall a. a -> [a]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Committee -> [Committee])
-> (Rational -> Committee) -> Rational -> [Committee]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map ColdCommitteeCredential Integer -> Rational -> Committee
PLA.Committee Map ColdCommitteeCredential Integer
committee' (Rational -> [Committee]) -> Rational -> [Committee]
forall a b. (a -> b) -> a -> b
$ Rational
quorum
instance CoArbitrary PLA.Committee where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. Committee -> Gen b -> Gen b
coarbitrary (PLA.Committee Map ColdCommitteeCredential Integer
committee Rational
quorum) =
Map ColdCommitteeCredential Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Map ColdCommitteeCredential Integer -> Gen b -> Gen b
coarbitrary Map ColdCommitteeCredential Integer
committee
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Rational -> Integer
Ratio.numerator Rational
quorum)
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Rational -> Integer
Ratio.denominator Rational
quorum)
instance Function PLA.Committee where
{-# INLINEABLE function #-}
function :: forall b. (Committee -> b) -> Committee :-> b
function = (Committee
-> (Map ColdCommitteeCredential Integer, Integer, Integer))
-> ((Map ColdCommitteeCredential Integer, Integer, Integer)
-> Committee)
-> (Committee -> b)
-> Committee :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Committee
-> (Map ColdCommitteeCredential Integer, Integer, Integer)
into (Map ColdCommitteeCredential Integer, Integer, Integer)
-> Committee
outOf
where
into ::
PLA.Committee ->
(PLA.Map PLA.ColdCommitteeCredential Integer, Integer, Integer)
into :: Committee
-> (Map ColdCommitteeCredential Integer, Integer, Integer)
into (PLA.Committee Map ColdCommitteeCredential Integer
committee Rational
quorum) =
(Map ColdCommitteeCredential Integer
committee, Rational -> Integer
Ratio.numerator Rational
quorum, Rational -> Integer
Ratio.denominator Rational
quorum)
outOf ::
(PLA.Map PLA.ColdCommitteeCredential Integer, Integer, Integer) ->
PLA.Committee
outOf :: (Map ColdCommitteeCredential Integer, Integer, Integer)
-> Committee
outOf (Map ColdCommitteeCredential Integer
committee, Integer
num, Integer
den) =
Map ColdCommitteeCredential Integer -> Rational -> Committee
PLA.Committee Map ColdCommitteeCredential Integer
committee (Rational -> Committee)
-> (Integer -> Rational) -> Integer -> Committee
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Integer -> Rational
Ratio.unsafeRatio Integer
num (Integer -> Committee) -> Integer -> Committee
forall a b. (a -> b) -> a -> b
$ Integer
den
deriving via (Maybe PLA.ScriptHash) instance Arbitrary PLA.Constitution
deriving via (Maybe PLA.ScriptHash) instance CoArbitrary PLA.Constitution
instance Function PLA.Constitution where
{-# INLINEABLE function #-}
function :: forall b. (Constitution -> b) -> Constitution :-> b
function = (Constitution -> Maybe ScriptHash)
-> (Maybe ScriptHash -> Constitution)
-> (Constitution -> b)
-> Constitution :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap Constitution -> Maybe ScriptHash
forall a b. Coercible a b => a -> b
coerce Maybe ScriptHash -> Constitution
PLA.Constitution
instance Arbitrary PLA.ProtocolVersion where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen ProtocolVersion
arbitrary = do
NonNegative Integer
major <- Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary
NonNegative Integer
minor <- Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary
ProtocolVersion -> Gen ProtocolVersion
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (ProtocolVersion -> Gen ProtocolVersion)
-> (Integer -> ProtocolVersion) -> Integer -> Gen ProtocolVersion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Integer -> ProtocolVersion
PLA.ProtocolVersion Integer
major (Integer -> Gen ProtocolVersion) -> Integer -> Gen ProtocolVersion
forall a b. (a -> b) -> a -> b
$ Integer
minor
{-# INLINEABLE shrink #-}
shrink :: ProtocolVersion -> [ProtocolVersion]
shrink (PLA.ProtocolVersion Integer
major Integer
minor) = do
NonNegative Integer
major' <- NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
major)
NonNegative Integer
minor' <- NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
minor)
ProtocolVersion -> [ProtocolVersion]
forall a. a -> [a]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (ProtocolVersion -> [ProtocolVersion])
-> (Integer -> ProtocolVersion) -> Integer -> [ProtocolVersion]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Integer -> ProtocolVersion
PLA.ProtocolVersion Integer
major' (Integer -> [ProtocolVersion]) -> Integer -> [ProtocolVersion]
forall a b. (a -> b) -> a -> b
$ Integer
minor'
instance CoArbitrary PLA.ProtocolVersion where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. ProtocolVersion -> Gen b -> Gen b
coarbitrary (PLA.ProtocolVersion Integer
major Integer
minor) =
Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
major (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
minor
instance Function PLA.ProtocolVersion where
{-# INLINEABLE function #-}
function :: forall b. (ProtocolVersion -> b) -> ProtocolVersion :-> b
function =
(ProtocolVersion -> (Integer, Integer))
-> ((Integer, Integer) -> ProtocolVersion)
-> (ProtocolVersion -> b)
-> ProtocolVersion :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap
(\(PLA.ProtocolVersion Integer
maj' Integer
min') -> (Integer
maj', Integer
min'))
((Integer -> Integer -> ProtocolVersion)
-> (Integer, Integer) -> ProtocolVersion
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Integer -> Integer -> ProtocolVersion
PLA.ProtocolVersion)
instance Arbitrary PLA.ChangedParameters where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen ChangedParameters
arbitrary =
BuiltinData -> ChangedParameters
PLA.ChangedParameters (BuiltinData -> ChangedParameters)
-> ([(BuiltinData, BuiltinData)] -> BuiltinData)
-> [(BuiltinData, BuiltinData)]
-> ChangedParameters
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(BuiltinData, BuiltinData)] -> BuiltinData
Builtins.mkMap ([(BuiltinData, BuiltinData)] -> ChangedParameters)
-> Gen [(BuiltinData, BuiltinData)] -> Gen ChangedParameters
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> do
[Int]
keyList <- Gen Int -> Gen [Int]
forall a. Gen a -> Gen [a]
forall (f :: Type -> Type) a. Arbitrary1 f => Gen a -> Gen (f a)
liftArbitrary ((Int, Int) -> Gen Int
chooseInt (Int
0, Int
33))
let keySet :: Set Int
keySet = [Int] -> Set Int
forall a. Ord a => [a] -> Set a
Set.fromList [Int]
keyList
(Int -> Gen (BuiltinData, BuiltinData))
-> [Int] -> Gen [(BuiltinData, BuiltinData)]
forall (t :: Type -> Type) (f :: Type -> Type) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: Type -> Type) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (\Int
k -> (Integer -> BuiltinData
Builtins.mkI (Integer -> BuiltinData) -> (Int -> Integer) -> Int -> BuiltinData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> BuiltinData) -> Int -> BuiltinData
forall a b. (a -> b) -> a -> b
$ Int
k,) (BuiltinData -> (BuiltinData, BuiltinData))
-> Gen BuiltinData -> Gen (BuiltinData, BuiltinData)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen BuiltinData
forall a. Arbitrary a => Gen a
arbitrary) ([Int] -> Gen [(BuiltinData, BuiltinData)])
-> (Set Int -> [Int])
-> Set Int
-> Gen [(BuiltinData, BuiltinData)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Set Int -> [Int]
forall a. Set a -> [a]
Set.toList (Set Int -> Gen [(BuiltinData, BuiltinData)])
-> Set Int -> Gen [(BuiltinData, BuiltinData)]
forall a b. (a -> b) -> a -> b
$ Set Int
keySet
deriving via PlutusTx.BuiltinData instance CoArbitrary PLA.ChangedParameters
instance Function PLA.ChangedParameters where
{-# INLINEABLE function #-}
function :: forall b. (ChangedParameters -> b) -> ChangedParameters :-> b
function = (ChangedParameters -> BuiltinData)
-> (BuiltinData -> ChangedParameters)
-> (ChangedParameters -> b)
-> ChangedParameters :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ChangedParameters -> BuiltinData
forall a b. Coercible a b => a -> b
coerce BuiltinData -> ChangedParameters
PLA.ChangedParameters
instance Arbitrary PLA.GovernanceAction where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen GovernanceAction
arbitrary =
[Gen GovernanceAction] -> Gen GovernanceAction
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ Maybe GovernanceActionId
-> ChangedParameters -> Maybe ScriptHash -> GovernanceAction
PLA.ParameterChange (Maybe GovernanceActionId
-> ChangedParameters -> Maybe ScriptHash -> GovernanceAction)
-> Gen (Maybe GovernanceActionId)
-> Gen (ChangedParameters -> Maybe ScriptHash -> GovernanceAction)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe GovernanceActionId)
forall a. Arbitrary a => Gen a
arbitrary Gen (ChangedParameters -> Maybe ScriptHash -> GovernanceAction)
-> Gen ChangedParameters
-> Gen (Maybe ScriptHash -> GovernanceAction)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen ChangedParameters
forall a. Arbitrary a => Gen a
arbitrary Gen (Maybe ScriptHash -> GovernanceAction)
-> Gen (Maybe ScriptHash) -> Gen GovernanceAction
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen (Maybe ScriptHash)
forall a. Arbitrary a => Gen a
arbitrary
, Maybe GovernanceActionId -> ProtocolVersion -> GovernanceAction
PLA.HardForkInitiation (Maybe GovernanceActionId -> ProtocolVersion -> GovernanceAction)
-> Gen (Maybe GovernanceActionId)
-> Gen (ProtocolVersion -> GovernanceAction)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe GovernanceActionId)
forall a. Arbitrary a => Gen a
arbitrary Gen (ProtocolVersion -> GovernanceAction)
-> Gen ProtocolVersion -> Gen GovernanceAction
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen ProtocolVersion
forall a. Arbitrary a => Gen a
arbitrary
, Map Credential Lovelace -> Maybe ScriptHash -> GovernanceAction
PLA.TreasuryWithdrawals (Map Credential Lovelace -> Maybe ScriptHash -> GovernanceAction)
-> Gen (Map Credential Lovelace)
-> Gen (Maybe ScriptHash -> GovernanceAction)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Map Credential Lovelace)
forall a. Arbitrary a => Gen a
arbitrary Gen (Maybe ScriptHash -> GovernanceAction)
-> Gen (Maybe ScriptHash) -> Gen GovernanceAction
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen (Maybe ScriptHash)
forall a. Arbitrary a => Gen a
arbitrary
, Maybe GovernanceActionId -> GovernanceAction
PLA.NoConfidence (Maybe GovernanceActionId -> GovernanceAction)
-> Gen (Maybe GovernanceActionId) -> Gen GovernanceAction
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe GovernanceActionId)
forall a. Arbitrary a => Gen a
arbitrary
, Maybe GovernanceActionId
-> [ColdCommitteeCredential]
-> Map ColdCommitteeCredential Integer
-> Rational
-> GovernanceAction
PLA.UpdateCommittee
(Maybe GovernanceActionId
-> [ColdCommitteeCredential]
-> Map ColdCommitteeCredential Integer
-> Rational
-> GovernanceAction)
-> Gen (Maybe GovernanceActionId)
-> Gen
([ColdCommitteeCredential]
-> Map ColdCommitteeCredential Integer
-> Rational
-> GovernanceAction)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe GovernanceActionId)
forall a. Arbitrary a => Gen a
arbitrary
Gen
([ColdCommitteeCredential]
-> Map ColdCommitteeCredential Integer
-> Rational
-> GovernanceAction)
-> Gen [ColdCommitteeCredential]
-> Gen
(Map ColdCommitteeCredential Integer
-> Rational -> GovernanceAction)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen [ColdCommitteeCredential]
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Map ColdCommitteeCredential Integer
-> Rational -> GovernanceAction)
-> Gen (Map ColdCommitteeCredential Integer)
-> Gen (Rational -> GovernanceAction)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen (Map ColdCommitteeCredential Integer)
forall a. Arbitrary a => Gen a
arbitrary
Gen (Rational -> GovernanceAction)
-> Gen Rational -> Gen GovernanceAction
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (Integer -> Integer -> Rational
Ratio.unsafeRatio (Integer -> Integer -> Rational)
-> (Int -> Integer) -> Int -> Integer -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Integer -> Rational)
-> Gen Int -> Gen (Integer -> Rational)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int, Int) -> Gen Int
chooseInt (Int
1, Int
100) Gen (Integer -> Rational) -> Gen Integer -> Gen Rational
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Integer -> Gen Integer
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Integer
100)
, Maybe GovernanceActionId -> Constitution -> GovernanceAction
PLA.NewConstitution (Maybe GovernanceActionId -> Constitution -> GovernanceAction)
-> Gen (Maybe GovernanceActionId)
-> Gen (Constitution -> GovernanceAction)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Maybe GovernanceActionId)
forall a. Arbitrary a => Gen a
arbitrary Gen (Constitution -> GovernanceAction)
-> Gen Constitution -> Gen GovernanceAction
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Constitution
forall a. Arbitrary a => Gen a
arbitrary
, GovernanceAction -> Gen GovernanceAction
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure GovernanceAction
PLA.InfoAction
]
{-# INLINEABLE shrink #-}
shrink :: GovernanceAction -> [GovernanceAction]
shrink = \case
PLA.ParameterChange Maybe GovernanceActionId
mgid ChangedParameters
cp Maybe ScriptHash
msh ->
Maybe GovernanceActionId
-> ChangedParameters -> Maybe ScriptHash -> GovernanceAction
PLA.ParameterChange
(Maybe GovernanceActionId
-> ChangedParameters -> Maybe ScriptHash -> GovernanceAction)
-> [Maybe GovernanceActionId]
-> [ChangedParameters -> Maybe ScriptHash -> GovernanceAction]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GovernanceActionId -> [Maybe GovernanceActionId]
forall a. Arbitrary a => a -> [a]
shrink Maybe GovernanceActionId
mgid
[ChangedParameters -> Maybe ScriptHash -> GovernanceAction]
-> [ChangedParameters] -> [Maybe ScriptHash -> GovernanceAction]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> ChangedParameters -> [ChangedParameters]
forall a. Arbitrary a => a -> [a]
shrink ChangedParameters
cp
[Maybe ScriptHash -> GovernanceAction]
-> [Maybe ScriptHash] -> [GovernanceAction]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Maybe ScriptHash -> [Maybe ScriptHash]
forall a. Arbitrary a => a -> [a]
shrink Maybe ScriptHash
msh
PLA.HardForkInitiation Maybe GovernanceActionId
mgid ProtocolVersion
v ->
Maybe GovernanceActionId -> ProtocolVersion -> GovernanceAction
PLA.HardForkInitiation
(Maybe GovernanceActionId -> ProtocolVersion -> GovernanceAction)
-> [Maybe GovernanceActionId]
-> [ProtocolVersion -> GovernanceAction]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GovernanceActionId -> [Maybe GovernanceActionId]
forall a. Arbitrary a => a -> [a]
shrink Maybe GovernanceActionId
mgid
[ProtocolVersion -> GovernanceAction]
-> [ProtocolVersion] -> [GovernanceAction]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> ProtocolVersion -> [ProtocolVersion]
forall a. Arbitrary a => a -> [a]
shrink ProtocolVersion
v
PLA.TreasuryWithdrawals Map Credential Lovelace
wdrls Maybe ScriptHash
msh ->
Map Credential Lovelace -> Maybe ScriptHash -> GovernanceAction
PLA.TreasuryWithdrawals
(Map Credential Lovelace -> Maybe ScriptHash -> GovernanceAction)
-> [Map Credential Lovelace]
-> [Maybe ScriptHash -> GovernanceAction]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Map Credential Lovelace -> [Map Credential Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Map Credential Lovelace
wdrls
[Maybe ScriptHash -> GovernanceAction]
-> [Maybe ScriptHash] -> [GovernanceAction]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Maybe ScriptHash -> [Maybe ScriptHash]
forall a. Arbitrary a => a -> [a]
shrink Maybe ScriptHash
msh
PLA.NoConfidence Maybe GovernanceActionId
msh -> Maybe GovernanceActionId -> GovernanceAction
PLA.NoConfidence (Maybe GovernanceActionId -> GovernanceAction)
-> [Maybe GovernanceActionId] -> [GovernanceAction]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GovernanceActionId -> [Maybe GovernanceActionId]
forall a. Arbitrary a => a -> [a]
shrink Maybe GovernanceActionId
msh
PLA.UpdateCommittee Maybe GovernanceActionId
mgid [ColdCommitteeCredential]
creds Map ColdCommitteeCredential Integer
mems Rational
quorum -> do
Maybe GovernanceActionId
mgid' <- Maybe GovernanceActionId -> [Maybe GovernanceActionId]
forall a. Arbitrary a => a -> [a]
shrink Maybe GovernanceActionId
mgid
[ColdCommitteeCredential]
creds' <- [ColdCommitteeCredential] -> [[ColdCommitteeCredential]]
forall a. Arbitrary a => a -> [a]
shrink [ColdCommitteeCredential]
creds
Map ColdCommitteeCredential Integer
mems' <- Map ColdCommitteeCredential Integer
-> [Map ColdCommitteeCredential Integer]
forall a. Arbitrary a => a -> [a]
shrink Map ColdCommitteeCredential Integer
mems
GovernanceAction -> [GovernanceAction]
forall a. a -> [a]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (GovernanceAction -> [GovernanceAction])
-> (Rational -> GovernanceAction) -> Rational -> [GovernanceAction]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe GovernanceActionId
-> [ColdCommitteeCredential]
-> Map ColdCommitteeCredential Integer
-> Rational
-> GovernanceAction
PLA.UpdateCommittee Maybe GovernanceActionId
mgid' [ColdCommitteeCredential]
creds' Map ColdCommitteeCredential Integer
mems' (Rational -> [GovernanceAction]) -> Rational -> [GovernanceAction]
forall a b. (a -> b) -> a -> b
$ Rational
quorum
PLA.NewConstitution Maybe GovernanceActionId
mgid Constitution
c -> Maybe GovernanceActionId -> Constitution -> GovernanceAction
PLA.NewConstitution (Maybe GovernanceActionId -> Constitution -> GovernanceAction)
-> [Maybe GovernanceActionId] -> [Constitution -> GovernanceAction]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe GovernanceActionId -> [Maybe GovernanceActionId]
forall a. Arbitrary a => a -> [a]
shrink Maybe GovernanceActionId
mgid [Constitution -> GovernanceAction]
-> [Constitution] -> [GovernanceAction]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Constitution -> [Constitution]
forall a. Arbitrary a => a -> [a]
shrink Constitution
c
GovernanceAction
_ -> []
instance CoArbitrary PLA.GovernanceAction where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. GovernanceAction -> Gen b -> Gen b
coarbitrary = \case
PLA.ParameterChange Maybe GovernanceActionId
mgid ChangedParameters
cp Maybe ScriptHash
msh ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe GovernanceActionId -> Gen b -> Gen b
forall b. Maybe GovernanceActionId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe GovernanceActionId
mgid (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ChangedParameters -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. ChangedParameters -> Gen b -> Gen b
coarbitrary ChangedParameters
cp (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe ScriptHash -> Gen b -> Gen b
forall b. Maybe ScriptHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe ScriptHash
msh
PLA.HardForkInitiation Maybe GovernanceActionId
mgid ProtocolVersion
v ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe GovernanceActionId -> Gen b -> Gen b
forall b. Maybe GovernanceActionId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe GovernanceActionId
mgid (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolVersion -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. ProtocolVersion -> Gen b -> Gen b
coarbitrary ProtocolVersion
v
PLA.TreasuryWithdrawals Map Credential Lovelace
wdrls Maybe ScriptHash
msh ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Credential Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Map Credential Lovelace -> Gen b -> Gen b
coarbitrary Map Credential Lovelace
wdrls (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe ScriptHash -> Gen b -> Gen b
forall b. Maybe ScriptHash -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe ScriptHash
msh
PLA.NoConfidence Maybe GovernanceActionId
msh ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
3 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe GovernanceActionId -> Gen b -> Gen b
forall b. Maybe GovernanceActionId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe GovernanceActionId
msh
PLA.UpdateCommittee Maybe GovernanceActionId
mgid [ColdCommitteeCredential]
creds Map ColdCommitteeCredential Integer
mems Rational
quorum ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
4 :: Int)
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe GovernanceActionId -> Gen b -> Gen b
forall b. Maybe GovernanceActionId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe GovernanceActionId
mgid
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ColdCommitteeCredential] -> Gen b -> Gen b
forall b. [ColdCommitteeCredential] -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary [ColdCommitteeCredential]
creds
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map ColdCommitteeCredential Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Map ColdCommitteeCredential Integer -> Gen b -> Gen b
coarbitrary Map ColdCommitteeCredential Integer
mems
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Rational -> Integer
Ratio.numerator Rational
quorum)
(Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary (Rational -> Integer
Ratio.denominator Rational
quorum)
PLA.NewConstitution Maybe GovernanceActionId
mgid Constitution
c ->
Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
5 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe GovernanceActionId -> Gen b -> Gen b
forall b. Maybe GovernanceActionId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Maybe GovernanceActionId
mgid (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Constitution -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Constitution -> Gen b -> Gen b
coarbitrary Constitution
c
GovernanceAction
PLA.InfoAction -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
6 :: Int)
instance Function PLA.GovernanceAction where
{-# INLINEABLE function #-}
function :: forall b. (GovernanceAction -> b) -> GovernanceAction :-> b
function = (GovernanceAction
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))))
-> (Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
-> GovernanceAction)
-> (GovernanceAction -> b)
-> GovernanceAction :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap GovernanceAction
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
into Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
-> GovernanceAction
outOf
where
into ::
PLA.GovernanceAction ->
Maybe
( Either
(Maybe PLA.GovernanceActionId, PLA.ChangedParameters, Maybe PLA.ScriptHash)
( Either
(Maybe PLA.GovernanceActionId, PLA.ProtocolVersion)
( Either
(PLA.Map PLA.Credential PLA.Lovelace, Maybe PLA.ScriptHash)
( Either
(Maybe PLA.GovernanceActionId)
( Either (Maybe PLA.GovernanceActionId, [PLA.ColdCommitteeCredential], PLA.Map PLA.ColdCommitteeCredential Integer, Integer, Integer) (Maybe PLA.GovernanceActionId, PLA.Constitution)
)
)
)
)
)
into :: GovernanceAction
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
into = \case
GovernanceAction
PLA.InfoAction -> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. Maybe a
Nothing
PLA.ParameterChange Maybe GovernanceActionId
mgid ChangedParameters
cp Maybe ScriptHash
msh -> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. a -> Maybe a
Just ((Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
-> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
forall a b. a -> Either a b
Left (Maybe GovernanceActionId
mgid, ChangedParameters
cp, Maybe ScriptHash
msh))
PLA.HardForkInitiation Maybe GovernanceActionId
mgid ProtocolVersion
v -> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. a -> Maybe a
Just (Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
-> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
forall a b. b -> Either a b
Right ((Maybe GovernanceActionId, ProtocolVersion)
-> Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
forall a b. a -> Either a b
Left (Maybe GovernanceActionId
mgid, ProtocolVersion
v)))
PLA.TreasuryWithdrawals Map Credential Lovelace
wdrls Maybe ScriptHash
msh -> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. a -> Maybe a
Just (Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
-> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
forall a b. b -> Either a b
Right (Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
-> Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
forall a b. b -> Either a b
Right ((Map Credential Lovelace, Maybe ScriptHash)
-> Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
forall a b. a -> Either a b
Left (Map Credential Lovelace
wdrls, Maybe ScriptHash
msh))))
PLA.NoConfidence Maybe GovernanceActionId
msh -> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. a -> Maybe a
Just (Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
-> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
forall a b. b -> Either a b
Right (Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
-> Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
forall a b. b -> Either a b
Right (Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))
-> Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
forall a b. b -> Either a b
Right (Maybe GovernanceActionId
-> Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))
forall a b. a -> Either a b
Left Maybe GovernanceActionId
msh))))
PLA.UpdateCommittee Maybe GovernanceActionId
mgid [ColdCommitteeCredential]
creds Map ColdCommitteeCredential Integer
mems Rational
quorum ->
Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. a -> Maybe a
Just (Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
-> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
forall a b. b -> Either a b
Right (Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
-> Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
forall a b. b -> Either a b
Right (Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))
-> Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
forall a b. b -> Either a b
Right (Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)
-> Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))
forall a b. b -> Either a b
Right ((Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
-> Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)
forall a b. a -> Either a b
Left (Maybe GovernanceActionId
mgid, [ColdCommitteeCredential]
creds, Map ColdCommitteeCredential Integer
mems, Rational -> Integer
Ratio.numerator Rational
quorum, Rational -> Integer
Ratio.denominator Rational
quorum))))))
PLA.NewConstitution Maybe GovernanceActionId
mgid Constitution
c ->
Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
-> Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
forall a. a -> Maybe a
Just (Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
-> Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))))
forall a b. b -> Either a b
Right (Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
-> Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))
forall a b. b -> Either a b
Right (Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))
-> Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)))
forall a b. b -> Either a b
Right (Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)
-> Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))
forall a b. b -> Either a b
Right ((Maybe GovernanceActionId, Constitution)
-> Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution)
forall a b. b -> Either a b
Right (Maybe GovernanceActionId
mgid, Constitution
c))))))
outOf ::
Maybe
( Either
(Maybe PLA.GovernanceActionId, PLA.ChangedParameters, Maybe PLA.ScriptHash)
( Either
(Maybe PLA.GovernanceActionId, PLA.ProtocolVersion)
( Either
(PLA.Map PLA.Credential PLA.Lovelace, Maybe PLA.ScriptHash)
( Either
(Maybe PLA.GovernanceActionId)
( Either (Maybe PLA.GovernanceActionId, [PLA.ColdCommitteeCredential], PLA.Map PLA.ColdCommitteeCredential Integer, Integer, Integer) (Maybe PLA.GovernanceActionId, PLA.Constitution)
)
)
)
)
) ->
PLA.GovernanceAction
outOf :: Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
-> GovernanceAction
outOf = \case
Maybe
(Either
(Maybe GovernanceActionId, ChangedParameters, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId, ProtocolVersion)
(Either
(Map Credential Lovelace, Maybe ScriptHash)
(Either
(Maybe GovernanceActionId)
(Either
(Maybe GovernanceActionId, [ColdCommitteeCredential],
Map ColdCommitteeCredential Integer, Integer, Integer)
(Maybe GovernanceActionId, Constitution))))))
Nothing -> GovernanceAction
PLA.InfoAction
Just (Left (Maybe GovernanceActionId
mgid, ChangedParameters
cp, Maybe ScriptHash
msh)) -> Maybe GovernanceActionId
-> ChangedParameters -> Maybe ScriptHash -> GovernanceAction
PLA.ParameterChange Maybe GovernanceActionId
mgid ChangedParameters
cp Maybe ScriptHash
msh
Just (Right (Left (Maybe GovernanceActionId
mgid, ProtocolVersion
v))) -> Maybe GovernanceActionId -> ProtocolVersion -> GovernanceAction
PLA.HardForkInitiation Maybe GovernanceActionId
mgid ProtocolVersion
v
Just (Right (Right (Left (Map Credential Lovelace
wdrls, Maybe ScriptHash
msh)))) -> Map Credential Lovelace -> Maybe ScriptHash -> GovernanceAction
PLA.TreasuryWithdrawals Map Credential Lovelace
wdrls Maybe ScriptHash
msh
Just (Right (Right (Right (Left Maybe GovernanceActionId
msh)))) -> Maybe GovernanceActionId -> GovernanceAction
PLA.NoConfidence Maybe GovernanceActionId
msh
Just (Right (Right (Right (Right (Left (Maybe GovernanceActionId
mgid, [ColdCommitteeCredential]
creds, Map ColdCommitteeCredential Integer
mems, Integer
n, Integer
d)))))) ->
Maybe GovernanceActionId
-> [ColdCommitteeCredential]
-> Map ColdCommitteeCredential Integer
-> Rational
-> GovernanceAction
PLA.UpdateCommittee Maybe GovernanceActionId
mgid [ColdCommitteeCredential]
creds Map ColdCommitteeCredential Integer
mems (Integer -> Integer -> Rational
Ratio.unsafeRatio Integer
n Integer
d)
Just (Right (Right (Right (Right (Right (Maybe GovernanceActionId
mgid, Constitution
c)))))) ->
Maybe GovernanceActionId -> Constitution -> GovernanceAction
PLA.NewConstitution Maybe GovernanceActionId
mgid Constitution
c
instance Arbitrary PLA.ProposalProcedure where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen ProposalProcedure
arbitrary = Lovelace -> Credential -> GovernanceAction -> ProposalProcedure
PLA.ProposalProcedure (Lovelace -> Credential -> GovernanceAction -> ProposalProcedure)
-> Gen Lovelace
-> Gen (Credential -> GovernanceAction -> ProposalProcedure)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Lovelace
forall a. Arbitrary a => Gen a
arbitrary Gen (Credential -> GovernanceAction -> ProposalProcedure)
-> Gen Credential -> Gen (GovernanceAction -> ProposalProcedure)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary Gen (GovernanceAction -> ProposalProcedure)
-> Gen GovernanceAction -> Gen ProposalProcedure
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen GovernanceAction
forall a. Arbitrary a => Gen a
arbitrary
{-# INLINEABLE shrink #-}
shrink :: ProposalProcedure -> [ProposalProcedure]
shrink (PLA.ProposalProcedure Lovelace
dep Credential
raddr GovernanceAction
ga) =
Lovelace -> Credential -> GovernanceAction -> ProposalProcedure
PLA.ProposalProcedure (Lovelace -> Credential -> GovernanceAction -> ProposalProcedure)
-> [Lovelace]
-> [Credential -> GovernanceAction -> ProposalProcedure]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Lovelace -> [Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Lovelace
dep [Credential -> GovernanceAction -> ProposalProcedure]
-> [Credential] -> [GovernanceAction -> ProposalProcedure]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
raddr [GovernanceAction -> ProposalProcedure]
-> [GovernanceAction] -> [ProposalProcedure]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> GovernanceAction -> [GovernanceAction]
forall a. Arbitrary a => a -> [a]
shrink GovernanceAction
ga
instance CoArbitrary PLA.ProposalProcedure where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. ProposalProcedure -> Gen b -> Gen b
coarbitrary (PLA.ProposalProcedure Lovelace
dep Credential
raddr GovernanceAction
ga) =
Lovelace -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Lovelace -> Gen b -> Gen b
coarbitrary Lovelace
dep (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Credential -> Gen b -> Gen b
coarbitrary Credential
raddr (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GovernanceAction -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. GovernanceAction -> Gen b -> Gen b
coarbitrary GovernanceAction
ga
instance Function PLA.ProposalProcedure where
{-# INLINEABLE function #-}
function :: forall b. (ProposalProcedure -> b) -> ProposalProcedure :-> b
function = (ProposalProcedure -> (Lovelace, Credential, GovernanceAction))
-> ((Lovelace, Credential, GovernanceAction) -> ProposalProcedure)
-> (ProposalProcedure -> b)
-> ProposalProcedure :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ProposalProcedure -> (Lovelace, Credential, GovernanceAction)
into (Lovelace, Credential, GovernanceAction) -> ProposalProcedure
outOf
where
into ::
PLA.ProposalProcedure ->
(PLA.Lovelace, PLA.Credential, PLA.GovernanceAction)
into :: ProposalProcedure -> (Lovelace, Credential, GovernanceAction)
into (PLA.ProposalProcedure Lovelace
dep Credential
raddr GovernanceAction
ga) = (Lovelace
dep, Credential
raddr, GovernanceAction
ga)
outOf ::
(PLA.Lovelace, PLA.Credential, PLA.GovernanceAction) ->
PLA.ProposalProcedure
outOf :: (Lovelace, Credential, GovernanceAction) -> ProposalProcedure
outOf (Lovelace
dep, Credential
raddr, GovernanceAction
ga) = Lovelace -> Credential -> GovernanceAction -> ProposalProcedure
PLA.ProposalProcedure Lovelace
dep Credential
raddr GovernanceAction
ga
instance Arbitrary PLA.TxOutRef where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen TxOutRef
arbitrary = TxId -> Integer -> TxOutRef
PLA.TxOutRef (TxId -> Integer -> TxOutRef)
-> Gen TxId -> Gen (Integer -> TxOutRef)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxId
forall a. Arbitrary a => Gen a
arbitrary Gen (Integer -> TxOutRef) -> Gen Integer -> Gen TxOutRef
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> (NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> Integer)
-> Gen (NonNegative Integer) -> Gen Integer
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary)
{-# INLINEABLE shrink #-}
shrink :: TxOutRef -> [TxOutRef]
shrink (PLA.TxOutRef TxId
tid Integer
ix) =
TxId -> Integer -> TxOutRef
PLA.TxOutRef (TxId -> Integer -> TxOutRef) -> [TxId] -> [Integer -> TxOutRef]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> TxId -> [TxId]
forall a. Arbitrary a => a -> [a]
shrink TxId
tid [Integer -> TxOutRef] -> [Integer] -> [TxOutRef]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> ((NonNegative Integer -> Integer)
-> [NonNegative Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative ([NonNegative Integer] -> [Integer])
-> (Integer -> [NonNegative Integer]) -> Integer -> [Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (NonNegative Integer -> [NonNegative Integer])
-> (Integer -> NonNegative Integer)
-> Integer
-> [NonNegative Integer]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative (Integer -> [Integer]) -> Integer -> [Integer]
forall a b. (a -> b) -> a -> b
$ Integer
ix)
instance CoArbitrary PLA.TxOutRef where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. TxOutRef -> Gen b -> Gen b
coarbitrary (PLA.TxOutRef TxId
tid Integer
ix) =
TxId -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. TxId -> Gen b -> Gen b
coarbitrary TxId
tid (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
ix
instance Function PLA.TxOutRef where
{-# INLINEABLE function #-}
function :: forall b. (TxOutRef -> b) -> TxOutRef :-> b
function = (TxOutRef -> (TxId, Integer))
-> ((TxId, Integer) -> TxOutRef)
-> (TxOutRef -> b)
-> TxOutRef :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap (\(PLA.TxOutRef TxId
tid Integer
ix) -> (TxId
tid, Integer
ix)) ((TxId -> Integer -> TxOutRef) -> (TxId, Integer) -> TxOutRef
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry TxId -> Integer -> TxOutRef
PLA.TxOutRef)
instance Arbitrary PLA.ScriptPurpose where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen ScriptPurpose
arbitrary =
[Gen ScriptPurpose] -> Gen ScriptPurpose
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ CurrencySymbol -> ScriptPurpose
PLA.Minting (CurrencySymbol -> ScriptPurpose)
-> Gen CurrencySymbol -> Gen ScriptPurpose
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen CurrencySymbol
forall a. Arbitrary a => Gen a
arbitrary
, TxOutRef -> ScriptPurpose
PLA.Spending (TxOutRef -> ScriptPurpose) -> Gen TxOutRef -> Gen ScriptPurpose
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxOutRef
forall a. Arbitrary a => Gen a
arbitrary
, Credential -> ScriptPurpose
PLA.Rewarding (Credential -> ScriptPurpose)
-> Gen Credential -> Gen ScriptPurpose
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary
, Integer -> TxCert -> ScriptPurpose
PLA.Certifying (Integer -> TxCert -> ScriptPurpose)
-> (NonNegative Integer -> Integer)
-> NonNegative Integer
-> TxCert
-> ScriptPurpose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> TxCert -> ScriptPurpose)
-> Gen (NonNegative Integer) -> Gen (TxCert -> ScriptPurpose)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary Gen (TxCert -> ScriptPurpose) -> Gen TxCert -> Gen ScriptPurpose
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen TxCert
forall a. Arbitrary a => Gen a
arbitrary
, Voter -> ScriptPurpose
PLA.Voting (Voter -> ScriptPurpose) -> Gen Voter -> Gen ScriptPurpose
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Voter
forall a. Arbitrary a => Gen a
arbitrary
, Integer -> ProposalProcedure -> ScriptPurpose
PLA.Proposing (Integer -> ProposalProcedure -> ScriptPurpose)
-> (NonNegative Integer -> Integer)
-> NonNegative Integer
-> ProposalProcedure
-> ScriptPurpose
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> ProposalProcedure -> ScriptPurpose)
-> Gen (NonNegative Integer)
-> Gen (ProposalProcedure -> ScriptPurpose)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary Gen (ProposalProcedure -> ScriptPurpose)
-> Gen ProposalProcedure -> Gen ScriptPurpose
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen ProposalProcedure
forall a. Arbitrary a => Gen a
arbitrary
]
{-# INLINEABLE shrink #-}
shrink :: ScriptPurpose -> [ScriptPurpose]
shrink = \case
PLA.Minting CurrencySymbol
cs -> CurrencySymbol -> ScriptPurpose
PLA.Minting (CurrencySymbol -> ScriptPurpose)
-> [CurrencySymbol] -> [ScriptPurpose]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> CurrencySymbol -> [CurrencySymbol]
forall a. Arbitrary a => a -> [a]
shrink CurrencySymbol
cs
PLA.Spending TxOutRef
txo -> TxOutRef -> ScriptPurpose
PLA.Spending (TxOutRef -> ScriptPurpose) -> [TxOutRef] -> [ScriptPurpose]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> TxOutRef -> [TxOutRef]
forall a. Arbitrary a => a -> [a]
shrink TxOutRef
txo
PLA.Rewarding Credential
cred -> Credential -> ScriptPurpose
PLA.Rewarding (Credential -> ScriptPurpose) -> [Credential] -> [ScriptPurpose]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
cred
PLA.Certifying Integer
ix TxCert
cert -> do
TxCert
cert' <- TxCert -> [TxCert]
forall a. Arbitrary a => a -> [a]
shrink TxCert
cert
NonNegative Integer
ix' <- NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
ix)
ScriptPurpose -> [ScriptPurpose]
forall a. a -> [a]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (ScriptPurpose -> [ScriptPurpose])
-> (TxCert -> ScriptPurpose) -> TxCert -> [ScriptPurpose]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> TxCert -> ScriptPurpose
PLA.Certifying Integer
ix' (TxCert -> [ScriptPurpose]) -> TxCert -> [ScriptPurpose]
forall a b. (a -> b) -> a -> b
$ TxCert
cert'
PLA.Voting Voter
voter -> Voter -> ScriptPurpose
PLA.Voting (Voter -> ScriptPurpose) -> [Voter] -> [ScriptPurpose]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Voter -> [Voter]
forall a. Arbitrary a => a -> [a]
shrink Voter
voter
PLA.Proposing Integer
ix ProposalProcedure
pp -> do
ProposalProcedure
pp' <- ProposalProcedure -> [ProposalProcedure]
forall a. Arbitrary a => a -> [a]
shrink ProposalProcedure
pp
NonNegative Integer
ix' <- NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
ix)
ScriptPurpose -> [ScriptPurpose]
forall a. a -> [a]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (ScriptPurpose -> [ScriptPurpose])
-> (ProposalProcedure -> ScriptPurpose)
-> ProposalProcedure
-> [ScriptPurpose]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> ProposalProcedure -> ScriptPurpose
PLA.Proposing Integer
ix' (ProposalProcedure -> [ScriptPurpose])
-> ProposalProcedure -> [ScriptPurpose]
forall a b. (a -> b) -> a -> b
$ ProposalProcedure
pp'
instance CoArbitrary PLA.ScriptPurpose where
{-# INLINEABLE coarbitrary #-}
coarbitrary :: forall b. ScriptPurpose -> Gen b -> Gen b
coarbitrary = \case
PLA.Minting CurrencySymbol
cs -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
0 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CurrencySymbol -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. CurrencySymbol -> Gen b -> Gen b
coarbitrary CurrencySymbol
cs
PLA.Spending TxOutRef
txo -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
1 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. TxOutRef -> Gen b -> Gen b
coarbitrary TxOutRef
txo
PLA.Rewarding Credential
cred -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
2 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Credential -> Gen b -> Gen b
coarbitrary Credential
cred
PLA.Certifying Integer
ix TxCert
cert -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
3 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
ix (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxCert -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. TxCert -> Gen b -> Gen b
coarbitrary TxCert
cert
PLA.Voting Voter
voter -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
4 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Voter -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. Voter -> Gen b -> Gen b
coarbitrary Voter
voter
PLA.Proposing Integer
ix ProposalProcedure
pp -> Int -> Gen b -> Gen b
forall n a. Integral n => n -> Gen a -> Gen a
variant (Int
5 :: Int) (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Gen b -> Gen b
forall b. Integer -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
coarbitrary Integer
ix (Gen b -> Gen b) -> (Gen b -> Gen b) -> Gen b -> Gen b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProposalProcedure -> Gen b -> Gen b
forall a b. CoArbitrary a => a -> Gen b -> Gen b
forall b. ProposalProcedure -> Gen b -> Gen b
coarbitrary ProposalProcedure
pp
instance Function PLA.ScriptPurpose where
{-# INLINEABLE function #-}
function :: forall b. (ScriptPurpose -> b) -> ScriptPurpose :-> b
function = (ScriptPurpose
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))))
-> (Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
-> ScriptPurpose)
-> (ScriptPurpose -> b)
-> ScriptPurpose :-> b
forall b a c.
Function b =>
(a -> b) -> (b -> a) -> (a -> c) -> a :-> c
functionMap ScriptPurpose
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
into Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
-> ScriptPurpose
outOf
where
into ::
PLA.ScriptPurpose ->
Either
PLA.CurrencySymbol
( Either
PLA.TxOutRef
( Either
PLA.Credential
( Either
(Integer, PLA.TxCert)
( Either PLA.Voter (Integer, PLA.ProposalProcedure)
)
)
)
)
into :: ScriptPurpose
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
into = \case
PLA.Minting CurrencySymbol
cs -> CurrencySymbol
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
forall a b. a -> Either a b
Left CurrencySymbol
cs
PLA.Spending TxOutRef
txo -> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
forall a b. b -> Either a b
Right (TxOutRef
-> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
forall a b. a -> Either a b
Left TxOutRef
txo)
PLA.Rewarding Credential
cred -> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
forall a b. b -> Either a b
Right (Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
-> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
forall a b. b -> Either a b
Right (Credential
-> Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
forall a b. a -> Either a b
Left Credential
cred))
PLA.Certifying Integer
ix TxCert
cert -> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
forall a b. b -> Either a b
Right (Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
-> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
forall a b. b -> Either a b
Right (Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))
-> Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
forall a b. b -> Either a b
Right ((Integer, TxCert)
-> Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))
forall a b. a -> Either a b
Left (Integer
ix, TxCert
cert))))
PLA.Voting Voter
voter -> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
forall a b. b -> Either a b
Right (Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
-> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
forall a b. b -> Either a b
Right (Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))
-> Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
forall a b. b -> Either a b
Right (Either Voter (Integer, ProposalProcedure)
-> Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))
forall a b. b -> Either a b
Right (Voter -> Either Voter (Integer, ProposalProcedure)
forall a b. a -> Either a b
Left Voter
voter))))
PLA.Proposing Integer
ix ProposalProcedure
pp -> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
-> Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
forall a b. b -> Either a b
Right (Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
-> Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))))
forall a b. b -> Either a b
Right (Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))
-> Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))
forall a b. b -> Either a b
Right (Either Voter (Integer, ProposalProcedure)
-> Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure))
forall a b. b -> Either a b
Right ((Integer, ProposalProcedure)
-> Either Voter (Integer, ProposalProcedure)
forall a b. b -> Either a b
Right (Integer
ix, ProposalProcedure
pp)))))
outOf ::
Either
PLA.CurrencySymbol
( Either
PLA.TxOutRef
( Either
PLA.Credential
( Either
(Integer, PLA.TxCert)
( Either PLA.Voter (Integer, PLA.ProposalProcedure)
)
)
)
) ->
PLA.ScriptPurpose
outOf :: Either
CurrencySymbol
(Either
TxOutRef
(Either
Credential
(Either
(Integer, TxCert) (Either Voter (Integer, ProposalProcedure)))))
-> ScriptPurpose
outOf = \case
Left CurrencySymbol
cs -> CurrencySymbol -> ScriptPurpose
PLA.Minting CurrencySymbol
cs
Right (Left TxOutRef
txo) -> TxOutRef -> ScriptPurpose
PLA.Spending TxOutRef
txo
Right (Right (Left Credential
cred)) -> Credential -> ScriptPurpose
PLA.Rewarding Credential
cred
Right (Right (Right (Left (Integer
ix, TxCert
cert)))) -> Integer -> TxCert -> ScriptPurpose
PLA.Certifying Integer
ix TxCert
cert
Right (Right (Right (Right (Left Voter
voter)))) -> Voter -> ScriptPurpose
PLA.Voting Voter
voter
Right (Right (Right (Right (Right (Integer
ix, ProposalProcedure
pp))))) -> Integer -> ProposalProcedure -> ScriptPurpose
PLA.Proposing Integer
ix ProposalProcedure
pp
instance Arbitrary PLA.ScriptInfo where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen ScriptInfo
arbitrary =
[Gen ScriptInfo] -> Gen ScriptInfo
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ CurrencySymbol -> ScriptInfo
PLA.MintingScript (CurrencySymbol -> ScriptInfo)
-> Gen CurrencySymbol -> Gen ScriptInfo
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen CurrencySymbol
forall a. Arbitrary a => Gen a
arbitrary
, TxOutRef -> Maybe Datum -> ScriptInfo
PLA.SpendingScript (TxOutRef -> Maybe Datum -> ScriptInfo)
-> Gen TxOutRef -> Gen (Maybe Datum -> ScriptInfo)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxOutRef
forall a. Arbitrary a => Gen a
arbitrary Gen (Maybe Datum -> ScriptInfo)
-> Gen (Maybe Datum) -> Gen ScriptInfo
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen (Maybe Datum)
forall a. Arbitrary a => Gen a
arbitrary
, Credential -> ScriptInfo
PLA.RewardingScript (Credential -> ScriptInfo) -> Gen Credential -> Gen ScriptInfo
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Credential
forall a. Arbitrary a => Gen a
arbitrary
, Integer -> TxCert -> ScriptInfo
PLA.CertifyingScript (Integer -> TxCert -> ScriptInfo)
-> (NonNegative Integer -> Integer)
-> NonNegative Integer
-> TxCert
-> ScriptInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> TxCert -> ScriptInfo)
-> Gen (NonNegative Integer) -> Gen (TxCert -> ScriptInfo)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary Gen (TxCert -> ScriptInfo) -> Gen TxCert -> Gen ScriptInfo
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen TxCert
forall a. Arbitrary a => Gen a
arbitrary
, Voter -> ScriptInfo
PLA.VotingScript (Voter -> ScriptInfo) -> Gen Voter -> Gen ScriptInfo
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Voter
forall a. Arbitrary a => Gen a
arbitrary
, Integer -> ProposalProcedure -> ScriptInfo
PLA.ProposingScript (Integer -> ProposalProcedure -> ScriptInfo)
-> (NonNegative Integer -> Integer)
-> NonNegative Integer
-> ProposalProcedure
-> ScriptInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonNegative Integer -> Integer
forall a. NonNegative a -> a
getNonNegative (NonNegative Integer -> ProposalProcedure -> ScriptInfo)
-> Gen (NonNegative Integer)
-> Gen (ProposalProcedure -> ScriptInfo)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonNegative Integer)
forall a. Arbitrary a => Gen a
arbitrary Gen (ProposalProcedure -> ScriptInfo)
-> Gen ProposalProcedure -> Gen ScriptInfo
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen ProposalProcedure
forall a. Arbitrary a => Gen a
arbitrary
]
{-# INLINEABLE shrink #-}
shrink :: ScriptInfo -> [ScriptInfo]
shrink = \case
PLA.MintingScript CurrencySymbol
cs -> CurrencySymbol -> ScriptInfo
PLA.MintingScript (CurrencySymbol -> ScriptInfo) -> [CurrencySymbol] -> [ScriptInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> CurrencySymbol -> [CurrencySymbol]
forall a. Arbitrary a => a -> [a]
shrink CurrencySymbol
cs
PLA.SpendingScript TxOutRef
outRef Maybe Datum
mdat -> TxOutRef -> Maybe Datum -> ScriptInfo
PLA.SpendingScript (TxOutRef -> Maybe Datum -> ScriptInfo)
-> [TxOutRef] -> [Maybe Datum -> ScriptInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> TxOutRef -> [TxOutRef]
forall a. Arbitrary a => a -> [a]
shrink TxOutRef
outRef [Maybe Datum -> ScriptInfo] -> [Maybe Datum] -> [ScriptInfo]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Maybe Datum -> [Maybe Datum]
forall a. Arbitrary a => a -> [a]
shrink Maybe Datum
mdat
PLA.RewardingScript Credential
cred -> Credential -> ScriptInfo
PLA.RewardingScript (Credential -> ScriptInfo) -> [Credential] -> [ScriptInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Credential -> [Credential]
forall a. Arbitrary a => a -> [a]
shrink Credential
cred
PLA.CertifyingScript Integer
ix TxCert
cert -> do
NonNegative Integer
ix' <- NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
ix)
Integer -> TxCert -> ScriptInfo
PLA.CertifyingScript Integer
ix' (TxCert -> ScriptInfo) -> [TxCert] -> [ScriptInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> TxCert -> [TxCert]
forall a. Arbitrary a => a -> [a]
shrink TxCert
cert
PLA.VotingScript Voter
voter -> Voter -> ScriptInfo
PLA.VotingScript (Voter -> ScriptInfo) -> [Voter] -> [ScriptInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Voter -> [Voter]
forall a. Arbitrary a => a -> [a]
shrink Voter
voter
PLA.ProposingScript Integer
ix ProposalProcedure
pp -> do
NonNegative Integer
ix' <- NonNegative Integer -> [NonNegative Integer]
forall a. Arbitrary a => a -> [a]
shrink (Integer -> NonNegative Integer
forall a. a -> NonNegative a
NonNegative Integer
ix)
Integer -> ProposalProcedure -> ScriptInfo
PLA.ProposingScript Integer
ix' (ProposalProcedure -> ScriptInfo)
-> [ProposalProcedure] -> [ScriptInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> ProposalProcedure -> [ProposalProcedure]
forall a. Arbitrary a => a -> [a]
shrink ProposalProcedure
pp
instance Arbitrary PLA.TxInInfo where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen TxInInfo
arbitrary = TxOutRef -> TxOut -> TxInInfo
PLA.TxInInfo (TxOutRef -> TxOut -> TxInInfo)
-> Gen TxOutRef -> Gen (TxOut -> TxInInfo)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxOutRef
forall a. Arbitrary a => Gen a
arbitrary Gen (TxOut -> TxInInfo) -> Gen TxOut -> Gen TxInInfo
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen TxOut
forall a. Arbitrary a => Gen a
arbitrary
{-# INLINEABLE shrink #-}
shrink :: TxInInfo -> [TxInInfo]
shrink (PLA.TxInInfo TxOutRef
toutref TxOut
tout) =
TxOutRef -> TxOut -> TxInInfo
PLA.TxInInfo (TxOutRef -> TxOut -> TxInInfo)
-> [TxOutRef] -> [TxOut -> TxInInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> TxOutRef -> [TxOutRef]
forall a. Arbitrary a => a -> [a]
shrink TxOutRef
toutref [TxOut -> TxInInfo] -> [TxOut] -> [TxInInfo]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> TxOut -> [TxOut]
forall a. Arbitrary a => a -> [a]
shrink TxOut
tout
instance Arbitrary PLA.TxInfo where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen TxInfo
arbitrary = do
[TxInInfo]
ins <- NonEmptyList TxInInfo -> [TxInInfo]
forall a. NonEmptyList a -> [a]
getNonEmpty (NonEmptyList TxInInfo -> [TxInInfo])
-> Gen (NonEmptyList TxInInfo) -> Gen [TxInInfo]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonEmptyList TxInInfo)
forall a. Arbitrary a => Gen a
arbitrary
[TxInInfo]
routs <- Gen [TxInInfo]
forall a. Arbitrary a => Gen a
arbitrary
[TxOut]
outs <- NonEmptyList TxOut -> [TxOut]
forall a. NonEmptyList a -> [a]
getNonEmpty (NonEmptyList TxOut -> [TxOut])
-> Gen (NonEmptyList TxOut) -> Gen [TxOut]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (NonEmptyList TxOut)
forall a. Arbitrary a => Gen a
arbitrary
Lovelace
fee <- Gen Lovelace
forall a. Arbitrary a => Gen a
arbitrary
Value
mint <- MintValue -> Value
Value.getMintValue (MintValue -> Value) -> Gen MintValue -> Gen Value
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen MintValue
forall a. Arbitrary a => Gen a
arbitrary
[TxCert]
cert <- Gen [TxCert]
forall a. Arbitrary a => Gen a
arbitrary
Map Credential Lovelace
wdrl <- Gen (Map Credential Lovelace)
forall a. Arbitrary a => Gen a
arbitrary
POSIXTimeRange
valid <- Gen POSIXTimeRange
forall a. Arbitrary a => Gen a
arbitrary
[PubKeyHash]
sigs <- Set PubKeyHash -> [PubKeyHash]
forall a. Set a -> [a]
Set.toList (Set PubKeyHash -> [PubKeyHash])
-> Gen (Set PubKeyHash) -> Gen [PubKeyHash]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Set PubKeyHash)
forall a. Arbitrary a => Gen a
arbitrary
Map ScriptPurpose Redeemer
reds <- Gen (Map ScriptPurpose Redeemer)
forall a. Arbitrary a => Gen a
arbitrary
Map DatumHash Datum
dats <- Gen (Map DatumHash Datum)
forall a. Arbitrary a => Gen a
arbitrary
TxId
tid <- Gen TxId
forall a. Arbitrary a => Gen a
arbitrary
Map Voter (Map GovernanceActionId Vote)
votes <- Gen (Map Voter (Map GovernanceActionId Vote))
forall a. Arbitrary a => Gen a
arbitrary
[ProposalProcedure]
pps <- Gen [ProposalProcedure]
forall a. Arbitrary a => Gen a
arbitrary
Maybe Lovelace
currT <- Gen (Maybe Lovelace)
forall a. Arbitrary a => Gen a
arbitrary
Maybe Lovelace
tDonation <- Gen (Maybe Lovelace)
forall a. Arbitrary a => Gen a
arbitrary
TxInfo -> Gen TxInfo
forall a. a -> Gen a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (TxInfo -> Gen TxInfo)
-> (Maybe Lovelace -> TxInfo) -> Maybe Lovelace -> Gen TxInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TxInInfo]
-> [TxInInfo]
-> [TxOut]
-> Lovelace
-> Value
-> [TxCert]
-> Map Credential Lovelace
-> POSIXTimeRange
-> [PubKeyHash]
-> Map ScriptPurpose Redeemer
-> Map DatumHash Datum
-> TxId
-> Map Voter (Map GovernanceActionId Vote)
-> [ProposalProcedure]
-> Maybe Lovelace
-> Maybe Lovelace
-> TxInfo
PLA.TxInfo [TxInInfo]
ins [TxInInfo]
routs [TxOut]
outs Lovelace
fee Value
mint [TxCert]
cert Map Credential Lovelace
wdrl POSIXTimeRange
valid [PubKeyHash]
sigs Map ScriptPurpose Redeemer
reds Map DatumHash Datum
dats TxId
tid Map Voter (Map GovernanceActionId Vote)
votes [ProposalProcedure]
pps Maybe Lovelace
currT (Maybe Lovelace -> Gen TxInfo) -> Maybe Lovelace -> Gen TxInfo
forall a b. (a -> b) -> a -> b
$ Maybe Lovelace
tDonation
{-# INLINEABLE shrink #-}
shrink :: TxInfo -> [TxInfo]
shrink (PLA.TxInfo [TxInInfo]
ins [TxInInfo]
routs [TxOut]
outs Lovelace
fee Value
mint [TxCert]
cert Map Credential Lovelace
wdrl POSIXTimeRange
valid [PubKeyHash]
sigs Map ScriptPurpose Redeemer
reds Map DatumHash Datum
dats TxId
tid Map Voter (Map GovernanceActionId Vote)
votes [ProposalProcedure]
pps Maybe Lovelace
currT Maybe Lovelace
tDonation) = do
NonEmpty [TxInInfo]
ins' <- NonEmptyList TxInInfo -> [NonEmptyList TxInInfo]
forall a. Arbitrary a => a -> [a]
shrink ([TxInInfo] -> NonEmptyList TxInInfo
forall a. [a] -> NonEmptyList a
NonEmpty [TxInInfo]
ins)
[TxInInfo]
routs' <- [TxInInfo] -> [[TxInInfo]]
forall a. Arbitrary a => a -> [a]
shrink [TxInInfo]
routs
NonEmpty [TxOut]
outs' <- NonEmptyList TxOut -> [NonEmptyList TxOut]
forall a. Arbitrary a => a -> [a]
shrink ([TxOut] -> NonEmptyList TxOut
forall a. [a] -> NonEmptyList a
NonEmpty [TxOut]
outs)
Lovelace
fee' <- Lovelace -> [Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Lovelace
fee
(Value.MintValue Value
mint') <- MintValue -> [MintValue]
forall a. Arbitrary a => a -> [a]
shrink (Value -> MintValue
Value.MintValue Value
mint)
[TxCert]
cert' <- [TxCert] -> [[TxCert]]
forall a. Arbitrary a => a -> [a]
shrink [TxCert]
cert
Map Credential Lovelace
wdrl' <- Map Credential Lovelace -> [Map Credential Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Map Credential Lovelace
wdrl
POSIXTimeRange
valid' <- POSIXTimeRange -> [POSIXTimeRange]
forall a. Arbitrary a => a -> [a]
shrink POSIXTimeRange
valid
[PubKeyHash]
sigs' <- [PubKeyHash] -> [[PubKeyHash]]
forall a. Arbitrary a => a -> [a]
shrink [PubKeyHash]
sigs
Map ScriptPurpose Redeemer
reds' <- Map ScriptPurpose Redeemer -> [Map ScriptPurpose Redeemer]
forall a. Arbitrary a => a -> [a]
shrink Map ScriptPurpose Redeemer
reds
Map DatumHash Datum
dats' <- Map DatumHash Datum -> [Map DatumHash Datum]
forall a. Arbitrary a => a -> [a]
shrink Map DatumHash Datum
dats
TxId
tid' <- TxId -> [TxId]
forall a. Arbitrary a => a -> [a]
shrink TxId
tid
Map Voter (Map GovernanceActionId Vote)
votes' <- Map Voter (Map GovernanceActionId Vote)
-> [Map Voter (Map GovernanceActionId Vote)]
forall a. Arbitrary a => a -> [a]
shrink Map Voter (Map GovernanceActionId Vote)
votes
[ProposalProcedure]
pps' <- [ProposalProcedure] -> [[ProposalProcedure]]
forall a. Arbitrary a => a -> [a]
shrink [ProposalProcedure]
pps
Maybe Lovelace
currT' <- Maybe Lovelace -> [Maybe Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Maybe Lovelace
currT
Maybe Lovelace
tDonation' <- Maybe Lovelace -> [Maybe Lovelace]
forall a. Arbitrary a => a -> [a]
shrink Maybe Lovelace
tDonation
TxInfo -> [TxInfo]
forall a. a -> [a]
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (TxInfo -> [TxInfo])
-> (Maybe Lovelace -> TxInfo) -> Maybe Lovelace -> [TxInfo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [TxInInfo]
-> [TxInInfo]
-> [TxOut]
-> Lovelace
-> Value
-> [TxCert]
-> Map Credential Lovelace
-> POSIXTimeRange
-> [PubKeyHash]
-> Map ScriptPurpose Redeemer
-> Map DatumHash Datum
-> TxId
-> Map Voter (Map GovernanceActionId Vote)
-> [ProposalProcedure]
-> Maybe Lovelace
-> Maybe Lovelace
-> TxInfo
PLA.TxInfo [TxInInfo]
ins' [TxInInfo]
routs' [TxOut]
outs' Lovelace
fee' Value
mint' [TxCert]
cert' Map Credential Lovelace
wdrl' POSIXTimeRange
valid' [PubKeyHash]
sigs' Map ScriptPurpose Redeemer
reds' Map DatumHash Datum
dats' TxId
tid' Map Voter (Map GovernanceActionId Vote)
votes' [ProposalProcedure]
pps' Maybe Lovelace
currT' (Maybe Lovelace -> [TxInfo]) -> Maybe Lovelace -> [TxInfo]
forall a b. (a -> b) -> a -> b
$ Maybe Lovelace
tDonation'
instance Arbitrary PLA.ScriptContext where
{-# INLINEABLE arbitrary #-}
arbitrary :: Gen ScriptContext
arbitrary = TxInfo -> Redeemer -> ScriptInfo -> ScriptContext
PLA.ScriptContext (TxInfo -> Redeemer -> ScriptInfo -> ScriptContext)
-> Gen TxInfo -> Gen (Redeemer -> ScriptInfo -> ScriptContext)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxInfo
forall a. Arbitrary a => Gen a
arbitrary Gen (Redeemer -> ScriptInfo -> ScriptContext)
-> Gen Redeemer -> Gen (ScriptInfo -> ScriptContext)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen Redeemer
forall a. Arbitrary a => Gen a
arbitrary Gen (ScriptInfo -> ScriptContext)
-> Gen ScriptInfo -> Gen ScriptContext
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Gen ScriptInfo
forall a. Arbitrary a => Gen a
arbitrary
{-# INLINEABLE shrink #-}
shrink :: ScriptContext -> [ScriptContext]
shrink (PLA.ScriptContext TxInfo
tinfo Redeemer
red ScriptInfo
sinfo) =
TxInfo -> Redeemer -> ScriptInfo -> ScriptContext
PLA.ScriptContext (TxInfo -> Redeemer -> ScriptInfo -> ScriptContext)
-> [TxInfo] -> [Redeemer -> ScriptInfo -> ScriptContext]
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> TxInfo -> [TxInfo]
forall a. Arbitrary a => a -> [a]
shrink TxInfo
tinfo [Redeemer -> ScriptInfo -> ScriptContext]
-> [Redeemer] -> [ScriptInfo -> ScriptContext]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Redeemer -> [Redeemer]
forall a. Arbitrary a => a -> [a]
shrink Redeemer
red [ScriptInfo -> ScriptContext] -> [ScriptInfo] -> [ScriptContext]
forall a b. [a -> b] -> [a] -> [b]
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> ScriptInfo -> [ScriptInfo]
forall a. Arbitrary a => a -> [a]
shrink ScriptInfo
sinfo