{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
#if __GLASGOW_HASKELL__ < 900
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# OPTIONS_GHC -O0 #-}
#endif
module Test.Cardano.Ledger.Constrained.Conway.Instances.Ledger (
ConwayFn,
StringFn,
ProposalTree,
onJust',
onSized,
cKeyHashObj,
cScriptHashObj,
maryValueCoin_,
strLen_,
sizedValue_,
sizedSize_,
txOutVal_,
pProcDeposit_,
pProcGovAction_,
IsConwayUniv,
gasId_,
gasCommitteeVotes_,
gasDRepVotes_,
gasProposalProcedure_,
ProposalsSplit (..),
genProposalsSplit,
proposalSplitSum,
coerce_,
toDelta_,
module Test.Cardano.Ledger.Constrained.Conway.Instances.Basic,
) where
import Cardano.Chain.Common (
AddrAttributes (..),
AddrType (..),
Address (..),
Address',
Attributes (..),
NetworkMagic (..),
UnparsedFields (..),
)
import Cardano.Crypto.Hash hiding (Blake2b_224)
import Cardano.Crypto.Hashing (AbstractHash, abstractHashFromBytes)
import Cardano.Ledger.Address
import Cardano.Ledger.Allegra.Scripts
import Cardano.Ledger.Allegra.TxAuxData (AllegraTxAuxData (..))
import Cardano.Ledger.Alonzo.Scripts (AlonzoScript (..))
import Cardano.Ledger.Alonzo.Tx
import Cardano.Ledger.Alonzo.TxAuxData (AlonzoTxAuxData (..), AuxiliaryDataHash)
import Cardano.Ledger.Alonzo.TxOut
import Cardano.Ledger.Alonzo.TxWits
import Cardano.Ledger.Babbage.TxBody (BabbageTxOut (..))
import Cardano.Ledger.BaseTypes hiding (inject)
import Cardano.Ledger.Binary (DecCBOR (..), EncCBOR (..), Sized (..))
import Cardano.Ledger.Binary.Coders
import Cardano.Ledger.CertState
import Cardano.Ledger.Coin
import Cardano.Ledger.Compactible
import Cardano.Ledger.Conway (Conway, ConwayEra)
import Cardano.Ledger.Conway.Core
import Cardano.Ledger.Conway.Governance
import Cardano.Ledger.Conway.PParams
import Cardano.Ledger.Conway.Rules
import Cardano.Ledger.Conway.Scripts ()
import Cardano.Ledger.Conway.TxBody
import Cardano.Ledger.Conway.TxCert
import Cardano.Ledger.Credential
import Cardano.Ledger.Crypto (Crypto, StandardCrypto)
import Cardano.Ledger.EpochBoundary
import Cardano.Ledger.HKD
import Cardano.Ledger.Keys (
BootstrapWitness,
GenDelegPair (..),
GenDelegs (..),
KeyHash,
KeyRole (..),
VRFVerKeyHash (..),
WitVKey,
)
import Cardano.Ledger.Mary.Value (AssetName (..), MaryValue (..), MultiAsset (..), PolicyID (..))
import Cardano.Ledger.MemoBytes
import Cardano.Ledger.Plutus.Data
import Cardano.Ledger.Plutus.Language
import Cardano.Ledger.PoolDistr
import Cardano.Ledger.PoolParams
import Cardano.Ledger.SafeHash
import Cardano.Ledger.Shelley.LedgerState hiding (ptrMap)
import Cardano.Ledger.Shelley.PoolRank
import Cardano.Ledger.Shelley.RewardUpdate (FreeVars, Pulser, RewardAns, RewardPulser (RSLP))
import Cardano.Ledger.Shelley.Rewards (LeaderOnlyReward, PoolRewardInfo, StakeShare)
import Cardano.Ledger.Shelley.Rules
import Cardano.Ledger.Shelley.Tx (ShelleyTx (..))
import Cardano.Ledger.Shelley.TxAuxData (Metadatum, ShelleyTxAuxData (..))
import Cardano.Ledger.Shelley.TxCert (
GenesisDelegCert (..),
ShelleyDelegCert (..),
ShelleyTxCert (..),
)
import Cardano.Ledger.Shelley.TxOut (ShelleyTxOut (..))
import Cardano.Ledger.Shelley.TxWits (ShelleyTxWits (..))
import Cardano.Ledger.TxIn (TxId (..), TxIn (..))
import Cardano.Ledger.UMap
import Cardano.Ledger.UTxO
import Cardano.Ledger.Val (Val)
import Constrained hiding (Value)
import Constrained qualified as C
import Constrained.Base (Binder (..), HasGenHint (..), Pred (..), Term (..))
import Constrained.Spec.Map
import Control.DeepSeq (NFData)
import Crypto.Hash (Blake2b_224)
import Data.ByteString qualified as BS
import Data.ByteString.Short (ShortByteString)
import Data.ByteString.Short qualified as SBS
import Data.Coerce
import Data.Foldable
import Data.Int
import Data.Kind
import Data.List.NonEmpty qualified as NE
import Data.Map (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.OMap.Strict qualified as OMap
import Data.OSet.Strict qualified as SOS
import Data.Sequence (Seq)
import Data.Sequence qualified as Seq
import Data.Sequence.Strict (StrictSeq)
import Data.Sequence.Strict qualified as StrictSeq
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Tree
import Data.Typeable
import Data.VMap (VMap)
import Data.VMap qualified as VMap
import Data.Word
import GHC.Generics (Generic)
import PlutusLedgerApi.V1 qualified as PV1
import Test.Cardano.Ledger.Allegra.Arbitrary ()
import Test.Cardano.Ledger.Alonzo.Arbitrary ()
import Test.Cardano.Ledger.Constrained.Conway.Instances.Basic
import Test.Cardano.Ledger.Core.Utils
import Test.Cardano.Ledger.Shelley.Utils
import Test.Cardano.Ledger.TreeDiff (ToExpr)
import Test.Cardano.Slotting.Numeric ()
import Test.QuickCheck hiding (Args, Fun, forAll)
type ConwayUnivFns = CoinFn : CoerceFn : StringFn : MapFn : FunFn : TreeFn : BaseFns
type ConwayFn = Fix (OneofL ConwayUnivFns)
type IsConwayUniv fn =
( BaseUniverse fn
, Member (CoinFn fn) fn
, Member (CoerceFn fn) fn
, Member (StringFn fn) fn
, Member (MapFn fn) fn
, Member (FunFn fn) fn
, Member (TreeFn fn) fn
)
type ConwayTxBodyTypes c =
'[ Set (TxIn (EraCrypto (ConwayEra c)))
, Set (TxIn (EraCrypto (ConwayEra c)))
, Set (TxIn (EraCrypto (ConwayEra c)))
, StrictSeq (Sized (TxOut (ConwayEra c)))
, StrictMaybe (Sized (TxOut (ConwayEra c)))
, StrictMaybe Coin
, SOS.OSet (ConwayTxCert (ConwayEra c))
, Withdrawals (EraCrypto (ConwayEra c))
, Coin
, ValidityInterval
, Set (KeyHash 'Witness (EraCrypto (ConwayEra c)))
, MultiAsset (EraCrypto (ConwayEra c))
, StrictMaybe (ScriptIntegrityHash (EraCrypto (ConwayEra c)))
, StrictMaybe (AuxiliaryDataHash (EraCrypto (ConwayEra c)))
, StrictMaybe Network
, VotingProcedures (ConwayEra c)
, SOS.OSet (ProposalProcedure (ConwayEra c))
, StrictMaybe Coin
, Coin
]
instance (EraSpecPParams (ConwayEra c), IsConwayUniv fn, Crypto c) => HasSpec fn (ConwayTxBody (ConwayEra c))
instance Crypto c => HasSimpleRep (ConwayTxBody (ConwayEra c)) where
type SimpleRep (ConwayTxBody (ConwayEra c)) = SOP '["ConwayTxBody" ::: ConwayTxBodyTypes c]
toSimpleRep :: ConwayTxBody (ConwayEra c)
-> SimpleRep (ConwayTxBody (ConwayEra c))
toSimpleRep ConwayTxBody {Set (TxIn (EraCrypto (ConwayEra c)))
Set (KeyHash 'Witness (EraCrypto (ConwayEra c)))
OSet (ProposalProcedure (ConwayEra c))
OSet (ConwayTxCert (ConwayEra c))
Withdrawals (EraCrypto (ConwayEra c))
ValidityInterval
StrictMaybe (AuxiliaryDataHash (EraCrypto (ConwayEra c)))
StrictMaybe Coin
StrictMaybe (Sized (TxOut (ConwayEra c)))
StrictMaybe Network
StrictMaybe (ScriptIntegrityHash (EraCrypto (ConwayEra c)))
Coin
VotingProcedures (ConwayEra c)
StrictSeq (Sized (TxOut (ConwayEra c)))
MultiAsset (EraCrypto (ConwayEra c))
ctbSpendInputs :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> Set (TxIn (EraCrypto era))
ctbCollateralInputs :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> Set (TxIn (EraCrypto era))
ctbReferenceInputs :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> Set (TxIn (EraCrypto era))
ctbOutputs :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictSeq (Sized (TxOut era))
ctbCollateralReturn :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe (Sized (TxOut era))
ctbTotalCollateral :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe Coin
ctbCerts :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> OSet (ConwayTxCert era)
ctbWithdrawals :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> Withdrawals (EraCrypto era)
ctbTxfee :: forall era. ConwayEraTxBody era => ConwayTxBody era -> Coin
ctbVldt :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> ValidityInterval
ctbReqSignerHashes :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> Set (KeyHash 'Witness (EraCrypto era))
ctbMint :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> MultiAsset (EraCrypto era)
ctbScriptIntegrityHash :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era
-> StrictMaybe (ScriptIntegrityHash (EraCrypto era))
ctbAdHash :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe (AuxiliaryDataHash (EraCrypto era))
ctbTxNetworkId :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe Network
ctbVotingProcedures :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> VotingProcedures era
ctbProposalProcedures :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> OSet (ProposalProcedure era)
ctbCurrentTreasuryValue :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe Coin
ctbTreasuryDonation :: forall era. ConwayEraTxBody era => ConwayTxBody era -> Coin
ctbTreasuryDonation :: Coin
ctbCurrentTreasuryValue :: StrictMaybe Coin
ctbProposalProcedures :: OSet (ProposalProcedure (ConwayEra c))
ctbVotingProcedures :: VotingProcedures (ConwayEra c)
ctbTxNetworkId :: StrictMaybe Network
ctbAdHash :: StrictMaybe (AuxiliaryDataHash (EraCrypto (ConwayEra c)))
ctbScriptIntegrityHash :: StrictMaybe (ScriptIntegrityHash (EraCrypto (ConwayEra c)))
ctbMint :: MultiAsset (EraCrypto (ConwayEra c))
ctbReqSignerHashes :: Set (KeyHash 'Witness (EraCrypto (ConwayEra c)))
ctbVldt :: ValidityInterval
ctbTxfee :: Coin
ctbWithdrawals :: Withdrawals (EraCrypto (ConwayEra c))
ctbCerts :: OSet (ConwayTxCert (ConwayEra c))
ctbTotalCollateral :: StrictMaybe Coin
ctbCollateralReturn :: StrictMaybe (Sized (TxOut (ConwayEra c)))
ctbOutputs :: StrictSeq (Sized (TxOut (ConwayEra c)))
ctbReferenceInputs :: Set (TxIn (EraCrypto (ConwayEra c)))
ctbCollateralInputs :: Set (TxIn (EraCrypto (ConwayEra c)))
ctbSpendInputs :: Set (TxIn (EraCrypto (ConwayEra c)))
..} =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"ConwayTxBody" @'["ConwayTxBody" ::: ConwayTxBodyTypes c]
Set (TxIn (EraCrypto (ConwayEra c)))
ctbSpendInputs
Set (TxIn (EraCrypto (ConwayEra c)))
ctbCollateralInputs
Set (TxIn (EraCrypto (ConwayEra c)))
ctbReferenceInputs
StrictSeq (Sized (TxOut (ConwayEra c)))
ctbOutputs
StrictMaybe (Sized (TxOut (ConwayEra c)))
ctbCollateralReturn
StrictMaybe Coin
ctbTotalCollateral
OSet (ConwayTxCert (ConwayEra c))
ctbCerts
Withdrawals (EraCrypto (ConwayEra c))
ctbWithdrawals
Coin
ctbTxfee
ValidityInterval
ctbVldt
Set (KeyHash 'Witness (EraCrypto (ConwayEra c)))
ctbReqSignerHashes
MultiAsset (EraCrypto (ConwayEra c))
ctbMint
StrictMaybe (ScriptIntegrityHash (EraCrypto (ConwayEra c)))
ctbScriptIntegrityHash
StrictMaybe (AuxiliaryDataHash (EraCrypto (ConwayEra c)))
ctbAdHash
StrictMaybe Network
ctbTxNetworkId
VotingProcedures (ConwayEra c)
ctbVotingProcedures
OSet (ProposalProcedure (ConwayEra c))
ctbProposalProcedures
StrictMaybe Coin
ctbCurrentTreasuryValue
Coin
ctbTreasuryDonation
fromSimpleRep :: SimpleRep (ConwayTxBody (ConwayEra c))
-> ConwayTxBody (ConwayEra c)
fromSimpleRep SimpleRep (ConwayTxBody (ConwayEra c))
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ConwayTxBody" ::: ConwayTxBodyTypes c] SimpleRep (ConwayTxBody (ConwayEra c))
rep forall era.
ConwayEraTxBody era =>
Set (TxIn (EraCrypto era))
-> Set (TxIn (EraCrypto era))
-> Set (TxIn (EraCrypto era))
-> StrictSeq (Sized (TxOut era))
-> StrictMaybe (Sized (TxOut era))
-> StrictMaybe Coin
-> OSet (ConwayTxCert era)
-> Withdrawals (EraCrypto era)
-> Coin
-> ValidityInterval
-> Set (KeyHash 'Witness (EraCrypto era))
-> MultiAsset (EraCrypto era)
-> StrictMaybe (ScriptIntegrityHash (EraCrypto era))
-> StrictMaybe (AuxiliaryDataHash (EraCrypto era))
-> StrictMaybe Network
-> VotingProcedures era
-> OSet (ProposalProcedure era)
-> StrictMaybe Coin
-> Coin
-> ConwayTxBody era
ConwayTxBody
instance HasSimpleRep DeltaCoin where
type SimpleRep DeltaCoin = Integer
fromSimpleRep :: SimpleRep DeltaCoin -> DeltaCoin
fromSimpleRep = Integer -> DeltaCoin
DeltaCoin
toSimpleRep :: DeltaCoin -> SimpleRep DeltaCoin
toSimpleRep (DeltaCoin Integer
c) = Integer
c
instance IsConwayUniv fn => HasSpec fn DeltaCoin
instance IsConwayUniv fn => OrdLike fn DeltaCoin
instance IsConwayUniv fn => NumLike fn DeltaCoin
instance IsConwayUniv fn => Foldy fn DeltaCoin where
genList :: forall (m :: * -> *).
(BaseUniverse fn, MonadGenError m) =>
Specification fn DeltaCoin
-> Specification fn DeltaCoin -> GenT m [DeltaCoin]
genList Specification fn DeltaCoin
s Specification fn DeltaCoin
s' = forall a b. (a -> b) -> [a] -> [b]
map forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (fn :: [*] -> * -> *) a (m :: * -> *).
(Foldy fn a, BaseUniverse fn, MonadGenError m) =>
Specification fn a -> Specification fn a -> GenT m [a]
genList @fn @Integer (forall a (fn :: [*] -> * -> *).
(HasSpec fn a, HasSpec fn (SimpleRep a), HasSimpleRep a,
TypeSpec fn a ~ TypeSpec fn (SimpleRep a)) =>
Specification fn a -> Specification fn (SimpleRep a)
toSimpleRepSpec Specification fn DeltaCoin
s) (forall a (fn :: [*] -> * -> *).
(HasSpec fn a, HasSpec fn (SimpleRep a), HasSimpleRep a,
TypeSpec fn a ~ TypeSpec fn (SimpleRep a)) =>
Specification fn a -> Specification fn (SimpleRep a)
toSimpleRepSpec Specification fn DeltaCoin
s')
theAddFn :: fn '[DeltaCoin, DeltaCoin] DeltaCoin
theAddFn = forall (fn :: [*] -> * -> *) a. NumLike fn a => fn '[a, a] a
addFn
theZero :: DeltaCoin
theZero = Integer -> DeltaCoin
DeltaCoin Integer
0
deriving via Integer instance Num DeltaCoin
instance HasSimpleRep (GovSignal era)
instance (EraTxCert Conway, EraSpecPParams Conway, IsConwayUniv fn) => HasSpec fn (GovSignal Conway)
instance HasSimpleRep SlotNo
instance IsConwayUniv fn => OrdLike fn SlotNo
instance IsConwayUniv fn => HasSpec fn SlotNo
instance HasSimpleRep EpochNo
instance IsConwayUniv fn => OrdLike fn EpochNo
instance IsConwayUniv fn => HasSpec fn EpochNo
instance IsConwayUniv fn => NumLike fn EpochNo
instance HasSimpleRep TxIx
instance IsConwayUniv fn => HasSpec fn TxIx
instance (IsConwayUniv fn, Crypto c, Typeable index) => HasSpec fn (SafeHash c index) where
type TypeSpec fn (SafeHash c index) = ()
emptySpec :: TypeSpec fn (SafeHash c index)
emptySpec = ()
combineSpec :: TypeSpec fn (SafeHash c index)
-> TypeSpec fn (SafeHash c index)
-> Specification fn (SafeHash c index)
combineSpec TypeSpec fn (SafeHash c index)
_ TypeSpec fn (SafeHash c index)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn (SafeHash c index) -> GenT m (SafeHash c index)
genFromTypeSpec TypeSpec fn (SafeHash c index)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn (SafeHash c index) -> Specification fn Integer
cardinalTypeSpec TypeSpec fn (SafeHash c index)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn (SafeHash c index)
-> SafeHash c index -> [SafeHash c index]
shrinkWithTypeSpec TypeSpec fn (SafeHash c index)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack =>
SafeHash c index -> TypeSpec fn (SafeHash c index) -> Bool
conformsTo SafeHash c index
_ TypeSpec fn (SafeHash c index)
_ = Bool
True
toPreds :: Term fn (SafeHash c index)
-> TypeSpec fn (SafeHash c index) -> Pred fn
toPreds Term fn (SafeHash c index)
_ TypeSpec fn (SafeHash c index)
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance HasSimpleRep (TxId c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (TxId c)
instance HasSimpleRep (TxIn c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (TxIn c)
instance HasSimpleRep (StrictSeq a) where
type SimpleRep (StrictSeq a) = [a]
toSimpleRep :: StrictSeq a -> SimpleRep (StrictSeq a)
toSimpleRep = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
fromSimpleRep :: SimpleRep (StrictSeq a) -> StrictSeq a
fromSimpleRep = forall a. [a] -> StrictSeq a
StrictSeq.fromList
instance (IsConwayUniv fn, HasSpec fn a) => HasSpec fn (StrictSeq a)
instance HasSimpleRep (Seq a) where
type SimpleRep (Seq a) = [a]
toSimpleRep :: Seq a -> SimpleRep (Seq a)
toSimpleRep = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
fromSimpleRep :: SimpleRep (Seq a) -> Seq a
fromSimpleRep = forall a. [a] -> Seq a
Seq.fromList
instance (IsConwayUniv fn, HasSpec fn a) => HasSpec fn (Seq a)
instance HasSimpleRep (Sized a)
instance (IsConwayUniv fn, HasSpec fn a) => HasSpec fn (Sized a)
sizedValue_ :: (HasSpec fn (Sized a), HasSpec fn a) => Term fn (Sized a) -> Term fn a
sizedValue_ :: forall (fn :: [*] -> * -> *) a.
(HasSpec fn (Sized a), HasSpec fn a) =>
Term fn (Sized a) -> Term fn a
sizedValue_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @0
sizedSize_ :: (HasSpec fn (Sized a), HasSpec fn a) => Term fn (Sized a) -> Term fn Int64
sizedSize_ :: forall (fn :: [*] -> * -> *) a.
(HasSpec fn (Sized a), HasSpec fn a) =>
Term fn (Sized a) -> Term fn Int64
sizedSize_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @1
instance HasSimpleRep Addr28Extra
instance IsConwayUniv fn => HasSpec fn Addr28Extra
instance HasSimpleRep DataHash32
instance IsConwayUniv fn => HasSpec fn DataHash32
type ShelleyTxOutTypes era =
'[ Addr (EraCrypto era)
, Value era
]
instance (Era era, Val (Value era)) => HasSimpleRep (ShelleyTxOut era) where
type TheSop (ShelleyTxOut era) = '["ShelleyTxOut" ::: ShelleyTxOutTypes era]
toSimpleRep :: ShelleyTxOut era -> SimpleRep (ShelleyTxOut era)
toSimpleRep (ShelleyTxOut Addr (EraCrypto era)
addr Value era
val) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"ShelleyTxOut" @'["ShelleyTxOut" ::: ShelleyTxOutTypes era]
Addr (EraCrypto era)
addr
Value era
val
fromSimpleRep :: SimpleRep (ShelleyTxOut era) -> ShelleyTxOut era
fromSimpleRep SimpleRep (ShelleyTxOut era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ShelleyTxOut" ::: ShelleyTxOutTypes era] SimpleRep (ShelleyTxOut era)
rep forall era.
(HasCallStack, Era era, Val (Value era)) =>
Addr (EraCrypto era) -> Value era -> ShelleyTxOut era
ShelleyTxOut
instance (EraTxOut era, HasSpec fn (Value era), IsConwayUniv fn) => HasSpec fn (ShelleyTxOut era)
type AlonzoTxOutTypes era =
'[ Addr (EraCrypto era)
, Value era
, StrictMaybe (DataHash (EraCrypto era))
]
instance (Era era, Val (Value era)) => HasSimpleRep (AlonzoTxOut era) where
type TheSop (AlonzoTxOut era) = '["AlonzoTxOut" ::: AlonzoTxOutTypes era]
toSimpleRep :: AlonzoTxOut era -> SimpleRep (AlonzoTxOut era)
toSimpleRep (AlonzoTxOut Addr (EraCrypto era)
addr Value era
val StrictMaybe (DataHash (EraCrypto era))
mdat) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"AlonzoTxOut" @'["AlonzoTxOut" ::: AlonzoTxOutTypes era]
Addr (EraCrypto era)
addr
Value era
val
StrictMaybe (DataHash (EraCrypto era))
mdat
fromSimpleRep :: SimpleRep (AlonzoTxOut era) -> AlonzoTxOut era
fromSimpleRep SimpleRep (AlonzoTxOut era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["AlonzoTxOut" ::: AlonzoTxOutTypes era] SimpleRep (AlonzoTxOut era)
rep forall era.
(Era era, Val (Value era), HasCallStack) =>
Addr (EraCrypto era)
-> Value era
-> StrictMaybe (DataHash (EraCrypto era))
-> AlonzoTxOut era
AlonzoTxOut
instance (EraTxOut era, HasSpec fn (Value era), IsConwayUniv fn) => HasSpec fn (AlonzoTxOut era)
type BabbageTxOutTypes era =
'[ Addr (EraCrypto era)
, Value era
, Datum era
, StrictMaybe (Script era)
]
instance (Era era, Val (Value era)) => HasSimpleRep (BabbageTxOut era) where
type TheSop (BabbageTxOut era) = '["BabbageTxOut" ::: BabbageTxOutTypes era]
toSimpleRep :: BabbageTxOut era -> SimpleRep (BabbageTxOut era)
toSimpleRep (BabbageTxOut Addr (EraCrypto era)
addr Value era
val Datum era
dat StrictMaybe (Script era)
msc) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"BabbageTxOut" @'["BabbageTxOut" ::: BabbageTxOutTypes era]
Addr (EraCrypto era)
addr
Value era
val
Datum era
dat
StrictMaybe (Script era)
msc
fromSimpleRep :: SimpleRep (BabbageTxOut era) -> BabbageTxOut era
fromSimpleRep SimpleRep (BabbageTxOut era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["BabbageTxOut" ::: BabbageTxOutTypes era] SimpleRep (BabbageTxOut era)
rep forall era.
(Era era, Val (Value era), HasCallStack) =>
Addr (EraCrypto era)
-> Value era
-> Datum era
-> StrictMaybe (Script era)
-> BabbageTxOut era
BabbageTxOut
instance
( IsConwayUniv fn
, HasSpec fn (Value era)
, Era era
, HasSpec fn (Data era)
, Val (Value era)
, Crypto (EraCrypto era)
, HasSpec fn (Script era)
, IsNormalType (Script era)
) =>
HasSpec fn (BabbageTxOut era)
txOutVal_ ::
( HasSpec fn (Value era)
, Era era
, HasSpec fn (Data era)
, Val (Value era)
, HasSpec fn (Script era)
, IsConwayUniv fn
, HasSpec fn (BabbageTxOut era)
, IsNormalType (Script era)
) =>
Term fn (BabbageTxOut era) ->
Term fn (Value era)
txOutVal_ :: forall (fn :: [*] -> * -> *) era.
(HasSpec fn (Value era), Era era, HasSpec fn (Data era),
Val (Value era), HasSpec fn (Script era), IsConwayUniv fn,
HasSpec fn (BabbageTxOut era), IsNormalType (Script era)) =>
Term fn (BabbageTxOut era) -> Term fn (Value era)
txOutVal_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @1
instance
( Compactible a
, HasSimpleRep a
, Typeable (SimpleRep a)
, Show (SimpleRep a)
) =>
HasSimpleRep (CompactForm a)
where
type SimpleRep (CompactForm a) = SimpleRep a
toSimpleRep :: CompactForm a -> SimpleRep (CompactForm a)
toSimpleRep = forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Compactible a => CompactForm a -> a
fromCompact
fromSimpleRep :: SimpleRep (CompactForm a) -> CompactForm a
fromSimpleRep SimpleRep (CompactForm a)
x = forall a. a -> Maybe a -> a
fromMaybe CompactForm a
err forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Compactible a => a -> Maybe (CompactForm a)
toCompact forall a b. (a -> b) -> a -> b
$ forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep SimpleRep (CompactForm a)
x
where
err :: CompactForm a
err = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"toCompact @" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show (forall a. Typeable a => a -> TypeRep
typeOf SimpleRep (CompactForm a)
x) forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show SimpleRep (CompactForm a)
x
instance
( IsConwayUniv fn
, Compactible a
, HasSpec fn a
, HasSimpleRep a
, HasSpec fn (SimpleRep a)
, Show (TypeSpec fn (SimpleRep a))
) =>
HasSpec fn (CompactForm a)
instance HasSimpleRep (MaryValue c) where
type TheSop (MaryValue c) = '["MaryValue" ::: '[Coin]]
toSimpleRep :: MaryValue c -> SimpleRep (MaryValue c)
toSimpleRep (MaryValue Coin
c MultiAsset c
_) = Coin
c
fromSimpleRep :: SimpleRep (MaryValue c) -> MaryValue c
fromSimpleRep SimpleRep (MaryValue c)
c = forall c. Coin -> MultiAsset c -> MaryValue c
MaryValue SimpleRep (MaryValue c)
c forall a. Monoid a => a
mempty
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (MaryValue c)
maryValueCoin_ :: (IsConwayUniv fn, Crypto c) => Term fn (MaryValue c) -> Term fn Coin
maryValueCoin_ :: forall (fn :: [*] -> * -> *) c.
(IsConwayUniv fn, Crypto c) =>
Term fn (MaryValue c) -> Term fn Coin
maryValueCoin_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @0
instance HasSimpleRep PV1.Data
instance IsConwayUniv fn => HasSpec fn PV1.Data where
type TypeSpec fn PV1.Data = ()
emptySpec :: TypeSpec fn Data
emptySpec = ()
combineSpec :: TypeSpec fn Data -> TypeSpec fn Data -> Specification fn Data
combineSpec TypeSpec fn Data
_ TypeSpec fn Data
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn Data -> GenT m Data
genFromTypeSpec TypeSpec fn Data
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn Data -> Specification fn Integer
cardinalTypeSpec TypeSpec fn Data
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn Data -> Data -> [Data]
shrinkWithTypeSpec TypeSpec fn Data
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Data -> TypeSpec fn Data -> Bool
conformsTo Data
_ TypeSpec fn Data
_ = Bool
True
toPreds :: Term fn Data -> TypeSpec fn Data -> Pred fn
toPreds Term fn Data
_ TypeSpec fn Data
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance Era era => HasSimpleRep (Data era) where
type SimpleRep (Data era) = PV1.Data
toSimpleRep :: Data era -> SimpleRep (Data era)
toSimpleRep = forall era. Data era -> Data
getPlutusData
fromSimpleRep :: SimpleRep (Data era) -> Data era
fromSimpleRep = forall era (t :: * -> *).
(Era era, EncCBOR (RawType t era), Memoized t) =>
RawType t era -> t era
mkMemoized forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Data -> PlutusData era
PlutusData
instance (IsConwayUniv fn, Era era) => HasSpec fn (Data era)
instance Era era => HasSimpleRep (BinaryData era) where
type SimpleRep (BinaryData era) = Data era
toSimpleRep :: BinaryData era -> SimpleRep (BinaryData era)
toSimpleRep = forall era. Era era => BinaryData era -> Data era
binaryDataToData
fromSimpleRep :: SimpleRep (BinaryData era) -> BinaryData era
fromSimpleRep = forall era. Era era => Data era -> BinaryData era
dataToBinaryData
instance
(IsConwayUniv fn, Era era, Crypto (EraCrypto era), HasSpec fn (Data era)) =>
HasSpec fn (BinaryData era)
instance HasSimpleRep (Datum era)
instance (IsConwayUniv fn, Era era, HasSpec fn (Data era), Crypto (EraCrypto era)) => HasSpec fn (Datum era)
instance HasSimpleRep (AlonzoScript era) where
type SimpleRep (AlonzoScript era) = Timelock era
toSimpleRep :: AlonzoScript era -> SimpleRep (AlonzoScript era)
toSimpleRep (TimelockScript Timelock era
tl) = Timelock era
tl
toSimpleRep (PlutusScript PlutusScript era
_) = forall a. HasCallStack => [Char] -> a
error [Char]
"toSimpleRep for AlonzoScript on a PlutusScript"
fromSimpleRep :: SimpleRep (AlonzoScript era) -> AlonzoScript era
fromSimpleRep = forall era. Timelock era -> AlonzoScript era
TimelockScript
instance
( IsConwayUniv fn
, AlonzoEraScript era
, Script era ~ AlonzoScript era
, NativeScript era ~ Timelock era
) =>
HasSpec fn (AlonzoScript era)
instance
( IsConwayUniv fn
, Crypto (EraCrypto era)
, AllegraEraScript era
, NativeScript era ~ Timelock era
) =>
HasSpec fn (Timelock era)
where
type TypeSpec fn (Timelock era) = ()
emptySpec :: TypeSpec fn (Timelock era)
emptySpec = ()
combineSpec :: TypeSpec fn (Timelock era)
-> TypeSpec fn (Timelock era) -> Specification fn (Timelock era)
combineSpec TypeSpec fn (Timelock era)
_ TypeSpec fn (Timelock era)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn (Timelock era) -> GenT m (Timelock era)
genFromTypeSpec TypeSpec fn (Timelock era)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn (Timelock era) -> Specification fn Integer
cardinalTypeSpec TypeSpec fn (Timelock era)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn (Timelock era) -> Timelock era -> [Timelock era]
shrinkWithTypeSpec TypeSpec fn (Timelock era)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Timelock era -> TypeSpec fn (Timelock era) -> Bool
conformsTo Timelock era
_ TypeSpec fn (Timelock era)
_ = Bool
True
toPreds :: Term fn (Timelock era) -> TypeSpec fn (Timelock era) -> Pred fn
toPreds Term fn (Timelock era)
_ TypeSpec fn (Timelock era)
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance Crypto c => HasSimpleRep (CompactAddr c) where
type SimpleRep (CompactAddr c) = SimpleRep (Addr c)
toSimpleRep :: CompactAddr c -> SimpleRep (CompactAddr c)
toSimpleRep = forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. (HasCallStack, Crypto c) => CompactAddr c -> Addr c
decompactAddr
fromSimpleRep :: SimpleRep (CompactAddr c) -> CompactAddr c
fromSimpleRep = forall c. Addr c -> CompactAddr c
compactAddr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (CompactAddr c)
instance HasSimpleRep (Addr c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (Addr c)
instance HasSimpleRep (BootstrapAddress c) where
type
TheSop (BootstrapAddress c) =
'[ "BootstrapAddress"
::: '[ AbstractHash Blake2b_224 Address'
, NetworkMagic
, AddrType
]
]
toSimpleRep :: BootstrapAddress c -> SimpleRep (BootstrapAddress c)
toSimpleRep (BootstrapAddress (Address AbstractHash Blake2b_224 Address'
root (Attributes (AddrAttributes Maybe HDAddressPayload
_ NetworkMagic
magic) UnparsedFields
_) AddrType
typ)) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"BootstrapAddress" @(TheSop (BootstrapAddress c))
AbstractHash Blake2b_224 Address'
root
NetworkMagic
magic
AddrType
typ
fromSimpleRep :: SimpleRep (BootstrapAddress c) -> BootstrapAddress c
fromSimpleRep SimpleRep (BootstrapAddress c)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @(TheSop (BootstrapAddress c)) SimpleRep (BootstrapAddress c)
rep forall a b. (a -> b) -> a -> b
$
\AbstractHash Blake2b_224 Address'
root NetworkMagic
magic AddrType
typ ->
forall c. Address -> BootstrapAddress c
BootstrapAddress
(AbstractHash Blake2b_224 Address'
-> Attributes AddrAttributes -> AddrType -> Address
Address AbstractHash Blake2b_224 Address'
root (forall h. h -> UnparsedFields -> Attributes h
Attributes (Maybe HDAddressPayload -> NetworkMagic -> AddrAttributes
AddrAttributes forall a. Maybe a
Nothing NetworkMagic
magic) (Map Word8 ByteString -> UnparsedFields
UnparsedFields forall a. Monoid a => a
mempty)) AddrType
typ)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (BootstrapAddress c)
instance HasSimpleRep NetworkMagic
instance IsConwayUniv fn => HasSpec fn NetworkMagic
instance HasSimpleRep AddrType
instance IsConwayUniv fn => HasSpec fn AddrType
instance (IsConwayUniv fn, Typeable b) => HasSpec fn (AbstractHash Blake2b_224 b) where
type TypeSpec fn (AbstractHash Blake2b_224 b) = ()
emptySpec :: TypeSpec fn (AbstractHash Blake2b_224 b)
emptySpec = ()
combineSpec :: TypeSpec fn (AbstractHash Blake2b_224 b)
-> TypeSpec fn (AbstractHash Blake2b_224 b)
-> Specification fn (AbstractHash Blake2b_224 b)
combineSpec TypeSpec fn (AbstractHash Blake2b_224 b)
_ TypeSpec fn (AbstractHash Blake2b_224 b)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn (AbstractHash Blake2b_224 b)
-> GenT m (AbstractHash Blake2b_224 b)
genFromTypeSpec TypeSpec fn (AbstractHash Blake2b_224 b)
_ = do
[Word8]
bytes <- forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a b. (a -> b) -> a -> b
$ forall a. Int -> Gen a -> Gen [a]
vectorOf Int
28 forall a. Arbitrary a => Gen a
arbitrary
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ forall algo a.
HashAlgorithm algo =>
ByteString -> Maybe (AbstractHash algo a)
abstractHashFromBytes ([Word8] -> ByteString
BS.pack [Word8]
bytes)
shrinkWithTypeSpec :: TypeSpec fn (AbstractHash Blake2b_224 b)
-> AbstractHash Blake2b_224 b -> [AbstractHash Blake2b_224 b]
shrinkWithTypeSpec TypeSpec fn (AbstractHash Blake2b_224 b)
_ AbstractHash Blake2b_224 b
_ = []
cardinalTypeSpec :: TypeSpec fn (AbstractHash Blake2b_224 b)
-> Specification fn Integer
cardinalTypeSpec TypeSpec fn (AbstractHash Blake2b_224 b)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
conformsTo :: HasCallStack =>
AbstractHash Blake2b_224 b
-> TypeSpec fn (AbstractHash Blake2b_224 b) -> Bool
conformsTo AbstractHash Blake2b_224 b
_ TypeSpec fn (AbstractHash Blake2b_224 b)
_ = Bool
True
toPreds :: Term fn (AbstractHash Blake2b_224 b)
-> TypeSpec fn (AbstractHash Blake2b_224 b) -> Pred fn
toPreds Term fn (AbstractHash Blake2b_224 b)
_ TypeSpec fn (AbstractHash Blake2b_224 b)
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance HasSimpleRep (StakeReference c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (StakeReference c)
instance HasSimpleRep Ptr
instance IsConwayUniv fn => HasSpec fn Ptr
instance HasSimpleRep CertIx where
type SimpleRep CertIx = Word16
toSimpleRep :: CertIx -> SimpleRep CertIx
toSimpleRep (CertIx Word64
w) = forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
w
fromSimpleRep :: SimpleRep CertIx -> CertIx
fromSimpleRep = Word16 -> CertIx
mkCertIx
instance IsConwayUniv fn => HasSpec fn CertIx
instance HasSimpleRep (Credential r c)
instance (IsConwayUniv fn, Typeable r, Crypto c) => HasSpec fn (Credential r c)
cKeyHashObj ::
(IsConwayUniv fn, Typeable r, Crypto c) => Term fn (KeyHash r c) -> Term fn (Credential r c)
cKeyHashObj :: forall (fn :: [*] -> * -> *) (r :: KeyRole) c.
(IsConwayUniv fn, Typeable r, Crypto c) =>
Term fn (KeyHash r c) -> Term fn (Credential r c)
cKeyHashObj = forall (c :: Symbol) a r (fn :: [*] -> * -> *).
(SimpleRep a ~ SOP (TheSop a),
TypeSpec fn a ~ TypeSpec fn (SOP (TheSop a)),
TypeList (ConstrOf c (TheSop a)), HasSpec fn a, HasSimpleRep a,
r ~ FunTy (MapList (Term fn) (ConstrOf c (TheSop a))) (Term fn a),
ResultType r ~ Term fn a, SOPTerm c fn (TheSop a),
ConstrTerm fn (ConstrOf c (TheSop a))) =>
r
con @"KeyHashObj"
cScriptHashObj ::
(IsConwayUniv fn, Typeable r, Crypto c) => Term fn (ScriptHash c) -> Term fn (Credential r c)
cScriptHashObj :: forall (fn :: [*] -> * -> *) (r :: KeyRole) c.
(IsConwayUniv fn, Typeable r, Crypto c) =>
Term fn (ScriptHash c) -> Term fn (Credential r c)
cScriptHashObj = forall (c :: Symbol) a r (fn :: [*] -> * -> *).
(SimpleRep a ~ SOP (TheSop a),
TypeSpec fn a ~ TypeSpec fn (SOP (TheSop a)),
TypeList (ConstrOf c (TheSop a)), HasSpec fn a, HasSimpleRep a,
r ~ FunTy (MapList (Term fn) (ConstrOf c (TheSop a))) (Term fn a),
ResultType r ~ Term fn a, SOPTerm c fn (TheSop a),
ConstrTerm fn (ConstrOf c (TheSop a))) =>
r
con @"ScriptHashObj"
instance HasSimpleRep (ScriptHash c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (ScriptHash c)
pickFromFixedPool :: Arbitrary a => Int -> Gen a
pickFromFixedPool :: forall a. Arbitrary a => Int -> Gen a
pickFromFixedPool Int
n = do
Int
seed <- (Int, Int) -> Gen Int
chooseInt (Int
0, Int
n)
forall n a. Integral n => n -> Gen a -> Gen a
variant Int
seed forall a. Arbitrary a => Gen a
arbitrary
genHashWithDuplicates :: HashAlgorithm h => Gen (Hash h b)
genHashWithDuplicates :: forall h b. HashAlgorithm h => Gen (Hash h b)
genHashWithDuplicates =
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ forall a. Arbitrary a => Int -> Gen a
pickFromFixedPool Int
20
, forall a. Arbitrary a => Gen a
arbitrary
]
instance (IsConwayUniv fn, Typeable r, Crypto c) => HasSpec fn (VRFVerKeyHash r c) where
type TypeSpec fn (VRFVerKeyHash r c) = ()
emptySpec :: TypeSpec fn (VRFVerKeyHash r c)
emptySpec = ()
combineSpec :: TypeSpec fn (VRFVerKeyHash r c)
-> TypeSpec fn (VRFVerKeyHash r c)
-> Specification fn (VRFVerKeyHash r c)
combineSpec TypeSpec fn (VRFVerKeyHash r c)
_ TypeSpec fn (VRFVerKeyHash r c)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn (VRFVerKeyHash r c) -> GenT m (VRFVerKeyHash r c)
genFromTypeSpec TypeSpec fn (VRFVerKeyHash r c)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a b. (a -> b) -> a -> b
$ forall (r :: KeyRoleVRF) c.
Hash (HASH c) KeyRoleVRF -> VRFVerKeyHash r c
VRFVerKeyHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall h b. HashAlgorithm h => Gen (Hash h b)
genHashWithDuplicates
cardinalTypeSpec :: TypeSpec fn (VRFVerKeyHash r c) -> Specification fn Integer
cardinalTypeSpec TypeSpec fn (VRFVerKeyHash r c)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn (VRFVerKeyHash r c)
-> VRFVerKeyHash r c -> [VRFVerKeyHash r c]
shrinkWithTypeSpec TypeSpec fn (VRFVerKeyHash r c)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack =>
VRFVerKeyHash r c -> TypeSpec fn (VRFVerKeyHash r c) -> Bool
conformsTo VRFVerKeyHash r c
_ TypeSpec fn (VRFVerKeyHash r c)
_ = Bool
True
toPreds :: Term fn (VRFVerKeyHash r c)
-> TypeSpec fn (VRFVerKeyHash r c) -> Pred fn
toPreds Term fn (VRFVerKeyHash r c)
_ TypeSpec fn (VRFVerKeyHash r c)
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance (IsConwayUniv fn, HashAlgorithm a, Typeable b) => HasSpec fn (Hash a b) where
type TypeSpec fn (Hash a b) = ()
emptySpec :: TypeSpec fn (Hash a b)
emptySpec = ()
combineSpec :: TypeSpec fn (Hash a b)
-> TypeSpec fn (Hash a b) -> Specification fn (Hash a b)
combineSpec TypeSpec fn (Hash a b)
_ TypeSpec fn (Hash a b)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn (Hash a b) -> GenT m (Hash a b)
genFromTypeSpec TypeSpec fn (Hash a b)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall h b. HashAlgorithm h => Gen (Hash h b)
genHashWithDuplicates
cardinalTypeSpec :: TypeSpec fn (Hash a b) -> Specification fn Integer
cardinalTypeSpec TypeSpec fn (Hash a b)
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn (Hash a b) -> Hash a b -> [Hash a b]
shrinkWithTypeSpec TypeSpec fn (Hash a b)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Hash a b -> TypeSpec fn (Hash a b) -> Bool
conformsTo Hash a b
_ TypeSpec fn (Hash a b)
_ = Bool
True
toPreds :: Term fn (Hash a b) -> TypeSpec fn (Hash a b) -> Pred fn
toPreds Term fn (Hash a b)
_ TypeSpec fn (Hash a b)
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance HasSimpleRep (ConwayTxCert era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (ConwayTxCert era)
instance HasSimpleRep (ConwayDelegCert c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (ConwayDelegCert c)
instance HasSimpleRep (PoolCert c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (PoolCert c)
instance HasSimpleRep (PoolParams c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (PoolParams c)
instance HasSimpleRep PoolMetadata
instance IsConwayUniv fn => HasSpec fn PoolMetadata
instance IsConwayUniv fn => HasSpec fn StakePoolRelay where
type TypeSpec fn StakePoolRelay = ()
emptySpec :: TypeSpec fn StakePoolRelay
emptySpec = ()
combineSpec :: TypeSpec fn StakePoolRelay
-> TypeSpec fn StakePoolRelay -> Specification fn StakePoolRelay
combineSpec TypeSpec fn StakePoolRelay
_ TypeSpec fn StakePoolRelay
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn StakePoolRelay -> GenT m StakePoolRelay
genFromTypeSpec TypeSpec fn StakePoolRelay
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn StakePoolRelay -> Specification fn Integer
cardinalTypeSpec TypeSpec fn StakePoolRelay
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn StakePoolRelay -> StakePoolRelay -> [StakePoolRelay]
shrinkWithTypeSpec TypeSpec fn StakePoolRelay
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack =>
StakePoolRelay -> TypeSpec fn StakePoolRelay -> Bool
conformsTo StakePoolRelay
_ TypeSpec fn StakePoolRelay
_ = Bool
True
toPreds :: Term fn StakePoolRelay -> TypeSpec fn StakePoolRelay -> Pred fn
toPreds Term fn StakePoolRelay
_ TypeSpec fn StakePoolRelay
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance HasSimpleRep Port
instance IsConwayUniv fn => HasSpec fn Port
instance HasSimpleRep (ConwayGovCert c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (ConwayGovCert c)
instance HasSimpleRep (Anchor c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (Anchor c)
instance HasSimpleRep Url
instance IsConwayUniv fn => HasSpec fn Url where
type TypeSpec fn Url = ()
emptySpec :: TypeSpec fn Url
emptySpec = ()
combineSpec :: TypeSpec fn Url -> TypeSpec fn Url -> Specification fn Url
combineSpec TypeSpec fn Url
_ TypeSpec fn Url
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn Url -> GenT m Url
genFromTypeSpec TypeSpec fn Url
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn Url -> Specification fn Integer
cardinalTypeSpec TypeSpec fn Url
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn Url -> Url -> [Url]
shrinkWithTypeSpec TypeSpec fn Url
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Url -> TypeSpec fn Url -> Bool
conformsTo Url
_ TypeSpec fn Url
_ = Bool
True
toPreds :: Term fn Url -> TypeSpec fn Url -> Pred fn
toPreds Term fn Url
_ TypeSpec fn Url
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance IsConwayUniv fn => HasSpec fn Text where
type TypeSpec fn Text = ()
emptySpec :: TypeSpec fn Text
emptySpec = ()
combineSpec :: TypeSpec fn Text -> TypeSpec fn Text -> Specification fn Text
combineSpec TypeSpec fn Text
_ TypeSpec fn Text
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn Text -> GenT m Text
genFromTypeSpec TypeSpec fn Text
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn Text -> Specification fn Integer
cardinalTypeSpec TypeSpec fn Text
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn Text -> Text -> [Text]
shrinkWithTypeSpec TypeSpec fn Text
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Text -> TypeSpec fn Text -> Bool
conformsTo Text
_ TypeSpec fn Text
_ = Bool
True
toPreds :: Term fn Text -> TypeSpec fn Text -> Pred fn
toPreds Term fn Text
_ TypeSpec fn Text
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
newtype StringSpec fn = StringSpec {forall (fn :: [*] -> * -> *). StringSpec fn -> Specification fn Int
strSpecLen :: Specification fn Int}
deriving instance IsConwayUniv fn => Show (StringSpec fn)
instance HasSpec fn Int => Semigroup (StringSpec fn) where
StringSpec Specification fn Int
len <> :: StringSpec fn -> StringSpec fn -> StringSpec fn
<> StringSpec Specification fn Int
len' = forall (fn :: [*] -> * -> *). Specification fn Int -> StringSpec fn
StringSpec (Specification fn Int
len forall a. Semigroup a => a -> a -> a
<> Specification fn Int
len')
instance HasSpec fn Int => Monoid (StringSpec fn) where
mempty :: StringSpec fn
mempty = forall (fn :: [*] -> * -> *). Specification fn Int -> StringSpec fn
StringSpec forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
instance IsConwayUniv fn => HasSpec fn ByteString where
type TypeSpec fn ByteString = StringSpec fn
emptySpec :: TypeSpec fn ByteString
emptySpec = forall a. Monoid a => a
mempty
combineSpec :: TypeSpec fn ByteString
-> TypeSpec fn ByteString -> Specification fn ByteString
combineSpec TypeSpec fn ByteString
s TypeSpec fn ByteString
s' = forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
TypeSpec fn a -> Specification fn a
typeSpec forall a b. (a -> b) -> a -> b
$ TypeSpec fn ByteString
s forall a. Semigroup a => a -> a -> a
<> TypeSpec fn ByteString
s'
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn ByteString -> GenT m ByteString
genFromTypeSpec (StringSpec Specification fn Int
ls) = do
Int
len <- forall (fn :: [*] -> * -> *) a (m :: * -> *).
(HasCallStack, HasSpec fn a, MonadGenError m) =>
Specification fn a -> GenT m a
genFromSpecT Specification fn Int
ls
[Word8] -> ByteString
BS.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
MonadGenError m =>
Int -> GenT GE a -> GenT m [a]
vectorOfT Int
len (forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary)
shrinkWithTypeSpec :: TypeSpec fn ByteString -> ByteString -> [ByteString]
shrinkWithTypeSpec TypeSpec fn ByteString
_ = forall a. Arbitrary a => a -> [a]
shrink
cardinalTypeSpec :: TypeSpec fn ByteString -> Specification fn Integer
cardinalTypeSpec TypeSpec fn ByteString
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
conformsTo :: HasCallStack => ByteString -> TypeSpec fn ByteString -> Bool
conformsTo ByteString
bs (StringSpec Specification fn Int
ls) = ByteString -> Int
BS.length ByteString
bs forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
a -> Specification fn a -> Bool
`conformsToSpec` Specification fn Int
ls
toPreds :: Term fn ByteString -> TypeSpec fn ByteString -> Pred fn
toPreds Term fn ByteString
str (StringSpec Specification fn Int
len) = forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
Term fn a -> Specification fn a -> Pred fn
satisfies (forall (fn :: [*] -> * -> *) s.
(Member (StringFn fn) fn, StringLike s, HasSpec fn s) =>
Term fn s -> Term fn Int
strLen_ Term fn ByteString
str) Specification fn Int
len
instance IsConwayUniv fn => HasSpec fn ShortByteString where
type TypeSpec fn ShortByteString = StringSpec fn
emptySpec :: TypeSpec fn ShortByteString
emptySpec = forall a. Monoid a => a
mempty
combineSpec :: TypeSpec fn ShortByteString
-> TypeSpec fn ShortByteString -> Specification fn ShortByteString
combineSpec TypeSpec fn ShortByteString
s TypeSpec fn ShortByteString
s' = forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
TypeSpec fn a -> Specification fn a
typeSpec forall a b. (a -> b) -> a -> b
$ TypeSpec fn ShortByteString
s forall a. Semigroup a => a -> a -> a
<> TypeSpec fn ShortByteString
s'
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn ShortByteString -> GenT m ShortByteString
genFromTypeSpec (StringSpec Specification fn Int
ls) = do
Int
len <- forall (fn :: [*] -> * -> *) a (m :: * -> *).
(HasCallStack, HasSpec fn a, MonadGenError m) =>
Specification fn a -> GenT m a
genFromSpecT Specification fn Int
ls
[Word8] -> ShortByteString
SBS.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a.
MonadGenError m =>
Int -> GenT GE a -> GenT m [a]
vectorOfT Int
len (forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary)
shrinkWithTypeSpec :: TypeSpec fn ShortByteString -> ShortByteString -> [ShortByteString]
shrinkWithTypeSpec TypeSpec fn ShortByteString
_ = forall a. Arbitrary a => a -> [a]
shrink
cardinalTypeSpec :: TypeSpec fn ShortByteString -> Specification fn Integer
cardinalTypeSpec TypeSpec fn ShortByteString
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
conformsTo :: HasCallStack =>
ShortByteString -> TypeSpec fn ShortByteString -> Bool
conformsTo ShortByteString
bs (StringSpec Specification fn Int
ls) = ShortByteString -> Int
SBS.length ShortByteString
bs forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
a -> Specification fn a -> Bool
`conformsToSpec` Specification fn Int
ls
toPreds :: Term fn ShortByteString -> TypeSpec fn ShortByteString -> Pred fn
toPreds Term fn ShortByteString
str (StringSpec Specification fn Int
len) = forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
Term fn a -> Specification fn a -> Pred fn
satisfies (forall (fn :: [*] -> * -> *) s.
(Member (StringFn fn) fn, StringLike s, HasSpec fn s) =>
Term fn s -> Term fn Int
strLen_ Term fn ShortByteString
str) Specification fn Int
len
instance StringLike ByteString where
lengthSpec :: forall (fn :: [*] -> * -> *).
IsConwayUniv fn =>
Specification fn Int -> TypeSpec fn ByteString
lengthSpec = forall (fn :: [*] -> * -> *). Specification fn Int -> StringSpec fn
StringSpec
getLengthSpec :: forall (fn :: [*] -> * -> *).
TypeSpec fn ByteString -> Specification fn Int
getLengthSpec (StringSpec Specification fn Int
len) = Specification fn Int
len
getLength :: ByteString -> Int
getLength = ByteString -> Int
BS.length
instance StringLike ShortByteString where
lengthSpec :: forall (fn :: [*] -> * -> *).
IsConwayUniv fn =>
Specification fn Int -> TypeSpec fn ShortByteString
lengthSpec = forall (fn :: [*] -> * -> *). Specification fn Int -> StringSpec fn
StringSpec
getLengthSpec :: forall (fn :: [*] -> * -> *).
TypeSpec fn ShortByteString -> Specification fn Int
getLengthSpec (StringSpec Specification fn Int
len) = Specification fn Int
len
getLength :: ShortByteString -> Int
getLength = ShortByteString -> Int
SBS.length
data StringFn (fn :: [Type] -> Type -> Type) as b where
LengthFn :: StringLike s => StringFn fn '[s] Int
deriving instance IsConwayUniv fn => Show (StringFn fn as b)
deriving instance IsConwayUniv fn => Eq (StringFn fn as b)
strLen_ ::
forall fn s.
(Member (StringFn fn) fn, StringLike s, HasSpec fn s) =>
Term fn s ->
Term fn Int
strLen_ :: forall (fn :: [*] -> * -> *) s.
(Member (StringFn fn) fn, StringLike s, HasSpec fn s) =>
Term fn s -> Term fn Int
strLen_ = forall (fn :: [*] -> * -> *) b (as :: [*]).
(HasSpec fn b, Typeable as, TypeList as, All (HasSpec fn) as) =>
fn as b -> FunTy (MapList (Term fn) as) (Term fn b)
app (forall (fn :: [*] -> * -> *) (fnU :: [*] -> * -> *) (as :: [*]) b.
Member fn fnU =>
fn as b -> fnU as b
injectFn forall a b. (a -> b) -> a -> b
$ forall a (fn :: [*] -> * -> *).
StringLike a =>
StringFn fn '[a] Int
LengthFn @_ @fn)
instance FunctionLike (StringFn fn) where
sem :: forall (as :: [*]) b. StringFn fn as b -> FunTy as b
sem StringFn fn as b
LengthFn = forall s. StringLike s => s -> Int
getLength
instance IsConwayUniv fn => Functions (StringFn fn) fn where
propagateSpecFun :: forall (as :: [*]) a b.
(TypeList as, Typeable as, HasSpec fn a, HasSpec fn b,
All (HasSpec fn) as) =>
StringFn fn as b
-> ListCtx Value as (HOLE a)
-> Specification fn b
-> Specification fn a
propagateSpecFun StringFn fn as b
_ ListCtx Value as (HOLE a)
_ Specification fn b
TrueSpec = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
propagateSpecFun StringFn fn as b
_ ListCtx Value as (HOLE a)
_ (ErrorSpec NonEmpty [Char]
err) = forall (fn :: [*] -> * -> *) a.
NonEmpty [Char] -> Specification fn a
ErrorSpec NonEmpty [Char]
err
propagateSpecFun StringFn fn as b
fn ListCtx Value as (HOLE a)
ctx Specification fn b
spec = case StringFn fn as b
fn of
StringFn fn as b
_
| SuspendedSpec {} <- Specification fn b
spec
, ListCtx List Value as
pre HOLE a a
HOLE List Value as'
suf <- ListCtx Value as (HOLE a)
ctx ->
forall a (fn :: [*] -> * -> *) p.
(IsPred p fn, HasSpec fn a) =>
(Term fn a -> p) -> Specification fn a
constrained forall a b. (a -> b) -> a -> b
$ \Term fn a
x' ->
let args :: List (Term fn) (Append as (a : as'))
args =
forall {a} (f :: a -> *) (as :: [a]) (bs :: [a]).
List f as -> List f bs -> List f (Append as bs)
appendList
(forall {k} (f :: k -> *) (g :: k -> *) (as :: [k]).
(forall (a :: k). f a -> g a) -> List f as -> List g as
mapList (\(C.Value a
a) -> forall a (fn :: [*] -> * -> *). Show a => a -> Term fn a
lit a
a) List Value as
pre)
(Term fn a
x' forall {k} (f :: k -> *) (a :: k) (as1 :: [k]).
f a -> List f as1 -> List f (a : as1)
:> forall {k} (f :: k -> *) (g :: k -> *) (as :: [k]).
(forall (a :: k). f a -> g a) -> List f as -> List g as
mapList (\(C.Value a
a) -> forall a (fn :: [*] -> * -> *). Show a => a -> Term fn a
lit a
a) List Value as'
suf)
in forall (ts :: [*]) (f :: * -> *) r.
TypeList ts =>
FunTy (MapList f ts) r -> List f ts -> r
uncurryList (forall (fn :: [*] -> * -> *) b (as :: [*]).
(HasSpec fn b, Typeable as, TypeList as, All (HasSpec fn) as) =>
fn as b -> FunTy (MapList (Term fn) as) (Term fn b)
app @fn forall a b. (a -> b) -> a -> b
$ forall (fn :: [*] -> * -> *) (fnU :: [*] -> * -> *) (as :: [*]) b.
Member fn fnU =>
fn as b -> fnU as b
injectFn StringFn fn as b
fn) List (Term fn) (Append as (a : as'))
args forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
Term fn a -> Specification fn a -> Pred fn
`satisfies` Specification fn b
spec
StringFn fn as b
LengthFn ->
case StringFn fn as b
fn of
(StringFn fn '[s] Int
_ :: StringFn fn '[s] Int)
| NilCtx HOLE a s
HOLE <- ListCtx Value as (HOLE a)
ctx -> forall (fn :: [*] -> * -> *) a.
HasSpec fn a =>
TypeSpec fn a -> Specification fn a
typeSpec forall a b. (a -> b) -> a -> b
$ forall s (fn :: [*] -> * -> *).
(StringLike s, IsConwayUniv fn) =>
Specification fn Int -> TypeSpec fn s
lengthSpec @s Specification fn b
spec
mapTypeSpec :: forall a b.
(HasSpec fn a, HasSpec fn b) =>
StringFn fn '[a] b -> TypeSpec fn a -> Specification fn b
mapTypeSpec f :: StringFn fn '[a] b
f@StringFn fn '[a] b
LengthFn TypeSpec fn a
ss =
case StringFn fn '[a] b
f of
(StringFn fn '[a] Int
_ :: StringFn fn '[s] Int) -> forall s (fn :: [*] -> * -> *).
StringLike s =>
TypeSpec fn s -> Specification fn Int
getLengthSpec @s TypeSpec fn a
ss
class StringLike s where
lengthSpec :: IsConwayUniv fn => Specification fn Int -> TypeSpec fn s
getLengthSpec :: TypeSpec fn s -> Specification fn Int
getLength :: s -> Int
instance HasSimpleRep (Delegatee c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (Delegatee c)
instance HasSimpleRep (DRep c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (DRep c)
instance HasSimpleRep (Withdrawals c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (Withdrawals c)
instance HasSimpleRep (RewardAccount c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (RewardAccount c)
instance HasSimpleRep Network
instance IsConwayUniv fn => HasSpec fn Network
instance HasSimpleRep (MultiAsset c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (MultiAsset c) where
emptySpec :: TypeSpec fn (MultiAsset c)
emptySpec =
forall k (fn :: [*] -> * -> *) v. Ord k => MapSpec fn k v
defaultMapSpec
{ mapSpecElem :: Specification fn (PolicyID c, Map AssetName Integer)
mapSpecElem = forall a (fn :: [*] -> * -> *) p.
(Cases (SimpleRep a) ~ '[SimpleRep a],
TypeSpec fn a ~ TypeSpec fn (SimpleRep a),
HasSpec fn (SimpleRep a), HasSimpleRep a,
All (HasSpec fn) (Args (SimpleRep a)), IsProd (SimpleRep a),
HasSpec fn a, IsPred p fn) =>
FunTy (MapList (Term fn) (Args (SimpleRep a))) p
-> Specification fn a
constrained' forall a b. (a -> b) -> a -> b
$ \Term fn (PolicyID c)
_ Term fn (Map AssetName Integer)
innerMap ->
forall t a (fn :: [*] -> * -> *) p.
(Forallable t a, HasSpec fn t, HasSpec fn a, IsPred p fn) =>
Term fn t -> (Term fn a -> p) -> Pred fn
forAll Term fn (Map AssetName Integer)
innerMap forall a b. (a -> b) -> a -> b
$ \Term fn (AssetName, Integer)
kv' ->
forall a (fn :: [*] -> * -> *). Show a => a -> Term fn a
lit Integer
0 forall a (fn :: [*] -> * -> *).
(Ord a, OrdLike fn a) =>
Term fn a -> Term fn a -> Term fn Bool
<=. forall (fn :: [*] -> * -> *) a b.
(HasSpec fn a, HasSpec fn b) =>
Term fn (a, b) -> Term fn b
snd_ Term fn (AssetName, Integer)
kv'
}
instance HasSimpleRep AssetName where
type SimpleRep AssetName = ShortByteString
toSimpleRep :: AssetName -> SimpleRep AssetName
toSimpleRep (AssetName ShortByteString
sbs) = ShortByteString
sbs
fromSimpleRep :: SimpleRep AssetName -> AssetName
fromSimpleRep SimpleRep AssetName
sbs = ShortByteString -> AssetName
AssetName SimpleRep AssetName
sbs
instance IsConwayUniv fn => HasSpec fn AssetName
instance HasSimpleRep (PolicyID c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (PolicyID c)
instance HasSimpleRep (AuxiliaryDataHash c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (AuxiliaryDataHash c)
instance HasSimpleRep (VotingProcedures era)
instance (IsConwayUniv fn, Typeable era, Crypto (EraCrypto era)) => HasSpec fn (VotingProcedures era)
instance HasSimpleRep (VotingProcedure era)
instance (IsConwayUniv fn, Typeable era, Crypto (EraCrypto era)) => HasSpec fn (VotingProcedure era)
instance HasSimpleRep Vote
instance IsConwayUniv fn => HasSpec fn Vote
instance HasSimpleRep (GovActionId c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (GovActionId c) where
shrinkWithTypeSpec :: TypeSpec fn (GovActionId c) -> GovActionId c -> [GovActionId c]
shrinkWithTypeSpec TypeSpec fn (GovActionId c)
_ GovActionId c
_ = []
instance HasSimpleRep GovActionIx
instance IsConwayUniv fn => HasSpec fn GovActionIx
instance HasSimpleRep (GovPurposeId p era)
instance (Typeable p, IsConwayUniv fn, Era era) => HasSpec fn (GovPurposeId p era)
instance HasSimpleRep (GovAction era)
instance (IsConwayUniv fn, EraSpecPParams era) => HasSpec fn (GovAction era)
instance HasSimpleRep (Constitution era)
instance (IsConwayUniv fn, EraPParams era) => HasSpec fn (Constitution era)
instance HasSimpleRep (ConwayPParams StrictMaybe c)
instance
( IsConwayUniv fn
, Typeable c
) =>
HasSpec fn (ConwayPParams StrictMaybe c)
instance HasSimpleRep (ConwayPParams Identity era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (ConwayPParams Identity era)
instance HasSimpleRep CoinPerByte where
type SimpleRep CoinPerByte = Coin
fromSimpleRep :: SimpleRep CoinPerByte -> CoinPerByte
fromSimpleRep = Coin -> CoinPerByte
CoinPerByte
toSimpleRep :: CoinPerByte -> SimpleRep CoinPerByte
toSimpleRep = CoinPerByte -> Coin
unCoinPerByte
instance IsConwayUniv fn => HasSpec fn CoinPerByte
instance IsConwayUniv fn => HasSpec fn Char where
type TypeSpec fn Char = ()
emptySpec :: TypeSpec fn Char
emptySpec = ()
combineSpec :: TypeSpec fn Char -> TypeSpec fn Char -> Specification fn Char
combineSpec TypeSpec fn Char
_ TypeSpec fn Char
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn Char -> GenT m Char
genFromTypeSpec TypeSpec fn Char
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn Char -> Specification fn Integer
cardinalTypeSpec TypeSpec fn Char
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn Char -> Char -> [Char]
shrinkWithTypeSpec TypeSpec fn Char
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Char -> TypeSpec fn Char -> Bool
conformsTo Char
_ TypeSpec fn Char
_ = Bool
True
toPreds :: Term fn Char -> TypeSpec fn Char -> Pred fn
toPreds Term fn Char
_ TypeSpec fn Char
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance IsConwayUniv fn => HasSpec fn CostModel where
type TypeSpec fn CostModel = ()
emptySpec :: TypeSpec fn CostModel
emptySpec = ()
combineSpec :: TypeSpec fn CostModel
-> TypeSpec fn CostModel -> Specification fn CostModel
combineSpec TypeSpec fn CostModel
_ TypeSpec fn CostModel
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec fn CostModel -> GenT m CostModel
genFromTypeSpec TypeSpec fn CostModel
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec fn CostModel -> Specification fn Integer
cardinalTypeSpec TypeSpec fn CostModel
_ = forall (fn :: [*] -> * -> *) a. Specification fn a
TrueSpec
shrinkWithTypeSpec :: TypeSpec fn CostModel -> CostModel -> [CostModel]
shrinkWithTypeSpec TypeSpec fn CostModel
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => CostModel -> TypeSpec fn CostModel -> Bool
conformsTo CostModel
_ TypeSpec fn CostModel
_ = Bool
True
toPreds :: Term fn CostModel -> TypeSpec fn CostModel -> Pred fn
toPreds Term fn CostModel
_ TypeSpec fn CostModel
_ = forall (fn :: [*] -> * -> *) p.
(BaseUniverse fn, PredLike p, UnivConstr p fn) =>
p -> Pred fn
toPred Bool
True
instance HasSimpleRep Language
instance IsConwayUniv fn => HasSpec fn Language
instance HasSimpleRep (NoUpdate a)
instance (IsConwayUniv fn, Typeable a) => HasSpec fn (NoUpdate a)
instance HasSimpleRep (THKD tag StrictMaybe a) where
type SimpleRep (THKD tag StrictMaybe a) = SOP (TheSop (StrictMaybe a))
fromSimpleRep :: SimpleRep (THKD tag StrictMaybe a) -> THKD tag StrictMaybe a
fromSimpleRep = forall (t :: PPGroups) (f :: * -> *) a. HKD f a -> THKD t f a
THKD forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep
toSimpleRep :: THKD tag StrictMaybe a -> SimpleRep (THKD tag StrictMaybe a)
toSimpleRep (THKD HKD StrictMaybe a
sm) = forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep HKD StrictMaybe a
sm
instance (IsConwayUniv fn, IsNormalType a, Typeable tag, HasSpec fn a) => HasSpec fn (THKD tag StrictMaybe a)
instance HasSimpleRep (THKD tag Identity a) where
type SimpleRep (THKD tag Identity a) = a
fromSimpleRep :: SimpleRep (THKD tag Identity a) -> THKD tag Identity a
fromSimpleRep = forall (t :: PPGroups) (f :: * -> *) a. HKD f a -> THKD t f a
THKD
toSimpleRep :: THKD tag Identity a -> SimpleRep (THKD tag Identity a)
toSimpleRep (THKD HKD Identity a
a) = HKD Identity a
a
instance (IsConwayUniv fn, IsNormalType a, Typeable tag, HasSpec fn a) => HasSpec fn (THKD tag Identity a)
instance HasSimpleRep GovActionPurpose
instance IsConwayUniv fn => HasSpec fn GovActionPurpose
instance HasSimpleRep (Voter c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (Voter c)
instance Ord a => HasSimpleRep (SOS.OSet a) where
type SimpleRep (SOS.OSet a) = [a]
fromSimpleRep :: SimpleRep (OSet a) -> OSet a
fromSimpleRep = forall a. Ord a => StrictSeq a -> OSet a
SOS.fromStrictSeq forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> StrictSeq a
StrictSeq.fromList
toSimpleRep :: OSet a -> SimpleRep (OSet a)
toSimpleRep = forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. OSet a -> StrictSeq a
SOS.toStrictSeq
instance (IsConwayUniv fn, Ord a, HasSpec fn a) => HasSpec fn (SOS.OSet a)
instance Ord a => Forallable (SOS.OSet a) a
instance HasSimpleRep (ProposalProcedure era)
instance
(IsConwayUniv fn, EraSpecPParams era) =>
HasSpec fn (ProposalProcedure era)
pProcDeposit_ ::
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (ProposalProcedure Conway) ->
Term fn Coin
pProcDeposit_ :: forall (fn :: [*] -> * -> *).
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (ProposalProcedure Conway) -> Term fn Coin
pProcDeposit_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @0
pProcGovAction_ ::
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (ProposalProcedure Conway) ->
Term fn (GovAction Conway)
pProcGovAction_ :: forall (fn :: [*] -> * -> *).
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (ProposalProcedure Conway) -> Term fn (GovAction Conway)
pProcGovAction_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @2
instance HasSimpleRep ValidityInterval
instance IsConwayUniv fn => HasSpec fn ValidityInterval
instance HasSimpleRep (DRepState c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (DRepState c)
instance HasSimpleRep (CommitteeAuthorization c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (CommitteeAuthorization c)
instance HasSimpleRep (CommitteeState era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (CommitteeState era)
instance HasSimpleRep (VState era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (VState era)
instance HasSimpleRep (PState era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (PState era)
instance HasSimpleRep (DState era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (DState era)
instance HasSimpleRep (FutureGenDeleg c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (FutureGenDeleg c)
instance HasSimpleRep (GenDelegPair c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (GenDelegPair c)
instance HasSimpleRep (GenDelegs c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (GenDelegs c)
instance HasSimpleRep (InstantaneousRewards c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (InstantaneousRewards c)
type UMapTypes c =
'[ Map (Credential 'Staking c) RDPair
, Map Ptr (Credential 'Staking c)
, Map (Credential 'Staking c) (KeyHash 'StakePool c)
, Map (Credential 'Staking c) (DRep c)
]
instance Crypto c => HasSimpleRep (UMap c) where
type SimpleRep (UMap c) = SOP '["UMap" ::: UMapTypes c]
toSimpleRep :: UMap c -> SimpleRep (UMap c)
toSimpleRep UMap c
um = forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"UMap" @'["UMap" ::: UMapTypes c] (forall c. UMap c -> Map (Credential 'Staking c) RDPair
rdPairMap UMap c
um) (forall c. UMap c -> Map Ptr (Credential 'Staking c)
ptrMap UMap c
um) (forall c.
UMap c -> Map (Credential 'Staking c) (KeyHash 'StakePool c)
sPoolMap UMap c
um) (forall c. UMap c -> Map (Credential 'Staking c) (DRep c)
dRepMap UMap c
um)
fromSimpleRep :: SimpleRep (UMap c) -> UMap c
fromSimpleRep SimpleRep (UMap c)
rep = forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["UMap" ::: UMapTypes c] SimpleRep (UMap c)
rep forall c.
Map (Credential 'Staking c) RDPair
-> Map Ptr (Credential 'Staking c)
-> Map (Credential 'Staking c) (KeyHash 'StakePool c)
-> Map (Credential 'Staking c) (DRep c)
-> UMap c
unify
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (UMap c)
instance HasSimpleRep RDPair where
type SimpleRep RDPair = SOP '["RDPair" ::: '[SimpleRep Coin, SimpleRep Coin]]
toSimpleRep :: RDPair -> SimpleRep RDPair
toSimpleRep (RDPair CompactForm Coin
rew CompactForm Coin
dep) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject
@"RDPair"
@'["RDPair" ::: '[SimpleRep Coin, SimpleRep Coin]]
(forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep CompactForm Coin
rew)
(forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep CompactForm Coin
dep)
fromSimpleRep :: SimpleRep RDPair -> RDPair
fromSimpleRep SimpleRep RDPair
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["RDPair" ::: '[SimpleRep Coin, SimpleRep Coin]]
SimpleRep RDPair
rep
( \Word64
rew Word64
dep ->
CompactForm Coin -> CompactForm Coin -> RDPair
RDPair
(forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep Word64
rew)
(forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep Word64
dep)
)
instance IsConwayUniv fn => HasSpec fn RDPair
instance HasSimpleRep (CertState era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (CertState era)
instance HasSimpleRep (GovRelation StrictMaybe era)
instance (IsConwayUniv fn, Era era) => HasSpec fn (GovRelation StrictMaybe era)
instance Era era => HasSimpleRep (GovEnv era)
instance (EraSpecPParams era, IsConwayUniv fn) => HasSpec fn (GovEnv era)
instance HasSimpleRep (GovActionState era)
instance (IsConwayUniv fn, Era era, EraSpecPParams era) => HasSpec fn (GovActionState era)
gasId_ ::
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway) ->
Term fn (GovActionId StandardCrypto)
gasId_ :: forall (fn :: [*] -> * -> *).
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway)
-> Term fn (GovActionId StandardCrypto)
gasId_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @0
gasCommitteeVotes_ ::
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway) ->
Term fn (Map (Credential 'HotCommitteeRole StandardCrypto) Vote)
gasCommitteeVotes_ :: forall (fn :: [*] -> * -> *).
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway)
-> Term fn (Map (Credential 'HotCommitteeRole StandardCrypto) Vote)
gasCommitteeVotes_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @1
gasDRepVotes_ ::
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway) ->
Term fn (Map (Credential 'DRepRole StandardCrypto) Vote)
gasDRepVotes_ :: forall (fn :: [*] -> * -> *).
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway)
-> Term fn (Map (Credential 'DRepRole StandardCrypto) Vote)
gasDRepVotes_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @2
gasProposalProcedure_ ::
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway) ->
Term fn (ProposalProcedure Conway)
gasProposalProcedure_ :: forall (fn :: [*] -> * -> *).
(EraSpecPParams Conway, IsConwayUniv fn) =>
Term fn (GovActionState Conway)
-> Term fn (ProposalProcedure Conway)
gasProposalProcedure_ = forall (n :: Natural) (fn :: [*] -> * -> *) a (c :: Symbol)
(as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec fn a ~ TypeSpec fn (ProdOver as), Select fn n as,
HasSpec fn a, HasSpec fn (ProdOver as), HasSimpleRep a) =>
Term fn a -> Term fn (At n as)
sel @4
type GAS era = GovActionState era
type ProposalTree era = (StrictMaybe (GovActionId (EraCrypto era)), [Tree (GAS era)])
type ProposalsType era =
'[ ProposalTree era
, ProposalTree era
, ProposalTree era
, ProposalTree era
, [GAS era]
]
instance EraPParams era => HasSimpleRep (Proposals era) where
type SimpleRep (Proposals era) = SOP '["Proposals" ::: ProposalsType era]
toSimpleRep :: Proposals era -> SimpleRep (Proposals era)
toSimpleRep Proposals era
props =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"Proposals" @'["Proposals" ::: ProposalsType era]
(TreeMaybe (GovActionId (EraCrypto era))
-> (StrictMaybe (GovActionId (EraCrypto era)), [Tree (GAS era)])
buildProposalTree forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate)
(TreeMaybe (GovActionId (EraCrypto era))
-> (StrictMaybe (GovActionId (EraCrypto era)), [Tree (GAS era)])
buildProposalTree forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'HardForkPurpose era)
grHardFork)
(TreeMaybe (GovActionId (EraCrypto era))
-> (StrictMaybe (GovActionId (EraCrypto era)), [Tree (GAS era)])
buildProposalTree forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'CommitteePurpose era)
grCommittee)
(TreeMaybe (GovActionId (EraCrypto era))
-> (StrictMaybe (GovActionId (EraCrypto era)), [Tree (GAS era)])
buildProposalTree forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
grConstitution)
(forall k a. Map k a -> [a]
Map.elems forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => Map k a -> Set k -> Map k a
Map.withoutKeys Map (GovActionId (EraCrypto era)) (GAS era)
idMap Set (GovActionId (EraCrypto era))
treeKeys)
where
GovRelation {TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
TreeMaybe (GovPurposeId 'HardForkPurpose era)
TreeMaybe (GovPurposeId 'CommitteePurpose era)
TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
grConstitution :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grCommittee :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grHardFork :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grPParamUpdate :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grConstitution :: TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
grCommittee :: TreeMaybe (GovPurposeId 'CommitteePurpose era)
grHardFork :: TreeMaybe (GovPurposeId 'HardForkPurpose era)
grPParamUpdate :: TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
..} = forall era.
(Era era, HasCallStack) =>
Proposals era -> GovRelation TreeMaybe era
toGovRelationTree Proposals era
props
idMap :: Map (GovActionId (EraCrypto era)) (GAS era)
idMap = forall era.
Proposals era
-> Map (GovActionId (EraCrypto era)) (GovActionState era)
proposalsActionsMap Proposals era
props
treeKeys :: Set (GovActionId (EraCrypto era))
treeKeys =
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap
TreeMaybe (GovActionId (EraCrypto era))
-> Set (GovActionId (EraCrypto era))
keys
[ coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate
, coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'HardForkPurpose era)
grHardFork
, coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'CommitteePurpose era)
grCommittee
, coerce :: forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
grConstitution
]
buildProposalTree :: TreeMaybe (GovActionId (EraCrypto era)) -> ProposalTree era
buildProposalTree :: TreeMaybe (GovActionId (EraCrypto era))
-> (StrictMaybe (GovActionId (EraCrypto era)), [Tree (GAS era)])
buildProposalTree (TreeMaybe (Node StrictMaybe (GovActionId (EraCrypto era))
mId [Tree (StrictMaybe (GovActionId (EraCrypto era)))]
cs)) = (StrictMaybe (GovActionId (EraCrypto era))
mId, forall a b. (a -> b) -> [a] -> [b]
map Tree (StrictMaybe (GovActionId (EraCrypto era))) -> Tree (GAS era)
buildTree [Tree (StrictMaybe (GovActionId (EraCrypto era)))]
cs)
buildTree :: Tree (StrictMaybe (GovActionId (EraCrypto era))) -> Tree (GAS era)
buildTree :: Tree (StrictMaybe (GovActionId (EraCrypto era))) -> Tree (GAS era)
buildTree (Node (SJust GovActionId (EraCrypto era)
gid) [Tree (StrictMaybe (GovActionId (EraCrypto era)))]
cs) | Just GAS era
gas <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup GovActionId (EraCrypto era)
gid Map (GovActionId (EraCrypto era)) (GAS era)
idMap = forall a. a -> [Tree a] -> Tree a
Node GAS era
gas (forall a b. (a -> b) -> [a] -> [b]
map Tree (StrictMaybe (GovActionId (EraCrypto era))) -> Tree (GAS era)
buildTree [Tree (StrictMaybe (GovActionId (EraCrypto era)))]
cs)
buildTree Tree (StrictMaybe (GovActionId (EraCrypto era)))
_ =
forall a. HasCallStack => [Char] -> a
error [Char]
"toSimpleRep @Proposals: toGovRelationTree returned trees with Nothing nodes below the root"
keys :: TreeMaybe (GovActionId (EraCrypto era)) -> Set (GovActionId (EraCrypto era))
keys :: TreeMaybe (GovActionId (EraCrypto era))
-> Set (GovActionId (EraCrypto era))
keys (TreeMaybe Tree (StrictMaybe (GovActionId (EraCrypto era)))
t) = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall a b. a -> (b -> a) -> StrictMaybe b -> a
strictMaybe forall a. Monoid a => a
mempty forall a. a -> Set a
Set.singleton) Tree (StrictMaybe (GovActionId (EraCrypto era)))
t
fromSimpleRep :: SimpleRep (Proposals era) -> Proposals era
fromSimpleRep SimpleRep (Proposals era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["Proposals" ::: ProposalsType era]
SimpleRep (Proposals era)
rep
forall a b. (a -> b) -> a -> b
$ \(StrictMaybe (GovActionId (EraCrypto era))
rPPUp, [Tree (GAS era)]
ppupTree) (StrictMaybe (GovActionId (EraCrypto era))
rHF, [Tree (GAS era)]
hfTree) (StrictMaybe (GovActionId (EraCrypto era))
rCom, [Tree (GAS era)]
comTree) (StrictMaybe (GovActionId (EraCrypto era))
rCon, [Tree (GAS era)]
conTree) [GAS era]
others ->
let root :: GovRelation StrictMaybe era
root = forall (f :: * -> *) era.
f (GovPurposeId 'PParamUpdatePurpose era)
-> f (GovPurposeId 'HardForkPurpose era)
-> f (GovPurposeId 'CommitteePurpose era)
-> f (GovPurposeId 'ConstitutionPurpose era)
-> GovRelation f era
GovRelation (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe (GovActionId (EraCrypto era))
rPPUp) (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe (GovActionId (EraCrypto era))
rHF) (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe (GovActionId (EraCrypto era))
rCom) (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe (GovActionId (EraCrypto era))
rCon)
oMap :: OMap (GovActionId (EraCrypto era)) (GAS era)
oMap = forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall {k} {v}. HasOKey k v => Tree v -> OMap k v
mkOMap) [[Tree (GAS era)]
ppupTree, [Tree (GAS era)]
hfTree, [Tree (GAS era)]
comTree, [Tree (GAS era)]
conTree] forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) k v.
(Foldable f, HasOKey k v) =>
f v -> OMap k v
OMap.fromFoldable [GAS era]
others
in forall era.
(HasCallStack, EraPParams era) =>
GovRelation StrictMaybe era
-> OMap (GovActionId (EraCrypto era)) (GovActionState era)
-> Proposals era
unsafeMkProposals GovRelation StrictMaybe era
root OMap (GovActionId (EraCrypto era)) (GAS era)
oMap
where
mkOMap :: Tree v -> OMap k v
mkOMap (Node v
a [Tree v]
ts) = v
a forall k v. HasOKey k v => v -> OMap k v -> OMap k v
OMap.<| forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Tree v -> OMap k v
mkOMap [Tree v]
ts
instance (EraSpecPParams era, IsConwayUniv fn) => HasSpec fn (Proposals era)
data ProposalsSplit = ProposalsSplit
{ ProposalsSplit -> Integer
psPPChange :: Integer
, ProposalsSplit -> Integer
psHFInitiation :: Integer
, ProposalsSplit -> Integer
psUpdateCommittee :: Integer
, ProposalsSplit -> Integer
psNewConstitution :: Integer
, ProposalsSplit -> Integer
psOthers :: Integer
}
deriving (Int -> ProposalsSplit -> ShowS
[ProposalsSplit] -> ShowS
ProposalsSplit -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ProposalsSplit] -> ShowS
$cshowList :: [ProposalsSplit] -> ShowS
show :: ProposalsSplit -> [Char]
$cshow :: ProposalsSplit -> [Char]
showsPrec :: Int -> ProposalsSplit -> ShowS
$cshowsPrec :: Int -> ProposalsSplit -> ShowS
Show, ProposalsSplit -> ProposalsSplit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProposalsSplit -> ProposalsSplit -> Bool
$c/= :: ProposalsSplit -> ProposalsSplit -> Bool
== :: ProposalsSplit -> ProposalsSplit -> Bool
$c== :: ProposalsSplit -> ProposalsSplit -> Bool
Eq, forall x. Rep ProposalsSplit x -> ProposalsSplit
forall x. ProposalsSplit -> Rep ProposalsSplit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProposalsSplit x -> ProposalsSplit
$cfrom :: forall x. ProposalsSplit -> Rep ProposalsSplit x
Generic)
instance EncCBOR ProposalsSplit where
encCBOR :: ProposalsSplit -> Encoding
encCBOR x :: ProposalsSplit
x@(ProposalsSplit Integer
_ Integer
_ Integer
_ Integer
_ Integer
_) =
let ProposalsSplit {Integer
psOthers :: Integer
psNewConstitution :: Integer
psUpdateCommittee :: Integer
psHFInitiation :: Integer
psPPChange :: Integer
psOthers :: ProposalsSplit -> Integer
psNewConstitution :: ProposalsSplit -> Integer
psUpdateCommittee :: ProposalsSplit -> Integer
psHFInitiation :: ProposalsSplit -> Integer
psPPChange :: ProposalsSplit -> Integer
..} = ProposalsSplit
x
in forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec Integer
-> Integer -> Integer -> Integer -> Integer -> ProposalsSplit
ProposalsSplit
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psPPChange
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psHFInitiation
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psUpdateCommittee
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psNewConstitution
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psOthers
instance DecCBOR ProposalsSplit where
decCBOR :: forall s. Decoder s ProposalsSplit
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD Integer
-> Integer -> Integer -> Integer -> Integer -> ProposalsSplit
ProposalsSplit
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance ToExpr ProposalsSplit
instance NFData ProposalsSplit
proposalSplitSum :: ProposalsSplit -> Integer
proposalSplitSum :: ProposalsSplit -> Integer
proposalSplitSum ProposalsSplit {Integer
psOthers :: Integer
psNewConstitution :: Integer
psUpdateCommittee :: Integer
psHFInitiation :: Integer
psPPChange :: Integer
psOthers :: ProposalsSplit -> Integer
psNewConstitution :: ProposalsSplit -> Integer
psUpdateCommittee :: ProposalsSplit -> Integer
psHFInitiation :: ProposalsSplit -> Integer
psPPChange :: ProposalsSplit -> Integer
..} =
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
[ Integer
psPPChange
, Integer
psHFInitiation
, Integer
psUpdateCommittee
, Integer
psNewConstitution
, Integer
psOthers
]
splitInto :: Integer -> Int -> Gen [Integer]
splitInto :: Integer -> Int -> Gen [Integer]
splitInto Integer
budget Int
numSplits = do
[NonNegative Int]
splits <- forall a. Int -> Gen a -> Gen [a]
vectorOf Int
numSplits forall a b. (a -> b) -> a -> b
$ forall a. Arbitrary a => Gen a
arbitrary @(NonNegative Int)
let unwrappedSplits :: [Int]
unwrappedSplits = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. NonNegative a -> a
getNonNegative [NonNegative Int]
splits
let splitsTotal :: Integer
splitsTotal = forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
unwrappedSplits
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$
if Integer
splitsTotal forall a. Eq a => a -> a -> Bool
== Integer
0 Bool -> Bool -> Bool
|| Integer
budget forall a. Eq a => a -> a -> Bool
== Integer
0
then forall a. Int -> a -> [a]
replicate Int
numSplits Integer
0
else (forall a. Num a => a -> a -> a
* (Integer
budget forall a. Integral a => a -> a -> a
`div` Integer
splitsTotal)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int]
unwrappedSplits
genProposalsSplit :: Integer -> Gen ProposalsSplit
genProposalsSplit :: Integer -> Gen ProposalsSplit
genProposalsSplit Integer
maxTotal = do
Integer
actualMaxTotal <- forall a. Random a => (a, a) -> Gen a
choose (Integer
0, Integer
maxTotal)
[Integer]
splits <- Integer
actualMaxTotal Integer -> Int -> Gen [Integer]
`splitInto` Int
5
case [Integer]
splits of
[ Integer
psPPChange
, Integer
psHFInitiation
, Integer
psUpdateCommittee
, Integer
psNewConstitution
, Integer
psOthers
] -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ProposalsSplit {Integer
psOthers :: Integer
psNewConstitution :: Integer
psUpdateCommittee :: Integer
psHFInitiation :: Integer
psPPChange :: Integer
psOthers :: Integer
psNewConstitution :: Integer
psUpdateCommittee :: Integer
psHFInitiation :: Integer
psPPChange :: Integer
..}
[Integer]
l ->
forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$
[Char]
"impossible: should have exactly 5 values, but has "
forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> [Char]
show (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Integer]
l)
instance
( HasSpec fn (SimpleRep (Proposals era))
, HasSpec fn (Proposals era)
, HasSimpleRep (Proposals era)
, IsConwayUniv fn
, era ~ Conway
, EraSpecPParams Conway
) =>
HasGenHint fn (Proposals era)
where
type Hint (Proposals era) = ProposalsSplit
giveHint :: Hint (Proposals era) -> Specification fn (Proposals era)
giveHint ProposalsSplit {Integer
psOthers :: Integer
psNewConstitution :: Integer
psUpdateCommittee :: Integer
psHFInitiation :: Integer
psPPChange :: Integer
psOthers :: ProposalsSplit -> Integer
psNewConstitution :: ProposalsSplit -> Integer
psUpdateCommittee :: ProposalsSplit -> Integer
psHFInitiation :: ProposalsSplit -> Integer
psPPChange :: ProposalsSplit -> Integer
..} = forall a (fn :: [*] -> * -> *) p.
(Cases (SimpleRep a) ~ '[SimpleRep a],
TypeSpec fn a ~ TypeSpec fn (SimpleRep a),
HasSpec fn (SimpleRep a), HasSimpleRep a,
All (HasSpec fn) (Args (SimpleRep a)), IsProd (SimpleRep a),
HasSpec fn a, IsPred p fn) =>
FunTy (MapList (Term fn) (Args (SimpleRep a))) p
-> Specification fn a
constrained' forall a b. (a -> b) -> a -> b
$ \Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
ppuTree Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
hfTree Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
comTree Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
conTree Term fn [GovActionState Conway]
others ->
[ forall {a} {a} {t} {fn :: [*] -> * -> *} {a}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec fn a,
HasGenHint fn t, HasGenHint fn a, Num a) =>
Hint t -> Term fn (a, t) -> [Pred fn]
limitForest Integer
psPPChange Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
ppuTree
, forall {a} {a} {t} {fn :: [*] -> * -> *} {a}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec fn a,
HasGenHint fn t, HasGenHint fn a, Num a) =>
Hint t -> Term fn (a, t) -> [Pred fn]
limitForest Integer
psHFInitiation Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
hfTree
, forall {a} {a} {t} {fn :: [*] -> * -> *} {a}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec fn a,
HasGenHint fn t, HasGenHint fn a, Num a) =>
Hint t -> Term fn (a, t) -> [Pred fn]
limitForest Integer
psUpdateCommittee Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
comTree
, forall {a} {a} {t} {fn :: [*] -> * -> *} {a}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec fn a,
HasGenHint fn t, HasGenHint fn a, Num a) =>
Hint t -> Term fn (a, t) -> [Pred fn]
limitForest Integer
psNewConstitution Term
fn
(StrictMaybe (GovActionId StandardCrypto),
[Tree (GovActionState Conway)])
conTree
, [forall (fn :: [*] -> * -> *) t.
HasGenHint fn t =>
Hint t -> Term fn t -> Pred fn
genHint Integer
psOthers Term fn [GovActionState Conway]
others]
]
where
limitForest :: Hint t -> Term fn (a, t) -> [Pred fn]
limitForest Hint t
limit Term fn (a, t)
forest =
[ forall (fn :: [*] -> * -> *) t.
HasGenHint fn t =>
Hint t -> Term fn t -> Pred fn
genHint Hint t
limit (forall (fn :: [*] -> * -> *) a b.
(HasSpec fn a, HasSpec fn b) =>
Term fn (a, b) -> Term fn b
snd_ Term fn (a, t)
forest)
, forall t a (fn :: [*] -> * -> *) p.
(Forallable t a, HasSpec fn t, HasSpec fn a, IsPred p fn) =>
Term fn t -> (Term fn a -> p) -> Pred fn
forAll (forall (fn :: [*] -> * -> *) a b.
(HasSpec fn a, HasSpec fn b) =>
Term fn (a, b) -> Term fn b
snd_ Term fn (a, t)
forest) forall a b. (a -> b) -> a -> b
$ forall (fn :: [*] -> * -> *) t.
HasGenHint fn t =>
Hint t -> Term fn t -> Pred fn
genHint (forall a. a -> Maybe a
Just a
2, Hint t
limit)
]
instance HasSimpleRep (EnactSignal Conway)
instance (IsConwayUniv fn, EraSpecPParams Conway) => HasSpec fn (EnactSignal Conway)
instance HasSimpleRep (EnactState era)
instance (EraSpecPParams era, IsConwayUniv fn) => HasSpec fn (EnactState era)
instance HasSimpleRep (Committee era)
instance (Era era, IsConwayUniv fn) => HasSpec fn (Committee era)
instance HasSimpleRep (RatifyEnv era)
instance (Era era, IsConwayUniv fn) => HasSpec fn (RatifyEnv era)
instance HasSimpleRep (RatifyState Conway)
instance (EraSpecPParams Conway, IsConwayUniv fn) => HasSpec fn (RatifyState Conway)
instance HasSimpleRep (RatifySignal Conway)
instance (EraSpecPParams Conway, IsConwayUniv fn) => HasSpec fn (RatifySignal Conway)
instance Crypto c => HasSimpleRep (PoolDistr c)
instance (Crypto c, IsConwayUniv fn) => HasSpec fn (PoolDistr c)
instance Crypto c => HasSimpleRep (IndividualPoolStake c)
instance (Crypto c, IsConwayUniv fn) => HasSpec fn (IndividualPoolStake c)
instance HasSimpleRep (ConwayGovCertEnv Conway)
instance (EraSpecPParams Conway, IsConwayUniv fn) => HasSpec fn (ConwayGovCertEnv Conway)
instance HasSimpleRep (PoolEnv era)
instance (EraSpecPParams era, IsConwayUniv fn) => HasSpec fn (PoolEnv era)
instance Era era => HasSimpleRep (CertEnv era)
instance (EraSpecPParams era, IsConwayUniv fn) => HasSpec fn (CertEnv era)
instance HasSimpleRep (NonMyopic c)
instance (IsConwayUniv fn, Crypto c) => HasSpec fn (NonMyopic c)
instance HasSimpleRep Likelihood
instance IsConwayUniv fn => HasSpec fn Likelihood
instance HasSimpleRep LogWeight
instance IsConwayUniv fn => HasSpec fn