{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# 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 (
StringW,
ProposalTree,
onJust',
onSized,
cKeyHashObj,
cScriptHashObj,
maryValueCoin_,
strLen_,
sizedValue_,
sizedSize_,
txOutVal_,
pProcDeposit_,
pProcGovAction_,
gasId_,
gasCommitteeVotes_,
gasDRepVotes_,
gasProposalProcedure_,
psPParamUpdate_,
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.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 (..))
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.Coin
import Cardano.Ledger.Compactible
import Cardano.Ledger.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.State
import Cardano.Ledger.Conway.TxBody
import Cardano.Ledger.Conway.TxCert
import Cardano.Ledger.Credential
import Cardano.Ledger.HKD
import Cardano.Ledger.Hashes (GenDelegPair (..), GenDelegs (..))
import Cardano.Ledger.Keys (BootstrapWitness, WitVKey, coerceKeyRole)
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.PoolParams
import Cardano.Ledger.Shelley.LedgerState
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.Val (Val)
import Constrained.API
import Constrained.Base
import Constrained.GenT (pureGen, vectorOfT)
import Constrained.Generic
import Constrained.List (List (..))
import Constrained.Spec.ListFoldy (genListWithSize)
import Constrained.Spec.Map
import Constrained.Spec.Size qualified as C
import Constrained.Spec.Tree ()
import GHC.TypeLits hiding (Text)
import Test.Cardano.Ledger.Constrained.Conway.Instances.Basic
import Test.Cardano.Ledger.Constrained.Conway.Instances.PParams ()
import Cardano.Crypto.Hash hiding (Blake2b_224)
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.Conway.Arbitrary ()
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, NonZero, forAll)
type ConwayTxBodyTypes =
'[ Set TxIn
, Set TxIn
, Set TxIn
, StrictSeq (Sized (TxOut ConwayEra))
, StrictMaybe (Sized (TxOut ConwayEra))
, StrictMaybe Coin
, SOS.OSet (ConwayTxCert ConwayEra)
, Withdrawals
, Coin
, ValidityInterval
, Set (KeyHash 'Witness)
, MultiAsset
, StrictMaybe ScriptIntegrityHash
, StrictMaybe TxAuxDataHash
, StrictMaybe Network
, VotingProcedures ConwayEra
, SOS.OSet (ProposalProcedure ConwayEra)
, StrictMaybe Coin
, Coin
]
instance HasSpec (ConwayTxBody ConwayEra)
instance HasSimpleRep (ConwayTxBody ConwayEra) where
type TheSop (ConwayTxBody ConwayEra) = '["ConwayTxBody" ::: ConwayTxBodyTypes]
toSimpleRep :: ConwayTxBody ConwayEra -> SimpleRep (ConwayTxBody ConwayEra)
toSimpleRep ConwayTxBody {Set (KeyHash 'Witness)
Set TxIn
OSet (TxCert ConwayEra)
OSet (ProposalProcedure ConwayEra)
Withdrawals
ValidityInterval
StrictMaybe ScriptIntegrityHash
StrictMaybe TxAuxDataHash
StrictMaybe Coin
StrictMaybe (Sized (TxOut ConwayEra))
StrictMaybe Network
Coin
VotingProcedures ConwayEra
StrictSeq (Sized (TxOut ConwayEra))
MultiAsset
ctbSpendInputs :: forall era. ConwayEraTxBody era => ConwayTxBody era -> Set TxIn
ctbCollateralInputs :: forall era. ConwayEraTxBody era => ConwayTxBody era -> Set TxIn
ctbReferenceInputs :: forall era. ConwayEraTxBody era => ConwayTxBody era -> Set TxIn
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 (TxCert era)
ctbWithdrawals :: forall era. ConwayEraTxBody era => ConwayTxBody era -> Withdrawals
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)
ctbMint :: forall era. ConwayEraTxBody era => ConwayTxBody era -> MultiAsset
ctbScriptIntegrityHash :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe ScriptIntegrityHash
ctbAdHash :: forall era.
ConwayEraTxBody era =>
ConwayTxBody era -> StrictMaybe TxAuxDataHash
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)
ctbVotingProcedures :: VotingProcedures ConwayEra
ctbTxNetworkId :: StrictMaybe Network
ctbAdHash :: StrictMaybe TxAuxDataHash
ctbScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
ctbMint :: MultiAsset
ctbReqSignerHashes :: Set (KeyHash 'Witness)
ctbVldt :: ValidityInterval
ctbTxfee :: Coin
ctbWithdrawals :: Withdrawals
ctbCerts :: OSet (TxCert ConwayEra)
ctbTotalCollateral :: StrictMaybe Coin
ctbCollateralReturn :: StrictMaybe (Sized (TxOut ConwayEra))
ctbOutputs :: StrictSeq (Sized (TxOut ConwayEra))
ctbReferenceInputs :: Set TxIn
ctbCollateralInputs :: Set TxIn
ctbSpendInputs :: Set TxIn
..} =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"ConwayTxBody" @'["ConwayTxBody" ::: ConwayTxBodyTypes]
Set TxIn
ctbSpendInputs
Set TxIn
ctbCollateralInputs
Set TxIn
ctbReferenceInputs
StrictSeq (Sized (TxOut ConwayEra))
ctbOutputs
StrictMaybe (Sized (TxOut ConwayEra))
ctbCollateralReturn
StrictMaybe Coin
ctbTotalCollateral
OSet (TxCert ConwayEra)
ctbCerts
Withdrawals
ctbWithdrawals
Coin
ctbTxfee
ValidityInterval
ctbVldt
Set (KeyHash 'Witness)
ctbReqSignerHashes
MultiAsset
ctbMint
StrictMaybe ScriptIntegrityHash
ctbScriptIntegrityHash
StrictMaybe TxAuxDataHash
ctbAdHash
StrictMaybe Network
ctbTxNetworkId
VotingProcedures ConwayEra
ctbVotingProcedures
OSet (ProposalProcedure ConwayEra)
ctbProposalProcedures
StrictMaybe Coin
ctbCurrentTreasuryValue
Coin
ctbTreasuryDonation
fromSimpleRep :: SimpleRep (ConwayTxBody ConwayEra) -> ConwayTxBody ConwayEra
fromSimpleRep SimpleRep (ConwayTxBody ConwayEra)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ConwayTxBody" ::: ConwayTxBodyTypes] SimpleRep (ConwayTxBody ConwayEra)
rep forall era.
ConwayEraTxBody era =>
Set TxIn
-> Set TxIn
-> Set TxIn
-> StrictSeq (Sized (TxOut era))
-> StrictMaybe (Sized (TxOut era))
-> StrictMaybe Coin
-> OSet (TxCert era)
-> Withdrawals
-> Coin
-> ValidityInterval
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> 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 HasSpec DeltaCoin
instance OrdLike DeltaCoin
instance NumLike DeltaCoin
instance Foldy DeltaCoin where
genList :: forall (m :: * -> *).
MonadGenError m =>
Specification DeltaCoin
-> Specification DeltaCoin -> GenT m [DeltaCoin]
genList Specification DeltaCoin
s Specification 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 a (m :: * -> *).
(Foldy a, MonadGenError m) =>
Specification a -> Specification a -> GenT m [a]
genList @Integer (forall a.
(HasSpec (SimpleRep a), HasSimpleRep a,
TypeSpec a ~ TypeSpec (SimpleRep a),
Logic "fromGenericFn" BaseW '[SimpleRep a] a) =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
s) (forall a.
(HasSpec (SimpleRep a), HasSimpleRep a,
TypeSpec a ~ TypeSpec (SimpleRep a),
Logic "fromGenericFn" BaseW '[SimpleRep a] a) =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
s')
theAddFn :: IntW "addFn" '[DeltaCoin, DeltaCoin] DeltaCoin
theAddFn = forall b. NumLike b => IntW "addFn" '[b, b] b
AddW
theZero :: DeltaCoin
theZero = Integer -> DeltaCoin
DeltaCoin Integer
0
genSizedList :: forall (m :: * -> *).
MonadGenError m =>
Specification Integer
-> Specification DeltaCoin
-> Specification DeltaCoin
-> GenT m [DeltaCoin]
genSizedList Specification Integer
sz Specification DeltaCoin
elemSpec Specification DeltaCoin
foldSpec =
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 a (m :: * -> *).
(Foldy a, TypeSpec a ~ NumSpec a, MonadGenError m, Random a,
Integral a) =>
Specification Integer
-> Specification a -> Specification a -> GenT m [a]
genListWithSize @Integer Specification Integer
sz (forall a.
(HasSpec (SimpleRep a), HasSimpleRep a,
TypeSpec a ~ TypeSpec (SimpleRep a),
Logic "fromGenericFn" BaseW '[SimpleRep a] a) =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
elemSpec) (forall a.
(HasSpec (SimpleRep a), HasSimpleRep a,
TypeSpec a ~ TypeSpec (SimpleRep a),
Logic "fromGenericFn" BaseW '[SimpleRep a] a) =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
foldSpec)
noNegativeValues :: Bool
noNegativeValues = Bool
False
deriving via Integer instance Num DeltaCoin
instance (Typeable (TxCert era), Typeable era) => HasSimpleRep (GovSignal era)
instance HasSpec (GovSignal ConwayEra)
instance HasSimpleRep SlotNo
instance OrdLike SlotNo
instance HasSpec SlotNo
instance HasSimpleRep EpochNo
instance OrdLike EpochNo
instance HasSpec EpochNo
instance NumLike EpochNo
instance HasSimpleRep TxIx
instance HasSpec TxIx
instance Typeable index => HasSpec (SafeHash index) where
type TypeSpec (SafeHash index) = ()
emptySpec :: TypeSpec (SafeHash index)
emptySpec = ()
combineSpec :: TypeSpec (SafeHash index)
-> TypeSpec (SafeHash index) -> Specification (SafeHash index)
combineSpec TypeSpec (SafeHash index)
_ TypeSpec (SafeHash index)
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (SafeHash index) -> GenT m (SafeHash index)
genFromTypeSpec TypeSpec (SafeHash index)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec (SafeHash index) -> Specification Integer
cardinalTypeSpec TypeSpec (SafeHash index)
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec (SafeHash index) -> SafeHash index -> [SafeHash index]
shrinkWithTypeSpec TypeSpec (SafeHash index)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => SafeHash index -> TypeSpec (SafeHash index) -> Bool
conformsTo SafeHash index
_ TypeSpec (SafeHash index)
_ = Bool
True
toPreds :: Term (SafeHash index) -> TypeSpec (SafeHash index) -> Pred
toPreds Term (SafeHash index)
_ TypeSpec (SafeHash index)
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSimpleRep TxId
instance HasSpec TxId
instance HasSimpleRep TxIn
instance HasSpec TxIn
instance Typeable a => 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 HasSpec a => HasSpec (StrictSeq a)
instance Typeable a => Forallable (StrictSeq a) a
instance Typeable a => 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 HasSpec a => HasSpec (Seq a)
instance Typeable a => Forallable (Seq a) a
instance HasSpec a => C.Sized (Seq a)
instance Typeable a => HasSimpleRep (Sized a)
instance HasSpec a => HasSpec (Sized a)
sizedValue_ :: (HasSpec (Sized a), HasSpec a) => Term (Sized a) -> Term a
sizedValue_ :: forall a.
(HasSpec (Sized a), HasSpec a) =>
Term (Sized a) -> Term a
sizedValue_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @0
sizedSize_ :: (HasSpec (Sized a), HasSpec a) => Term (Sized a) -> Term Int64
sizedSize_ :: forall a.
(HasSpec (Sized a), HasSpec a) =>
Term (Sized a) -> Term Int64
sizedSize_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @1
instance HasSimpleRep Addr28Extra
instance HasSpec Addr28Extra
instance HasSimpleRep DataHash32
instance HasSpec DataHash32
type ShelleyTxOutTypes era =
'[ Addr
, 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
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
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 -> Value era -> ShelleyTxOut era
ShelleyTxOut
instance (EraTxOut era, HasSpec (Value era)) => HasSpec (ShelleyTxOut era)
type AlonzoTxOutTypes era =
'[ Addr
, Value era
, StrictMaybe DataHash
]
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
addr Value era
val StrictMaybe (SafeHash EraIndependentData)
mdat) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"AlonzoTxOut" @'["AlonzoTxOut" ::: AlonzoTxOutTypes era]
Addr
addr
Value era
val
StrictMaybe (SafeHash EraIndependentData)
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
-> Value era
-> StrictMaybe (SafeHash EraIndependentData)
-> AlonzoTxOut era
AlonzoTxOut
instance (EraTxOut era, HasSpec (Value era)) => HasSpec (AlonzoTxOut era)
type BabbageTxOutTypes era =
'[ Addr
, Value era
, Datum era
, StrictMaybe (Script era)
]
instance (Typeable (Script era), 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
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
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
-> Value era
-> Datum era
-> StrictMaybe (Script era)
-> BabbageTxOut era
BabbageTxOut
instance
( HasSpec (Value era)
, Era era
, HasSpec (Data era)
, Val (Value era)
, HasSpec (Script era)
, IsNormalType (Script era)
) =>
HasSpec (BabbageTxOut era)
txOutVal_ ::
( HasSpec (Value era)
, Era era
, HasSpec (Data era)
, Val (Value era)
, HasSpec (Script era)
, HasSpec (BabbageTxOut era)
, IsNormalType (Script era)
) =>
Term (BabbageTxOut era) ->
Term (Value era)
txOutVal_ :: forall era.
(HasSpec (Value era), Era era, HasSpec (Data era), Val (Value era),
HasSpec (Script era), HasSpec (BabbageTxOut era),
IsNormalType (Script era)) =>
Term (BabbageTxOut era) -> Term (Value era)
txOutVal_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @1
instance
( Compactible a
, HasSimpleRep 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
( Compactible a
, Typeable (TypeSpec (SimpleRep a))
, Show (TypeSpec (SimpleRep a))
, HasSpec a
, HasSimpleRep a
, HasSpec (SimpleRep a)
) =>
HasSpec (CompactForm a)
instance HasSimpleRep MaryValue where
type TheSop MaryValue = '["MaryValue" ::: '[Coin]]
toSimpleRep :: MaryValue -> SimpleRep MaryValue
toSimpleRep (MaryValue Coin
c MultiAsset
_) = Coin
c
fromSimpleRep :: SimpleRep MaryValue -> MaryValue
fromSimpleRep SimpleRep MaryValue
c = Coin -> MultiAsset -> MaryValue
MaryValue SimpleRep MaryValue
c forall a. Monoid a => a
mempty
instance HasSpec MaryValue
maryValueCoin_ :: Term MaryValue -> Term Coin
maryValueCoin_ :: Term MaryValue -> Term Coin
maryValueCoin_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @0
instance HasSimpleRep PV1.Data
instance HasSpec PV1.Data where
type TypeSpec PV1.Data = ()
emptySpec :: TypeSpec Data
emptySpec = ()
combineSpec :: TypeSpec Data -> TypeSpec Data -> Specification Data
combineSpec TypeSpec Data
_ TypeSpec Data
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Data -> GenT m Data
genFromTypeSpec TypeSpec Data
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec Data -> Specification Integer
cardinalTypeSpec TypeSpec Data
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec Data -> Data -> [Data]
shrinkWithTypeSpec TypeSpec Data
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Data -> TypeSpec Data -> Bool
conformsTo Data
_ TypeSpec Data
_ = Bool
True
toPreds :: Term Data -> TypeSpec Data -> Pred
toPreds Term Data
_ TypeSpec Data
_ = forall p. IsPred p => p -> Pred
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), Memoized t) =>
RawType t -> t
mkMemoizedEra @era forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Data -> PlutusData era
PlutusData
instance Era era => HasSpec (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. Data era -> BinaryData era
dataToBinaryData
instance
(Era era, HasSpec (Data era)) =>
HasSpec (BinaryData era)
instance Typeable era => HasSimpleRep (Datum era)
instance (Era era, HasSpec (Data era)) => HasSpec (Datum era)
instance Typeable era => 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
( AlonzoEraScript era
, Script era ~ AlonzoScript era
, NativeScript era ~ Timelock era
) =>
HasSpec (AlonzoScript era)
instance
( AllegraEraScript era
, NativeScript era ~ Timelock era
) =>
HasSpec (Timelock era)
where
type TypeSpec (Timelock era) = ()
emptySpec :: TypeSpec (Timelock era)
emptySpec = ()
combineSpec :: TypeSpec (Timelock era)
-> TypeSpec (Timelock era) -> Specification (Timelock era)
combineSpec TypeSpec (Timelock era)
_ TypeSpec (Timelock era)
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (Timelock era) -> GenT m (Timelock era)
genFromTypeSpec TypeSpec (Timelock era)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec (Timelock era) -> Specification Integer
cardinalTypeSpec TypeSpec (Timelock era)
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec (Timelock era) -> Timelock era -> [Timelock era]
shrinkWithTypeSpec TypeSpec (Timelock era)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Timelock era -> TypeSpec (Timelock era) -> Bool
conformsTo Timelock era
_ TypeSpec (Timelock era)
_ = Bool
True
toPreds :: Term (Timelock era) -> TypeSpec (Timelock era) -> Pred
toPreds Term (Timelock era)
_ TypeSpec (Timelock era)
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSimpleRep CompactAddr where
type SimpleRep CompactAddr = SimpleRep Addr
toSimpleRep :: CompactAddr -> SimpleRep CompactAddr
toSimpleRep = forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => CompactAddr -> Addr
decompactAddr
fromSimpleRep :: SimpleRep CompactAddr -> CompactAddr
fromSimpleRep = Addr -> CompactAddr
compactAddr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep
instance HasSpec CompactAddr
instance HasSimpleRep Addr
instance HasSpec Addr
instance HasSimpleRep BootstrapAddress where
type
TheSop BootstrapAddress =
'[ "BootstrapAddress"
::: '[ AbstractHash Blake2b_224 Address'
, NetworkMagic
, AddrType
]
]
toSimpleRep :: BootstrapAddress -> SimpleRep BootstrapAddress
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)
AbstractHash Blake2b_224 Address'
root
NetworkMagic
magic
AddrType
typ
fromSimpleRep :: SimpleRep BootstrapAddress -> BootstrapAddress
fromSimpleRep SimpleRep BootstrapAddress
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @(TheSop BootstrapAddress) SimpleRep BootstrapAddress
rep forall a b. (a -> b) -> a -> b
$
\AbstractHash Blake2b_224 Address'
root NetworkMagic
magic AddrType
typ ->
Address -> BootstrapAddress
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 HasSpec BootstrapAddress
instance HasSimpleRep NetworkMagic
instance HasSpec NetworkMagic
instance HasSimpleRep AddrType
instance HasSpec AddrType
instance Typeable b => HasSpec (AbstractHash Blake2b_224 b) where
type TypeSpec (AbstractHash Blake2b_224 b) = ()
emptySpec :: TypeSpec (AbstractHash Blake2b_224 b)
emptySpec = ()
combineSpec :: TypeSpec (AbstractHash Blake2b_224 b)
-> TypeSpec (AbstractHash Blake2b_224 b)
-> Specification (AbstractHash Blake2b_224 b)
combineSpec TypeSpec (AbstractHash Blake2b_224 b)
_ TypeSpec (AbstractHash Blake2b_224 b)
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (AbstractHash Blake2b_224 b)
-> GenT m (AbstractHash Blake2b_224 b)
genFromTypeSpec TypeSpec (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 (AbstractHash Blake2b_224 b)
-> AbstractHash Blake2b_224 b -> [AbstractHash Blake2b_224 b]
shrinkWithTypeSpec TypeSpec (AbstractHash Blake2b_224 b)
_ AbstractHash Blake2b_224 b
_ = []
cardinalTypeSpec :: TypeSpec (AbstractHash Blake2b_224 b) -> Specification Integer
cardinalTypeSpec TypeSpec (AbstractHash Blake2b_224 b)
_ = forall a. Specification a
TrueSpec
conformsTo :: HasCallStack =>
AbstractHash Blake2b_224 b
-> TypeSpec (AbstractHash Blake2b_224 b) -> Bool
conformsTo AbstractHash Blake2b_224 b
_ TypeSpec (AbstractHash Blake2b_224 b)
_ = Bool
True
toPreds :: Term (AbstractHash Blake2b_224 b)
-> TypeSpec (AbstractHash Blake2b_224 b) -> Pred
toPreds Term (AbstractHash Blake2b_224 b)
_ TypeSpec (AbstractHash Blake2b_224 b)
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSimpleRep StakeReference
instance HasSpec StakeReference
instance HasSimpleRep SlotNo32
instance HasSpec SlotNo32
instance HasSimpleRep Ptr
instance HasSpec Ptr
instance HasSimpleRep CertIx where
type SimpleRep CertIx = Word16
toSimpleRep :: CertIx -> SimpleRep CertIx
toSimpleRep = CertIx -> Word16
unCertIx
fromSimpleRep :: SimpleRep CertIx -> CertIx
fromSimpleRep = Word16 -> CertIx
CertIx
instance HasSpec CertIx
instance Typeable r => HasSimpleRep (Credential r)
instance Typeable r => HasSpec (Credential r)
cKeyHashObj ::
Typeable r => Term (KeyHash r) -> Term (Credential r)
cKeyHashObj :: forall (r :: KeyRole).
Typeable r =>
Term (KeyHash r) -> Term (Credential r)
cKeyHashObj = forall (c :: Symbol) a r.
(SimpleRep a ~ SOP (TheSop a),
TypeSpec a ~ TypeSpec (SOP (TheSop a)),
TypeList (ConstrOf c (TheSop a)), HasSpec a, HasSimpleRep a,
r ~ FunTy (MapList Term (ConstrOf c (TheSop a))) (Term a),
ResultType r ~ Term a, SOPTerm c (TheSop a),
ConstrTerm (ConstrOf c (TheSop a))) =>
r
con @"KeyHashObj"
cScriptHashObj ::
Typeable r => Term ScriptHash -> Term (Credential r)
cScriptHashObj :: forall (r :: KeyRole).
Typeable r =>
Term ScriptHash -> Term (Credential r)
cScriptHashObj = forall (c :: Symbol) a r.
(SimpleRep a ~ SOP (TheSop a),
TypeSpec a ~ TypeSpec (SOP (TheSop a)),
TypeList (ConstrOf c (TheSop a)), HasSpec a, HasSimpleRep a,
r ~ FunTy (MapList Term (ConstrOf c (TheSop a))) (Term a),
ResultType r ~ Term a, SOPTerm c (TheSop a),
ConstrTerm (ConstrOf c (TheSop a))) =>
r
con @"ScriptHashObj"
instance HasSimpleRep ScriptHash
instance HasSpec ScriptHash
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 Typeable r => HasSpec (VRFVerKeyHash r) where
type TypeSpec (VRFVerKeyHash r) = ()
emptySpec :: TypeSpec (VRFVerKeyHash r)
emptySpec = ()
combineSpec :: TypeSpec (VRFVerKeyHash r)
-> TypeSpec (VRFVerKeyHash r) -> Specification (VRFVerKeyHash r)
combineSpec TypeSpec (VRFVerKeyHash r)
_ TypeSpec (VRFVerKeyHash r)
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (VRFVerKeyHash r) -> GenT m (VRFVerKeyHash r)
genFromTypeSpec TypeSpec (VRFVerKeyHash r)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a b. (a -> b) -> a -> b
$ forall (r :: KeyRoleVRF). Hash HASH KeyRoleVRF -> VRFVerKeyHash r
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 (VRFVerKeyHash r) -> Specification Integer
cardinalTypeSpec TypeSpec (VRFVerKeyHash r)
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec (VRFVerKeyHash r) -> VRFVerKeyHash r -> [VRFVerKeyHash r]
shrinkWithTypeSpec TypeSpec (VRFVerKeyHash r)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack =>
VRFVerKeyHash r -> TypeSpec (VRFVerKeyHash r) -> Bool
conformsTo VRFVerKeyHash r
_ TypeSpec (VRFVerKeyHash r)
_ = Bool
True
toPreds :: Term (VRFVerKeyHash r) -> TypeSpec (VRFVerKeyHash r) -> Pred
toPreds Term (VRFVerKeyHash r)
_ TypeSpec (VRFVerKeyHash r)
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance (HashAlgorithm a, Typeable b) => HasSpec (Hash a b) where
type TypeSpec (Hash a b) = ()
emptySpec :: TypeSpec (Hash a b)
emptySpec = ()
combineSpec :: TypeSpec (Hash a b)
-> TypeSpec (Hash a b) -> Specification (Hash a b)
combineSpec TypeSpec (Hash a b)
_ TypeSpec (Hash a b)
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (Hash a b) -> GenT m (Hash a b)
genFromTypeSpec TypeSpec (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 (Hash a b) -> Specification Integer
cardinalTypeSpec TypeSpec (Hash a b)
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec (Hash a b) -> Hash a b -> [Hash a b]
shrinkWithTypeSpec TypeSpec (Hash a b)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Hash a b -> TypeSpec (Hash a b) -> Bool
conformsTo Hash a b
_ TypeSpec (Hash a b)
_ = Bool
True
toPreds :: Term (Hash a b) -> TypeSpec (Hash a b) -> Pred
toPreds Term (Hash a b)
_ TypeSpec (Hash a b)
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSimpleRep (ConwayTxCert era)
instance Era era => HasSpec (ConwayTxCert era)
instance HasSimpleRep ConwayDelegCert
instance HasSpec ConwayDelegCert
instance HasSimpleRep PoolCert
instance HasSpec PoolCert
instance HasSimpleRep PoolParams
instance HasSpec PoolParams
instance HasSimpleRep PoolMetadata
instance HasSpec PoolMetadata
instance HasSpec StakePoolRelay where
type TypeSpec StakePoolRelay = ()
emptySpec :: TypeSpec StakePoolRelay
emptySpec = ()
combineSpec :: TypeSpec StakePoolRelay
-> TypeSpec StakePoolRelay -> Specification StakePoolRelay
combineSpec TypeSpec StakePoolRelay
_ TypeSpec StakePoolRelay
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec StakePoolRelay -> GenT m StakePoolRelay
genFromTypeSpec TypeSpec StakePoolRelay
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec StakePoolRelay -> Specification Integer
cardinalTypeSpec TypeSpec StakePoolRelay
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec StakePoolRelay -> StakePoolRelay -> [StakePoolRelay]
shrinkWithTypeSpec TypeSpec StakePoolRelay
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => StakePoolRelay -> TypeSpec StakePoolRelay -> Bool
conformsTo StakePoolRelay
_ TypeSpec StakePoolRelay
_ = Bool
True
toPreds :: Term StakePoolRelay -> TypeSpec StakePoolRelay -> Pred
toPreds Term StakePoolRelay
_ TypeSpec StakePoolRelay
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSimpleRep Port
instance HasSpec Port
instance HasSimpleRep ConwayGovCert
instance HasSpec ConwayGovCert
instance HasSimpleRep Anchor
instance HasSpec Anchor
instance HasSimpleRep Url
instance HasSpec Url where
type TypeSpec Url = ()
emptySpec :: TypeSpec Url
emptySpec = ()
combineSpec :: TypeSpec Url -> TypeSpec Url -> Specification Url
combineSpec TypeSpec Url
_ TypeSpec Url
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Url -> GenT m Url
genFromTypeSpec TypeSpec Url
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec Url -> Specification Integer
cardinalTypeSpec TypeSpec Url
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec Url -> Url -> [Url]
shrinkWithTypeSpec TypeSpec Url
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Url -> TypeSpec Url -> Bool
conformsTo Url
_ TypeSpec Url
_ = Bool
True
toPreds :: Term Url -> TypeSpec Url -> Pred
toPreds Term Url
_ TypeSpec Url
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSpec Text where
type TypeSpec Text = ()
emptySpec :: TypeSpec Text
emptySpec = ()
combineSpec :: TypeSpec Text -> TypeSpec Text -> Specification Text
combineSpec TypeSpec Text
_ TypeSpec Text
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Text -> GenT m Text
genFromTypeSpec TypeSpec Text
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec Text -> Specification Integer
cardinalTypeSpec TypeSpec Text
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec Text -> Text -> [Text]
shrinkWithTypeSpec TypeSpec Text
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Text -> TypeSpec Text -> Bool
conformsTo Text
_ TypeSpec Text
_ = Bool
True
toPreds :: Term Text -> TypeSpec Text -> Pred
toPreds Term Text
_ TypeSpec Text
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
newtype StringSpec = StringSpec {StringSpec -> Specification Int
strSpecLen :: Specification Int}
deriving instance Show StringSpec
instance Semigroup StringSpec where
StringSpec Specification Int
len <> :: StringSpec -> StringSpec -> StringSpec
<> StringSpec Specification Int
len' = Specification Int -> StringSpec
StringSpec (Specification Int
len forall a. Semigroup a => a -> a -> a
<> Specification Int
len')
instance Monoid StringSpec where
mempty :: StringSpec
mempty = Specification Int -> StringSpec
StringSpec forall a. Specification a
TrueSpec
instance HasSpec ByteString where
type TypeSpec ByteString = StringSpec
emptySpec :: TypeSpec ByteString
emptySpec = forall a. Monoid a => a
mempty
combineSpec :: TypeSpec ByteString
-> TypeSpec ByteString -> Specification ByteString
combineSpec TypeSpec ByteString
s TypeSpec ByteString
s' = forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec forall a b. (a -> b) -> a -> b
$ TypeSpec ByteString
s forall a. Semigroup a => a -> a -> a
<> TypeSpec ByteString
s'
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec ByteString -> GenT m ByteString
genFromTypeSpec (StringSpec Specification Int
ls) = do
Int
len <- forall a (m :: * -> *).
(HasCallStack, HasSpec a, MonadGenError m) =>
Specification a -> GenT m a
genFromSpecT Specification 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 ByteString -> ByteString -> [ByteString]
shrinkWithTypeSpec TypeSpec ByteString
_ = forall a. Arbitrary a => a -> [a]
shrink
cardinalTypeSpec :: TypeSpec ByteString -> Specification Integer
cardinalTypeSpec TypeSpec ByteString
_ = forall a. Specification a
TrueSpec
conformsTo :: HasCallStack => ByteString -> TypeSpec ByteString -> Bool
conformsTo ByteString
bs (StringSpec Specification Int
ls) = ByteString -> Int
BS.length ByteString
bs forall a. HasSpec a => a -> Specification a -> Bool
`conformsToSpec` Specification Int
ls
toPreds :: Term ByteString -> TypeSpec ByteString -> Pred
toPreds Term ByteString
str (StringSpec Specification Int
len) = forall a. HasSpec a => Term a -> Specification a -> Pred
satisfies (forall s. (StringLike s, HasSpec s) => Term s -> Term Int
strLen_ Term ByteString
str) Specification Int
len
instance HasSpec ShortByteString where
type TypeSpec ShortByteString = StringSpec
emptySpec :: TypeSpec ShortByteString
emptySpec = forall a. Monoid a => a
mempty
combineSpec :: TypeSpec ShortByteString
-> TypeSpec ShortByteString -> Specification ShortByteString
combineSpec TypeSpec ShortByteString
s TypeSpec ShortByteString
s' = forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec forall a b. (a -> b) -> a -> b
$ TypeSpec ShortByteString
s forall a. Semigroup a => a -> a -> a
<> TypeSpec ShortByteString
s'
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec ShortByteString -> GenT m ShortByteString
genFromTypeSpec (StringSpec Specification Int
ls) = do
Int
len <- forall a (m :: * -> *).
(HasCallStack, HasSpec a, MonadGenError m) =>
Specification a -> GenT m a
genFromSpecT Specification 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 ShortByteString -> ShortByteString -> [ShortByteString]
shrinkWithTypeSpec TypeSpec ShortByteString
_ = forall a. Arbitrary a => a -> [a]
shrink
cardinalTypeSpec :: TypeSpec ShortByteString -> Specification Integer
cardinalTypeSpec TypeSpec ShortByteString
_ = forall a. Specification a
TrueSpec
conformsTo :: HasCallStack => ShortByteString -> TypeSpec ShortByteString -> Bool
conformsTo ShortByteString
bs (StringSpec Specification Int
ls) = ShortByteString -> Int
SBS.length ShortByteString
bs forall a. HasSpec a => a -> Specification a -> Bool
`conformsToSpec` Specification Int
ls
toPreds :: Term ShortByteString -> TypeSpec ShortByteString -> Pred
toPreds Term ShortByteString
str (StringSpec Specification Int
len) = forall a. HasSpec a => Term a -> Specification a -> Pred
satisfies (forall s. (StringLike s, HasSpec s) => Term s -> Term Int
strLen_ Term ShortByteString
str) Specification Int
len
instance StringLike ByteString where
lengthSpec :: Specification Int -> TypeSpec ByteString
lengthSpec = Specification Int -> StringSpec
StringSpec
getLengthSpec :: TypeSpec ByteString -> Specification Int
getLengthSpec (StringSpec Specification Int
len) = Specification Int
len
getLength :: ByteString -> Int
getLength = ByteString -> Int
BS.length
instance StringLike ShortByteString where
lengthSpec :: Specification Int -> TypeSpec ShortByteString
lengthSpec = Specification Int -> StringSpec
StringSpec
getLengthSpec :: TypeSpec ShortByteString -> Specification Int
getLengthSpec (StringSpec Specification Int
len) = Specification Int
len
getLength :: ShortByteString -> Int
getLength = ShortByteString -> Int
SBS.length
data StringW (sym :: Symbol) (as :: [Type]) (b :: Type) where
StrLenW :: StringLike s => StringW "strLen_" '[s] Int
deriving instance Show (StringW s as b)
deriving instance Eq (StringW s as b)
strLen_ ::
(StringLike s, HasSpec s) =>
Term s ->
Term Int
strLen_ :: forall s. (StringLike s, HasSpec s) => Term s -> Term Int
strLen_ = forall (sym :: Symbol) (t :: Symbol -> [*] -> * -> *) (ds :: [*])
r.
AppRequires sym t ds r =>
t sym ds r -> FunTy (MapList Term ds) (Term r)
appTerm forall a. StringLike a => StringW "strLen_" '[a] Int
StrLenW
instance Syntax StringW
instance Semantics StringW where
semantics :: forall (s :: Symbol) (d :: [*]) r. StringW s d r -> FunTy d r
semantics StringW s d r
StrLenW = forall s. StringLike s => s -> Int
getLength
instance (Typeable s, StringLike s) => Logic "strLen_" StringW '[s] Int where
propagate :: forall hole.
Context "strLen_" StringW '[s] Int hole
-> Specification Int -> Specification hole
propagate Context "strLen_" StringW '[s] Int hole
ctxt (ExplainSpec [] Specification Int
s) = forall (s :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
rng hole.
Logic s t dom rng =>
Context s t dom rng hole -> Specification rng -> Specification hole
propagate Context "strLen_" StringW '[s] Int hole
ctxt Specification Int
s
propagate Context "strLen_" StringW '[s] Int hole
ctxt (ExplainSpec [[Char]]
es Specification Int
s) = forall a. [[Char]] -> Specification a -> Specification a
ExplainSpec [[Char]]
es forall a b. (a -> b) -> a -> b
$ forall (s :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
rng hole.
Logic s t dom rng =>
Context s t dom rng hole -> Specification rng -> Specification hole
propagate Context "strLen_" StringW '[s] Int hole
ctxt Specification Int
s
propagate Context "strLen_" StringW '[s] Int hole
_ Specification Int
TrueSpec = forall a. Specification a
TrueSpec
propagate Context "strLen_" StringW '[s] Int hole
_ (ErrorSpec NonEmpty [Char]
msgs) = forall a. NonEmpty [Char] -> Specification a
ErrorSpec NonEmpty [Char]
msgs
propagate (Context StringW "strLen_" '[s] Int
StrLenW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) (SuspendedSpec Var Int
v Pred
ps) =
forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained forall a b. (a -> b) -> a -> b
$ \Term hole
v' -> forall a. Term a -> Binder a -> Pred
Let (forall (sym :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
a.
AppRequires sym t dom a =>
t sym dom a -> List Term dom -> Term a
App forall a. StringLike a => StringW "strLen_" '[a] Int
StrLenW (Term hole
v' forall {k} (f :: k -> *) (a :: k) (as1 :: [k]).
f a -> List f as1 -> List f (a : as1)
:> forall {k} (f :: k -> *). List f '[]
Nil)) (Var Int
v forall a. HasSpec a => Var a -> Pred -> Binder a
:-> Pred
ps)
propagate (Context StringW "strLen_" '[s] Int
StrLenW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) Specification Int
spec = forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec forall a b. (a -> b) -> a -> b
$ forall s. StringLike s => Specification Int -> TypeSpec s
lengthSpec @s Specification Int
spec
propagate Context "strLen_" StringW '[s] Int hole
ctx Specification Int
_ =
forall a. NonEmpty [Char] -> Specification a
ErrorSpec forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char]
"Logic instance for StrLenW with wrong number of arguments. " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Context "strLen_" StringW '[s] Int hole
ctx)
mapTypeSpec :: forall a b.
('[s] ~ '[a], Int ~ b, HasSpec a, HasSpec b) =>
StringW "strLen_" '[a] b -> TypeSpec a -> Specification b
mapTypeSpec StringW "strLen_" '[a] b
StrLenW TypeSpec a
ss = forall s. StringLike s => TypeSpec s -> Specification Int
getLengthSpec @s TypeSpec a
ss
class StringLike s where
lengthSpec :: Specification Int -> TypeSpec s
getLengthSpec :: TypeSpec s -> Specification Int
getLength :: s -> Int
instance HasSimpleRep Delegatee
instance HasSpec Delegatee
instance HasSimpleRep DRep
instance HasSpec DRep
instance HasSimpleRep Withdrawals
instance HasSpec Withdrawals
instance HasSimpleRep RewardAccount
instance HasSpec RewardAccount
instance HasSimpleRep Network
instance HasSpec Network
instance HasSimpleRep MultiAsset
instance HasSpec MultiAsset where
emptySpec :: TypeSpec MultiAsset
emptySpec =
forall k v. Ord k => MapSpec k v
defaultMapSpec
{ mapSpecElem :: Specification (PolicyID, Map AssetName Integer)
mapSpecElem = forall a p.
(Cases (SimpleRep a) ~ '[SimpleRep a],
TypeSpec a ~ TypeSpec (SimpleRep a), HasSpec (SimpleRep a),
HasSimpleRep a, All HasSpec (Args (SimpleRep a)),
IsProd (SimpleRep a), HasSpec a, IsPred p) =>
FunTy (MapList Term (Args (SimpleRep a))) p -> Specification a
constrained' forall a b. (a -> b) -> a -> b
$ \Term PolicyID
_ Term (Map AssetName Integer)
innerMap ->
forall t a p.
(Forallable t a, HasSpec t, HasSpec a, IsPred p) =>
Term t -> (Term a -> p) -> Pred
forAll Term (Map AssetName Integer)
innerMap forall a b. (a -> b) -> a -> b
$ \Term (AssetName, Integer)
kv' ->
forall a. HasSpec a => a -> Term a
lit Integer
0 forall a. OrdLike a => Term a -> Term a -> Term Bool
<=. forall x y. (HasSpec x, HasSpec y) => Term (x, y) -> Term y
snd_ Term (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 HasSpec AssetName
instance HasSimpleRep PolicyID
instance HasSpec PolicyID
instance HasSimpleRep TxAuxDataHash
instance HasSpec TxAuxDataHash
instance Typeable era => HasSimpleRep (VotingProcedures era)
instance Typeable era => HasSpec (VotingProcedures era)
instance HasSimpleRep (VotingProcedure era)
instance Typeable era => HasSpec (VotingProcedure era)
instance HasSimpleRep Vote
instance HasSpec Vote
instance HasSimpleRep GovActionId
instance HasSpec GovActionId where
shrinkWithTypeSpec :: TypeSpec GovActionId -> GovActionId -> [GovActionId]
shrinkWithTypeSpec TypeSpec GovActionId
_ GovActionId
_ = []
instance HasSimpleRep GovActionIx
instance HasSpec GovActionIx
instance HasSimpleRep (GovPurposeId p era)
instance (Typeable p, Era era) => HasSpec (GovPurposeId p era)
instance Typeable era => HasSimpleRep (GovAction era)
instance EraSpecPParams era => HasSpec (GovAction era)
instance HasSimpleRep (Constitution era)
instance EraPParams era => HasSpec (Constitution era)
instance HasSimpleRep (ConwayPParams StrictMaybe c)
instance Typeable c => HasSpec (ConwayPParams StrictMaybe c)
instance HasSimpleRep (ConwayPParams Identity era)
instance Era era => HasSpec (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 HasSpec CoinPerByte
instance HasSpec Char where
type TypeSpec Char = ()
emptySpec :: TypeSpec Char
emptySpec = ()
combineSpec :: TypeSpec Char -> TypeSpec Char -> Specification Char
combineSpec TypeSpec Char
_ TypeSpec Char
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Char -> GenT m Char
genFromTypeSpec TypeSpec Char
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec Char -> Specification Integer
cardinalTypeSpec TypeSpec Char
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec Char -> Char -> [Char]
shrinkWithTypeSpec TypeSpec Char
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => Char -> TypeSpec Char -> Bool
conformsTo Char
_ TypeSpec Char
_ = Bool
True
toPreds :: Term Char -> TypeSpec Char -> Pred
toPreds Term Char
_ TypeSpec Char
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSpec CostModel where
type TypeSpec CostModel = ()
emptySpec :: TypeSpec CostModel
emptySpec = ()
combineSpec :: TypeSpec CostModel -> TypeSpec CostModel -> Specification CostModel
combineSpec TypeSpec CostModel
_ TypeSpec CostModel
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec CostModel -> GenT m CostModel
genFromTypeSpec TypeSpec CostModel
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec CostModel -> Specification Integer
cardinalTypeSpec TypeSpec CostModel
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec CostModel -> CostModel -> [CostModel]
shrinkWithTypeSpec TypeSpec CostModel
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => CostModel -> TypeSpec CostModel -> Bool
conformsTo CostModel
_ TypeSpec CostModel
_ = Bool
True
toPreds :: Term CostModel -> TypeSpec CostModel -> Pred
toPreds Term CostModel
_ TypeSpec CostModel
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSimpleRep Language
instance HasSpec Language
instance HasSimpleRep (NoUpdate a)
instance Typeable a => HasSpec (NoUpdate a)
instance Typeable a => 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 (IsNormalType a, Typeable tag, HasSpec a) => HasSpec (THKD tag StrictMaybe a)
instance Typeable a => 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 (IsNormalType a, Typeable tag, HasSpec a) => HasSpec (THKD tag Identity a)
instance HasSimpleRep GovActionPurpose
instance HasSpec GovActionPurpose
instance HasSimpleRep Voter
instance HasSpec Voter
instance (Typeable a, 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 (Ord a, HasSpec a) => HasSpec (SOS.OSet a)
instance (Typeable a, Ord a) => Forallable (SOS.OSet a) a
instance Typeable era => HasSimpleRep (ProposalProcedure era)
instance EraSpecPParams era => HasSpec (ProposalProcedure era)
pProcDeposit_ ::
Term (ProposalProcedure ConwayEra) ->
Term Coin
pProcDeposit_ :: Term (ProposalProcedure ConwayEra) -> Term Coin
pProcDeposit_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @0
pProcGovAction_ ::
Term (ProposalProcedure ConwayEra) ->
Term (GovAction ConwayEra)
pProcGovAction_ :: Term (ProposalProcedure ConwayEra) -> Term (GovAction ConwayEra)
pProcGovAction_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @2
instance HasSimpleRep ValidityInterval
instance HasSpec ValidityInterval
instance HasSimpleRep DRepState
instance HasSpec DRepState
instance HasSimpleRep CommitteeAuthorization
instance HasSpec CommitteeAuthorization
instance HasSimpleRep (CommitteeState era)
instance Era era => HasSpec (CommitteeState era)
instance Typeable era => HasSimpleRep (VState era)
instance Era era => HasSpec (VState era)
instance HasSimpleRep (PState era)
instance Era era => HasSpec (PState era)
instance HasSimpleRep (DState era)
instance Era era => HasSpec (DState era)
instance HasSimpleRep FutureGenDeleg
instance HasSpec FutureGenDeleg
instance HasSimpleRep GenDelegPair
instance HasSpec GenDelegPair
instance HasSimpleRep GenDelegs
instance HasSpec GenDelegs
instance HasSimpleRep InstantaneousRewards
instance HasSpec InstantaneousRewards
type UMapTypes =
'[ Map (Credential 'Staking) RDPair
, Map Ptr (Credential 'Staking)
, Map (Credential 'Staking) (KeyHash 'StakePool)
, Map (Credential 'Staking) DRep
]
instance HasSimpleRep UMap where
type TheSop UMap = '["UMap" ::: UMapTypes]
toSimpleRep :: UMap -> SimpleRep UMap
toSimpleRep UMap
um = forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"UMap" @'["UMap" ::: UMapTypes] (UMap -> Map (Credential 'Staking) RDPair
rdPairMap UMap
um) (UMap -> Map Ptr (Credential 'Staking)
ptrMap UMap
um) (UMap -> Map (Credential 'Staking) (KeyHash 'StakePool)
sPoolMap UMap
um) (UMap -> Map (Credential 'Staking) DRep
dRepMap UMap
um)
fromSimpleRep :: SimpleRep UMap -> UMap
fromSimpleRep SimpleRep UMap
rep = forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["UMap" ::: UMapTypes] SimpleRep UMap
rep Map (Credential 'Staking) RDPair
-> Map Ptr (Credential 'Staking)
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (Credential 'Staking) DRep
-> UMap
unify
instance HasSpec UMap
instance HasSimpleRep RDPair where
type TheSop RDPair = '["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 HasSpec RDPair
instance Typeable era => HasSimpleRep (ShelleyCertState era)
instance EraCertState era => HasSpec (ShelleyCertState era)
instance Typeable era => HasSimpleRep (ConwayCertState era)
instance ConwayEraCertState era => HasSpec (ConwayCertState era)
instance Typeable era => HasSimpleRep (GovRelation StrictMaybe era)
instance Era era => HasSpec (GovRelation StrictMaybe era)
instance (Typeable (CertState era), Era era) => HasSimpleRep (GovEnv era)
instance
(EraSpecPParams era, EraTxOut era, EraCertState era, EraGov era, HasSpec (CertState era)) =>
HasSpec (GovEnv era)
instance Typeable era => HasSimpleRep (GovActionState era)
instance (Era era, EraSpecPParams era) => HasSpec (GovActionState era)
gasId_ ::
Term (GovActionState ConwayEra) ->
Term (GovActionId)
gasId_ :: Term (GovActionState ConwayEra) -> Term GovActionId
gasId_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @0
gasCommitteeVotes_ ::
Term (GovActionState ConwayEra) ->
Term (Map (Credential 'HotCommitteeRole) Vote)
gasCommitteeVotes_ :: Term (GovActionState ConwayEra)
-> Term (Map (Credential 'HotCommitteeRole) Vote)
gasCommitteeVotes_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @1
gasDRepVotes_ ::
Term (GovActionState ConwayEra) ->
Term (Map (Credential 'DRepRole) Vote)
gasDRepVotes_ :: Term (GovActionState ConwayEra)
-> Term (Map (Credential 'DRepRole) Vote)
gasDRepVotes_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @2
gasProposalProcedure_ ::
Term (GovActionState ConwayEra) ->
Term (ProposalProcedure ConwayEra)
gasProposalProcedure_ :: Term (GovActionState ConwayEra)
-> Term (ProposalProcedure ConwayEra)
gasProposalProcedure_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @4
type GAS era = GovActionState era
type ProposalTree era = (StrictMaybe GovActionId, [Tree (GAS era)])
type ProposalsType era =
'[ ProposalTree era
, ProposalTree era
, ProposalTree era
, ProposalTree era
, [GAS era]
]
instance EraPParams era => HasSimpleRep (Proposals era) where
type TheSop (Proposals era) = '["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
-> (StrictMaybe GovActionId, [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
-> (StrictMaybe GovActionId, [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
-> (StrictMaybe GovActionId, [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
-> (StrictMaybe GovActionId, [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 (GAS era)
idMap Set GovActionId
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 (GAS era)
idMap = forall era. Proposals era -> Map GovActionId (GovActionState era)
proposalsActionsMap Proposals era
props
treeKeys :: Set GovActionId
treeKeys =
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap
TreeMaybe GovActionId -> Set GovActionId
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 -> ProposalTree era
buildProposalTree :: TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
buildProposalTree (TreeMaybe (Node StrictMaybe GovActionId
mId [Tree (StrictMaybe GovActionId)]
cs)) = (StrictMaybe GovActionId
mId, forall a b. (a -> b) -> [a] -> [b]
map Tree (StrictMaybe GovActionId) -> Tree (GAS era)
buildTree [Tree (StrictMaybe GovActionId)]
cs)
buildTree :: Tree (StrictMaybe GovActionId) -> Tree (GAS era)
buildTree :: Tree (StrictMaybe GovActionId) -> Tree (GAS era)
buildTree (Node (SJust GovActionId
gid) [Tree (StrictMaybe GovActionId)]
cs) | Just GAS era
gas <- forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup GovActionId
gid Map GovActionId (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) -> Tree (GAS era)
buildTree [Tree (StrictMaybe GovActionId)]
cs)
buildTree Tree (StrictMaybe GovActionId)
_ =
forall a. HasCallStack => [Char] -> a
error [Char]
"toSimpleRep @Proposals: toGovRelationTree returned trees with Nothing nodes below the root"
keys :: TreeMaybe GovActionId -> Set GovActionId
keys :: TreeMaybe GovActionId -> Set GovActionId
keys (TreeMaybe Tree (StrictMaybe GovActionId)
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)
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
rPPUp, [Tree (GAS era)]
ppupTree) (StrictMaybe GovActionId
rHF, [Tree (GAS era)]
hfTree) (StrictMaybe GovActionId
rCom, [Tree (GAS era)]
comTree) (StrictMaybe GovActionId
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
rPPUp) (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rHF) (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rCom) (coerce :: forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rCon)
oMap :: OMap GovActionId (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 (GovActionState era) -> Proposals era
unsafeMkProposals GovRelation StrictMaybe era
root OMap GovActionId (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
, Arbitrary (Proposals era)
, HasSpec (Tree (GAS era))
) =>
HasSpec (Proposals era)
where
shrinkWithTypeSpec :: TypeSpec (Proposals era) -> Proposals era -> [Proposals era]
shrinkWithTypeSpec TypeSpec (Proposals era)
_ Proposals era
props = forall a. Arbitrary a => a -> [a]
shrink Proposals era
props
psPParamUpdate_ ::
(EraSpecPParams era, Arbitrary (Proposals era)) =>
Term (Proposals era) -> Term (ProposalTree era)
psPParamUpdate_ :: forall era.
(EraSpecPParams era, Arbitrary (Proposals era)) =>
Term (Proposals era) -> Term (ProposalTree era)
psPParamUpdate_ = forall (n :: Natural) a (c :: Symbol) (as :: [*]).
(SimpleRep a ~ ProdOver as, TheSop a ~ '[c ::: as],
TypeSpec a ~ TypeSpec (ProdOver as), Select n as, HasSpec a,
HasSpec (ProdOver as), HasSimpleRep a) =>
Term a -> Term (At n as)
sel @0
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 t (w :: Wrapped) s. Typeable t => 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 a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
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 (SimpleRep (Proposals era))
, HasSpec (Proposals era)
, HasSimpleRep (Proposals era)
, era ~ ConwayEra
, EraSpecPParams era
) =>
HasGenHint (Proposals era)
where
type Hint (Proposals era) = ProposalsSplit
giveHint :: Hint (Proposals era) -> Specification (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 p.
(Cases (SimpleRep a) ~ '[SimpleRep a],
TypeSpec a ~ TypeSpec (SimpleRep a), HasSpec (SimpleRep a),
HasSimpleRep a, All HasSpec (Args (SimpleRep a)),
IsProd (SimpleRep a), HasSpec a, IsPred p) =>
FunTy (MapList Term (Args (SimpleRep a))) p -> Specification a
constrained' forall a b. (a -> b) -> a -> b
$ \Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
ppuTree Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
hfTree Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
comTree Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
conTree Term [GovActionState ConwayEra]
others ->
[ forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
HasGenHint t, HasGenHint a, Num a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
psPPChange Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
ppuTree
, forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
HasGenHint t, HasGenHint a, Num a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
psHFInitiation Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
hfTree
, forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
HasGenHint t, HasGenHint a, Num a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
psUpdateCommittee Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
comTree
, forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
HasGenHint t, HasGenHint a, Num a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
psNewConstitution Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
conTree
, [forall t. HasGenHint t => Hint t -> Term t -> Pred
genHint Integer
psOthers Term [GovActionState ConwayEra]
others]
]
where
limitForest :: Hint t -> Term (x, t) -> [Pred]
limitForest Hint t
limit Term (x, t)
forest =
[ forall t. HasGenHint t => Hint t -> Term t -> Pred
genHint Hint t
limit (forall x y. (HasSpec x, HasSpec y) => Term (x, y) -> Term y
snd_ Term (x, t)
forest)
, forall t a p.
(Forallable t a, HasSpec t, HasSpec a, IsPred p) =>
Term t -> (Term a -> p) -> Pred
forAll (forall x y. (HasSpec x, HasSpec y) => Term (x, y) -> Term y
snd_ Term (x, t)
forest) forall a b. (a -> b) -> a -> b
$ forall t. HasGenHint t => Hint t -> Term t -> Pred
genHint (forall a. a -> Maybe a
Just a
2, Hint t
limit)
]
instance HasSimpleRep (EnactSignal ConwayEra)
instance HasSpec (EnactSignal ConwayEra)
instance Typeable era => HasSimpleRep (EnactState era)
instance (EraGov era, EraTxOut era, EraSpecPParams era) => HasSpec (EnactState era)
instance HasSimpleRep (Committee era)
instance Era era => HasSpec (Committee era)
instance
( HasSpec (InstantStake era)
, Typeable era
) =>
HasSimpleRep (RatifyEnv era)
instance
( HasSpec (InstantStake era)
, Era era
) =>
HasSpec (RatifyEnv era)
instance HasSimpleRep (RatifyState ConwayEra)
instance HasSpec (RatifyState ConwayEra)
instance HasSimpleRep (RatifySignal ConwayEra)
instance HasSpec (RatifySignal ConwayEra)
instance HasSimpleRep PoolDistr
instance HasSpec PoolDistr
instance HasSimpleRep IndividualPoolStake
instance HasSpec IndividualPoolStake
instance HasSimpleRep (ConwayGovCertEnv ConwayEra)
instance HasSpec (ConwayGovCertEnv ConwayEra)
instance Typeable era => HasSimpleRep (PoolEnv era)
instance (EraGov era, EraTxOut era, EraSpecPParams era) => HasSpec (PoolEnv era)
instance Era era => HasSimpleRep (CertEnv era)
instance (EraGov era, EraTxOut era, EraSpecPParams era) => HasSpec (CertEnv era)
instance HasSimpleRep NonMyopic
instance HasSpec NonMyopic
instance HasSimpleRep Likelihood
instance HasSpec Likelihood
instance HasSimpleRep LogWeight
instance HasSpec LogWeight
instance HasSimpleRep ChainAccountState
instance HasSpec ChainAccountState
instance HasSimpleRep SnapShot
instance HasSpec SnapShot
instance HasSimpleRep Stake
instance HasSpec Stake
instance (Typeable k, Typeable v, VMap.Vector vk k, VMap.Vector vv v) => HasSimpleRep (VMap vk vv k v) where
type SimpleRep (VMap vk vv k v) = Map k v
toSimpleRep :: VMap vk vv k v -> SimpleRep (VMap vk vv k v)
toSimpleRep = forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap
fromSimpleRep :: SimpleRep (VMap vk vv k v) -> VMap vk vv k v
fromSimpleRep = forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap
instance
( VMap.Vector vk k
, VMap.Vector vv v
, Typeable vk
, Typeable vv
, Ord k
, Eq (vv v)
, Eq (vk k)
, HasSpec k
, HasSpec v
, IsNormalType v
, IsNormalType k
) =>
HasSpec (VMap vk vv k v)
instance HasSimpleRep SnapShots
instance HasSpec SnapShots
instance (Typeable (CertState era), EraTxOut era) => HasSimpleRep (LedgerState era)
instance
( EraTxOut era
, HasSpec (TxOut era)
, IsNormalType (TxOut era)
, HasSpec (GovState era)
, EraStake era
, EraCertState era
, IsNormalType (CertState era)
, HasSpec (InstantStake era)
, HasSpec (CertState era)
) =>
HasSpec (LedgerState era)
instance (Typeable (InstantStake era), Typeable (GovState era), Typeable era) => HasSimpleRep (UTxOState era)
instance
( EraTxOut era
, HasSpec (TxOut era)
, IsNormalType (TxOut era)
, HasSpec (GovState era)
, HasSpec (InstantStake era)
) =>
HasSpec (UTxOState era)
instance HasSimpleRep (ShelleyInstantStake era)
instance Typeable era => HasSpec (ShelleyInstantStake era)
instance HasSimpleRep (ConwayInstantStake era)
instance Typeable era => HasSpec (ConwayInstantStake era)
instance Typeable (TxOut era) => HasSimpleRep (UTxO era)
instance
(Era era, HasSpec (TxOut era), IsNormalType (TxOut era)) =>
HasSpec (UTxO era)
instance HasSimpleRep (ConwayGovState ConwayEra)
instance HasSpec (ConwayGovState ConwayEra)
instance HasSimpleRep (DRepPulsingState ConwayEra)
instance HasSpec (DRepPulsingState ConwayEra)
instance HasSimpleRep (PulsingSnapshot ConwayEra)
instance HasSpec (PulsingSnapshot ConwayEra)
type DRepPulserTypes =
'[ Int
, UMap
, Int
, InstantStake ConwayEra
, PoolDistr
, Map DRep (CompactForm Coin)
, Map (Credential 'DRepRole) DRepState
, EpochNo
, CommitteeState ConwayEra
, EnactState ConwayEra
, StrictSeq (GovActionState ConwayEra)
, Map (Credential 'Staking) (CompactForm Coin)
, Map (KeyHash 'StakePool) PoolParams
]
instance
HasSimpleRep
(DRepPulser ConwayEra Identity (RatifyState ConwayEra))
where
type
TheSop (DRepPulser ConwayEra Identity (RatifyState ConwayEra)) =
'["DRepPulser" ::: DRepPulserTypes]
toSimpleRep :: DRepPulser ConwayEra Identity (RatifyState ConwayEra)
-> SimpleRep
(DRepPulser ConwayEra Identity (RatifyState ConwayEra))
toSimpleRep DRepPulser {Int
Map DRep (CompactForm Coin)
Map (KeyHash 'StakePool) PoolParams
Map (Credential 'Staking) (CompactForm Coin)
Map (Credential 'DRepRole) DRepState
PoolDistr
CommitteeState ConwayEra
InstantStake ConwayEra
EnactState ConwayEra
StrictSeq (GovActionState ConwayEra)
UMap
Globals
EpochNo
dpPulseSize :: forall era ans (m :: * -> *). DRepPulser era m ans -> Int
dpUMap :: forall era ans (m :: * -> *). DRepPulser era m ans -> UMap
dpIndex :: forall era ans (m :: * -> *). DRepPulser era m ans -> Int
dpInstantStake :: forall era ans (m :: * -> *).
DRepPulser era m ans -> InstantStake era
dpStakePoolDistr :: forall era ans (m :: * -> *). DRepPulser era m ans -> PoolDistr
dpDRepDistr :: forall era ans (m :: * -> *).
DRepPulser era m ans -> Map DRep (CompactForm Coin)
dpDRepState :: forall era ans (m :: * -> *).
DRepPulser era m ans -> Map (Credential 'DRepRole) DRepState
dpCurrentEpoch :: forall era ans (m :: * -> *). DRepPulser era m ans -> EpochNo
dpCommitteeState :: forall era ans (m :: * -> *).
DRepPulser era m ans -> CommitteeState era
dpEnactState :: forall era ans (m :: * -> *).
DRepPulser era m ans -> EnactState era
dpProposals :: forall era ans (m :: * -> *).
DRepPulser era m ans -> StrictSeq (GovActionState era)
dpProposalDeposits :: forall era ans (m :: * -> *).
DRepPulser era m ans
-> Map (Credential 'Staking) (CompactForm Coin)
dpGlobals :: forall era ans (m :: * -> *). DRepPulser era m ans -> Globals
dpPoolParams :: forall era ans (m :: * -> *).
DRepPulser era m ans -> Map (KeyHash 'StakePool) PoolParams
dpPoolParams :: Map (KeyHash 'StakePool) PoolParams
dpGlobals :: Globals
dpProposalDeposits :: Map (Credential 'Staking) (CompactForm Coin)
dpProposals :: StrictSeq (GovActionState ConwayEra)
dpEnactState :: EnactState ConwayEra
dpCommitteeState :: CommitteeState ConwayEra
dpCurrentEpoch :: EpochNo
dpDRepState :: Map (Credential 'DRepRole) DRepState
dpDRepDistr :: Map DRep (CompactForm Coin)
dpStakePoolDistr :: PoolDistr
dpInstantStake :: InstantStake ConwayEra
dpIndex :: Int
dpUMap :: UMap
dpPulseSize :: Int
..} =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"DRepPulser" @'["DRepPulser" ::: DRepPulserTypes]
Int
dpPulseSize
UMap
dpUMap
Int
dpIndex
InstantStake ConwayEra
dpInstantStake
PoolDistr
dpStakePoolDistr
Map DRep (CompactForm Coin)
dpDRepDistr
Map (Credential 'DRepRole) DRepState
dpDRepState
EpochNo
dpCurrentEpoch
CommitteeState ConwayEra
dpCommitteeState
EnactState ConwayEra
dpEnactState
StrictSeq (GovActionState ConwayEra)
dpProposals
Map (Credential 'Staking) (CompactForm Coin)
dpProposalDeposits
Map (KeyHash 'StakePool) PoolParams
dpPoolParams
fromSimpleRep :: SimpleRep (DRepPulser ConwayEra Identity (RatifyState ConwayEra))
-> DRepPulser ConwayEra Identity (RatifyState ConwayEra)
fromSimpleRep SimpleRep (DRepPulser ConwayEra Identity (RatifyState ConwayEra))
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["DRepPulser" ::: DRepPulserTypes]
SimpleRep (DRepPulser ConwayEra Identity (RatifyState ConwayEra))
rep
forall a b. (a -> b) -> a -> b
$ \Int
ps UMap
um Int
b ConwayInstantStake ConwayEra
sd PoolDistr
spd Map DRep (CompactForm Coin)
dd Map (Credential 'DRepRole) DRepState
ds EpochNo
ce CommitteeState ConwayEra
cs EnactState ConwayEra
es StrictSeq (GovActionState ConwayEra)
p Map (Credential 'Staking) (CompactForm Coin)
pds Map (KeyHash 'StakePool) PoolParams
poolps ->
forall era ans (m :: * -> *).
(ans ~ RatifyState era, m ~ Identity, RunConwayRatify era) =>
Int
-> UMap
-> Int
-> InstantStake era
-> PoolDistr
-> Map DRep (CompactForm Coin)
-> Map (Credential 'DRepRole) DRepState
-> EpochNo
-> CommitteeState era
-> EnactState era
-> StrictSeq (GovActionState era)
-> Map (Credential 'Staking) (CompactForm Coin)
-> Globals
-> Map (KeyHash 'StakePool) PoolParams
-> DRepPulser era m ans
DRepPulser Int
ps UMap
um Int
b ConwayInstantStake ConwayEra
sd PoolDistr
spd Map DRep (CompactForm Coin)
dd Map (Credential 'DRepRole) DRepState
ds EpochNo
ce CommitteeState ConwayEra
cs EnactState ConwayEra
es StrictSeq (GovActionState ConwayEra)
p Map (Credential 'Staking) (CompactForm Coin)
pds Globals
testGlobals Map (KeyHash 'StakePool) PoolParams
poolps
instance HasSpec (DRepPulser ConwayEra Identity (RatifyState ConwayEra))
instance (Typeable (CertState era), Era era) => HasSimpleRep (UtxoEnv era)
instance
(EraGov era, EraTxOut era, EraSpecPParams era, EraCertState era, HasSpec (CertState era)) =>
HasSpec (UtxoEnv era)
instance
( Typeable (TxAuxData era)
, Typeable (TxBody era)
, Typeable (TxWits era)
, Era era
) =>
HasSimpleRep (AlonzoTx era)
instance
( EraSpecPParams era
, HasSpec (TxBody era)
, HasSpec (TxWits era)
, HasSpec (TxAuxData era)
, IsNormalType (TxAuxData era)
) =>
HasSpec (AlonzoTx era)
type ShelleyTxTypes era =
'[ TxBody era
, TxWits era
, Maybe (TxAuxData era)
]
instance
( EraTxOut era
, EraTx era
, EraSpecPParams era
, HasSpec (TxBody era)
, HasSpec (TxWits era)
, HasSpec (TxAuxData era)
, IsNormalType (TxAuxData era)
) =>
HasSpec (ShelleyTx era)
instance (EraTx era, EraTxOut era, EraSpecPParams era) => HasSimpleRep (ShelleyTx era) where
type TheSop (ShelleyTx era) = '["ShelleyTx" ::: ShelleyTxTypes era]
toSimpleRep :: ShelleyTx era -> SimpleRep (ShelleyTx era)
toSimpleRep (ShelleyTx TxBody era
body TxWits era
wits StrictMaybe (TxAuxData era)
auxdata) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"ShelleyTx" @'["ShelleyTx" ::: ShelleyTxTypes era]
TxBody era
body
TxWits era
wits
(forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe StrictMaybe (TxAuxData era)
auxdata)
fromSimpleRep :: SimpleRep (ShelleyTx era) -> ShelleyTx era
fromSimpleRep SimpleRep (ShelleyTx era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ShelleyTx" ::: ShelleyTxTypes era]
SimpleRep (ShelleyTx era)
rep
(\TxBody era
body TxWits era
wits Maybe (TxAuxData era)
aux -> forall era.
EraTx era =>
TxBody era
-> TxWits era -> StrictMaybe (TxAuxData era) -> ShelleyTx era
ShelleyTx TxBody era
body TxWits era
wits (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe (TxAuxData era)
aux))
instance HasSimpleRep IsValid
instance HasSpec IsValid
type AlonzoTxAuxDataTypes era =
'[ Map Word64 Metadatum
, StrictSeq (Timelock era)
]
instance AlonzoEraScript era => HasSimpleRep (AlonzoTxAuxData era) where
type
TheSop (AlonzoTxAuxData era) =
'["AlonzoTxOutData" ::: AlonzoTxAuxDataTypes era]
toSimpleRep :: AlonzoTxAuxData era -> SimpleRep (AlonzoTxAuxData era)
toSimpleRep (AlonzoTxAuxData Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq Map Language (NonEmpty PlutusBinary)
_) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"AlonzoTxAuxData" @'["AlonzoTxAuxData" ::: AlonzoTxAuxDataTypes era]
Map Word64 Metadatum
metaMap
StrictSeq (Timelock era)
tsSeq
fromSimpleRep :: SimpleRep (AlonzoTxAuxData era) -> AlonzoTxAuxData era
fromSimpleRep SimpleRep (AlonzoTxAuxData era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["AlonzoTxAuxData" ::: AlonzoTxAuxDataTypes era] SimpleRep (AlonzoTxAuxData era)
rep forall a b. (a -> b) -> a -> b
$
\Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq -> forall era.
(HasCallStack, AlonzoEraScript era) =>
Map Word64 Metadatum
-> StrictSeq (Timelock era)
-> Map Language (NonEmpty PlutusBinary)
-> AlonzoTxAuxData era
AlonzoTxAuxData Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq forall a. Monoid a => a
mempty
instance
( Era era
, AlonzoEraScript era
, NativeScript era ~ Timelock era
) =>
HasSpec (AlonzoTxAuxData era)
type AllegraTxAuxDataTypes era =
'[ Map Word64 Metadatum
, StrictSeq (Timelock era)
]
instance Era era => HasSimpleRep (AllegraTxAuxData era) where
type
TheSop (AllegraTxAuxData era) =
'["AllegraTxOutData" ::: AllegraTxAuxDataTypes era]
toSimpleRep :: AllegraTxAuxData era -> SimpleRep (AllegraTxAuxData era)
toSimpleRep (AllegraTxAuxData Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"AllegraTxAuxData" @'["AllegraTxAuxData" ::: AllegraTxAuxDataTypes era]
Map Word64 Metadatum
metaMap
StrictSeq (Timelock era)
tsSeq
fromSimpleRep :: SimpleRep (AllegraTxAuxData era) -> AllegraTxAuxData era
fromSimpleRep SimpleRep (AllegraTxAuxData era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["AllegraTxAuxData" ::: AllegraTxAuxDataTypes era] SimpleRep (AllegraTxAuxData era)
rep forall a b. (a -> b) -> a -> b
$
\Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq -> forall era.
Era era =>
Map Word64 Metadatum
-> StrictSeq (Timelock era) -> AllegraTxAuxData era
AllegraTxAuxData Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq
instance
( Era era
, AllegraEraScript era
, NativeScript era ~ Timelock era
) =>
HasSpec (AllegraTxAuxData era)
type ShelleyTxAuxDataTypes era =
'[ Map Word64 Metadatum
]
instance Era era => HasSimpleRep (ShelleyTxAuxData era) where
type
TheSop (ShelleyTxAuxData era) =
'["ShelleyTxAuxData" ::: ShelleyTxAuxDataTypes era]
toSimpleRep :: ShelleyTxAuxData era -> SimpleRep (ShelleyTxAuxData era)
toSimpleRep (ShelleyTxAuxData Map Word64 Metadatum
metaMap) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"ShelleyTxAuxData" @'["ShelleyTxAuxData" ::: ShelleyTxAuxDataTypes era]
Map Word64 Metadatum
metaMap
fromSimpleRep :: SimpleRep (ShelleyTxAuxData era) -> ShelleyTxAuxData era
fromSimpleRep SimpleRep (ShelleyTxAuxData era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ShelleyTxAuxData" ::: ShelleyTxAuxDataTypes era] SimpleRep (ShelleyTxAuxData era)
rep forall a b. (a -> b) -> a -> b
$
\Map Word64 Metadatum
metaMap -> forall era. Era era => Map Word64 Metadatum -> ShelleyTxAuxData era
ShelleyTxAuxData Map Word64 Metadatum
metaMap
instance
( Era era
, AllegraEraScript era
, NativeScript era ~ Timelock era
) =>
HasSpec (ShelleyTxAuxData era)
instance HasSimpleRep Metadatum
instance HasSpec Metadatum
type AlonzoTxWitsTypes =
'[ Set (WitVKey 'Witness)
, Set BootstrapWitness
]
instance AlonzoEraScript era => HasSimpleRep (AlonzoTxWits era) where
type
TheSop (AlonzoTxWits era) =
'["AlonzoTxWits" ::: AlonzoTxWitsTypes]
toSimpleRep :: AlonzoTxWits era -> SimpleRep (AlonzoTxWits era)
toSimpleRep (AlonzoTxWits Set (WitVKey 'Witness)
vkeyWits Set BootstrapWitness
bootstrapWits Map ScriptHash (Script era)
_ TxDats era
_ Redeemers era
_) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"AlonzoTxWits" @'["AlonzoTxWits" ::: AlonzoTxWitsTypes]
Set (WitVKey 'Witness)
vkeyWits
Set BootstrapWitness
bootstrapWits
fromSimpleRep :: SimpleRep (AlonzoTxWits era) -> AlonzoTxWits era
fromSimpleRep SimpleRep (AlonzoTxWits era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["AlonzoTxWits" ::: AlonzoTxWitsTypes] SimpleRep (AlonzoTxWits era)
rep forall a b. (a -> b) -> a -> b
$
\Set (WitVKey 'Witness)
vkeyWits Set BootstrapWitness
bootstrapWits -> forall era.
AlonzoEraScript era =>
Set (WitVKey 'Witness)
-> Set BootstrapWitness
-> Map ScriptHash (Script era)
-> TxDats era
-> Redeemers era
-> AlonzoTxWits era
AlonzoTxWits Set (WitVKey 'Witness)
vkeyWits Set BootstrapWitness
bootstrapWits forall a. Monoid a => a
mempty (forall era.
Era era =>
Map (SafeHash EraIndependentData) (Data era) -> TxDats era
TxDats forall a. Monoid a => a
mempty) (forall era.
AlonzoEraScript era =>
Map (PlutusPurpose AsIx era) (Data era, ExUnits) -> Redeemers era
Redeemers forall a. Monoid a => a
mempty)
instance AlonzoEraScript era => HasSpec (AlonzoTxWits era)
type ShelleyTxWitsTypes era =
'[ Set (WitVKey 'Witness)
, Set BootstrapWitness
]
instance EraScript era => HasSimpleRep (ShelleyTxWits era) where
type
TheSop (ShelleyTxWits era) =
'["ShelleyTxWits" ::: ShelleyTxWitsTypes era]
toSimpleRep :: ShelleyTxWits era -> SimpleRep (ShelleyTxWits era)
toSimpleRep (ShelleyTxWits Set (WitVKey 'Witness)
vkeyWits Map ScriptHash (Script era)
_ Set BootstrapWitness
bootstrapWits) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"ShelleyTxWits" @'["ShelleyTxWits" ::: ShelleyTxWitsTypes era]
Set (WitVKey 'Witness)
vkeyWits
Set BootstrapWitness
bootstrapWits
fromSimpleRep :: SimpleRep (ShelleyTxWits era) -> ShelleyTxWits era
fromSimpleRep SimpleRep (ShelleyTxWits era)
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ShelleyTxWits" ::: ShelleyTxWitsTypes era] SimpleRep (ShelleyTxWits era)
rep forall a b. (a -> b) -> a -> b
$
\Set (WitVKey 'Witness)
vkeyWits Set BootstrapWitness
bootstrapWits -> forall era.
EraScript era =>
Set (WitVKey 'Witness)
-> Map ScriptHash (Script era)
-> Set BootstrapWitness
-> ShelleyTxWits era
ShelleyTxWits Set (WitVKey 'Witness)
vkeyWits forall a. Monoid a => a
mempty Set BootstrapWitness
bootstrapWits
instance EraScript era => HasSpec (ShelleyTxWits era)
instance Typeable r => HasSpec (WitVKey r) where
type TypeSpec (WitVKey r) = ()
emptySpec :: TypeSpec (WitVKey r)
emptySpec = ()
combineSpec :: TypeSpec (WitVKey r)
-> TypeSpec (WitVKey r) -> Specification (WitVKey r)
combineSpec TypeSpec (WitVKey r)
_ TypeSpec (WitVKey r)
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (WitVKey r) -> GenT m (WitVKey r)
genFromTypeSpec TypeSpec (WitVKey r)
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec (WitVKey r) -> Specification Integer
cardinalTypeSpec TypeSpec (WitVKey r)
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec (WitVKey r) -> WitVKey r -> [WitVKey r]
shrinkWithTypeSpec TypeSpec (WitVKey r)
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack => WitVKey r -> TypeSpec (WitVKey r) -> Bool
conformsTo WitVKey r
_ TypeSpec (WitVKey r)
_ = Bool
True
toPreds :: Term (WitVKey r) -> TypeSpec (WitVKey r) -> Pred
toPreds Term (WitVKey r)
_ TypeSpec (WitVKey r)
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance HasSpec BootstrapWitness where
type TypeSpec BootstrapWitness = ()
emptySpec :: TypeSpec BootstrapWitness
emptySpec = ()
combineSpec :: TypeSpec BootstrapWitness
-> TypeSpec BootstrapWitness -> Specification BootstrapWitness
combineSpec TypeSpec BootstrapWitness
_ TypeSpec BootstrapWitness
_ = forall a. Specification a
TrueSpec
genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec BootstrapWitness -> GenT m BootstrapWitness
genFromTypeSpec TypeSpec BootstrapWitness
_ = forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen forall a. Arbitrary a => Gen a
arbitrary
cardinalTypeSpec :: TypeSpec BootstrapWitness -> Specification Integer
cardinalTypeSpec TypeSpec BootstrapWitness
_ = forall a. Specification a
TrueSpec
shrinkWithTypeSpec :: TypeSpec BootstrapWitness -> BootstrapWitness -> [BootstrapWitness]
shrinkWithTypeSpec TypeSpec BootstrapWitness
_ = forall a. Arbitrary a => a -> [a]
shrink
conformsTo :: HasCallStack =>
BootstrapWitness -> TypeSpec BootstrapWitness -> Bool
conformsTo BootstrapWitness
_ TypeSpec BootstrapWitness
_ = Bool
True
toPreds :: Term BootstrapWitness -> TypeSpec BootstrapWitness -> Pred
toPreds Term BootstrapWitness
_ TypeSpec BootstrapWitness
_ = forall p. IsPred p => p -> Pred
toPred Bool
True
instance Era era => HasSimpleRep (LedgerEnv era)
instance (HasSpec (PParams era), Era era) => HasSpec (LedgerEnv era)
onJust' ::
( HasSpec a
, IsNormalType a
, IsPred p
) =>
Term (StrictMaybe a) ->
(Term a -> p) ->
Pred
onJust' :: forall a p.
(HasSpec a, IsNormalType a, IsPred p) =>
Term (StrictMaybe a) -> (Term a -> p) -> Pred
onJust' Term (StrictMaybe a)
tm Term a -> p
p = forall a.
(HasSpec a, HasSpec (SimpleRep a), HasSimpleRep a,
TypeSpec a ~ TypeSpec (SimpleRep a),
SimpleRep a ~ SumOver (Cases (SimpleRep a)),
TypeList (Cases (SimpleRep a))) =>
Term a
-> FunTy (MapList (Weighted Binder) (Cases (SimpleRep a))) Pred
caseOn Term (StrictMaybe a)
tm (forall p a.
(HasSpec a, All HasSpec (Args a), IsPred p, IsProd a) =>
FunTy (MapList Term (Args a)) p -> Weighted Binder a
branch forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const Bool
True) (forall p a.
(HasSpec a, All HasSpec (Args a), IsPred p, IsProd a) =>
FunTy (MapList Term (Args a)) p -> Weighted Binder a
branch Term a -> p
p)
onSized ::
(HasSpec a, IsPred p) =>
Term (Sized a) ->
(Term a -> p) ->
Pred
onSized :: forall a p.
(HasSpec a, IsPred p) =>
Term (Sized a) -> (Term a -> p) -> Pred
onSized Term (Sized a)
sz Term a -> p
p = forall p a.
(HasSpec a, IsProductType a, IsPred p) =>
Term a -> FunTy (MapList Term (ProductAsList a)) p -> Pred
match Term (Sized a)
sz forall a b. (a -> b) -> a -> b
$ \Term a
a Term Int64
_ -> Term a -> p
p Term a
a
instance Typeable era => HasSimpleRep (ConwayDelegEnv era)
instance (HasSpec (PParams era), Era era) => HasSpec (ConwayDelegEnv era)
instance Era era => HasSimpleRep (EpochState era)
instance
( EraTxOut era
, HasSpec (TxOut era)
, IsNormalType (TxOut era)
, HasSpec (GovState era)
, EraStake era
, EraCertState era
, IsNormalType (CertState era)
, HasSpec (InstantStake era)
, HasSpec (CertState era)
) =>
HasSpec (EpochState era)
instance HasSimpleRep FreeVars
instance HasSpec FreeVars
instance HasSimpleRep PoolRewardInfo
instance HasSpec PoolRewardInfo
instance HasSimpleRep LeaderOnlyReward
instance HasSpec LeaderOnlyReward
instance HasSimpleRep StakeShare
instance HasSpec StakeShare
instance HasSimpleRep BlocksMade
instance HasSpec BlocksMade
instance HasSimpleRep RewardType
instance HasSpec RewardType
instance HasSimpleRep RewardAns
instance HasSpec RewardAns
instance HasSimpleRep PulsingRewUpdate where
type SimpleRep PulsingRewUpdate = SimpleRep RewardUpdate
toSimpleRep :: PulsingRewUpdate -> SimpleRep PulsingRewUpdate
toSimpleRep (Complete RewardUpdate
x) = forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep RewardUpdate
x
toSimpleRep x :: PulsingRewUpdate
x@(Pulsing RewardSnapShot
_ Pulser
_) = forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep (forall a. ShelleyBase a -> a
runShelleyBase (forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PulsingRewUpdate
-> ShelleyBase
(RewardUpdate, Map (Credential 'Staking) (Set Reward))
completeRupd PulsingRewUpdate
x))
fromSimpleRep :: SimpleRep PulsingRewUpdate -> PulsingRewUpdate
fromSimpleRep SimpleRep PulsingRewUpdate
x = RewardUpdate -> PulsingRewUpdate
Complete (forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep SimpleRep PulsingRewUpdate
x)
instance HasSpec PulsingRewUpdate
instance (Typeable (StashedAVVMAddresses era), Era era) => HasSimpleRep (NewEpochState era)
instance
( EraTxOut era
, HasSpec (TxOut era)
, IsNormalType (TxOut era)
, HasSpec (GovState era)
, HasSpec (StashedAVVMAddresses era)
, EraStake era
, EraCertState era
, IsNormalType (CertState era)
, HasSpec (CertState era)
, HasSpec (InstantStake era)
) =>
HasSpec (NewEpochState era)
instance HasSimpleRep Reward
instance HasSpec Reward
instance HasSimpleRep RewardSnapShot
instance HasSpec RewardSnapShot
instance HasSimpleRep RewardUpdate
instance HasSpec RewardUpdate
type PulserTypes =
'[ Int
, FreeVars
, VMap VMap.VB VMap.VP (Credential 'Staking) (CompactForm Coin)
, RewardAns
]
instance HasSimpleRep Pulser where
type TheSop Pulser = '["Pulser" ::: PulserTypes]
toSimpleRep :: Pulser -> SimpleRep Pulser
toSimpleRep (RSLP Int
n FreeVars
free VMap VB VP (Credential 'Staking) (CompactForm Coin)
bal RewardAns
ans) =
forall (c :: Symbol) (constrs :: [*]).
Inject c constrs (SOP constrs) =>
FunTy (ConstrOf c constrs) (SOP constrs)
inject @"Pulser" @'["Pulser" ::: PulserTypes]
Int
n
FreeVars
free
VMap VB VP (Credential 'Staking) (CompactForm Coin)
bal
RewardAns
ans
fromSimpleRep :: SimpleRep Pulser -> Pulser
fromSimpleRep SimpleRep Pulser
rep =
forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["Pulser" ::: PulserTypes]
SimpleRep Pulser
rep
forall ans (m :: * -> *).
(ans ~ RewardAns, m ~ ReaderT Globals Identity) =>
Int
-> FreeVars
-> VMap VB VP (Credential 'Staking) (CompactForm Coin)
-> ans
-> RewardPulser m ans
RSLP
instance HasSpec Pulser
instance (Typeable (Tx era), Typeable era) => HasSimpleRep (CertsEnv era)
instance (EraGov era, EraTx era, EraSpecPParams era, HasSpec (Tx era)) => HasSpec (CertsEnv era)
class Coercible a b => CoercibleLike a b where
coerceSpec ::
Specification b ->
Specification a
getCoerceSpec ::
TypeSpec a ->
Specification b
instance Typeable krole => CoercibleLike (KeyHash krole) (KeyHash 'Witness) where
coerceSpec :: Specification (KeyHash 'Witness) -> Specification (KeyHash krole)
coerceSpec (ExplainSpec [[Char]]
es Specification (KeyHash 'Witness)
x) = forall a. [[Char]] -> Specification a -> Specification a
explainSpecOpt [[Char]]
es (forall a b. CoercibleLike a b => Specification b -> Specification a
coerceSpec Specification (KeyHash 'Witness)
x)
coerceSpec (TypeSpec TypeSpec (KeyHash 'Witness)
z [KeyHash 'Witness]
excl) = forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec TypeSpec (KeyHash 'Witness)
z forall a b. (a -> b) -> a -> b
$ forall (a :: KeyRole -> *) (r :: KeyRole) (r' :: KeyRole).
HasKeyRole a =>
a r -> a r'
coerceKeyRole forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [KeyHash 'Witness]
excl
coerceSpec (MemberSpec NonEmpty (KeyHash 'Witness)
s) = forall a. NonEmpty a -> Specification a
MemberSpec forall a b. (a -> b) -> a -> b
$ forall (a :: KeyRole -> *) (r :: KeyRole) (r' :: KeyRole).
HasKeyRole a =>
a r -> a r'
coerceKeyRole forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (KeyHash 'Witness)
s
coerceSpec (ErrorSpec NonEmpty [Char]
e) = forall a. NonEmpty [Char] -> Specification a
ErrorSpec NonEmpty [Char]
e
coerceSpec (SuspendedSpec Var (KeyHash 'Witness)
x Pred
p) = forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained forall a b. (a -> b) -> a -> b
$ \Term (KeyHash krole)
x' ->
[ Pred
p
, forall a b p.
(HasSpec a, HasSpec b, IsPred p) =>
Term a -> (a -> b) -> (Term b -> p) -> Pred
reify Term (KeyHash krole)
x' forall (a :: KeyRole -> *) (r :: KeyRole) (r' :: KeyRole).
HasKeyRole a =>
a r -> a r'
coerceKeyRole (forall a. HasSpec a => Term a -> Term a -> Term Bool
==. forall a. HasSpec a => Var a -> Term a
V Var (KeyHash 'Witness)
x)
]
coerceSpec Specification (KeyHash 'Witness)
TrueSpec = forall a. Specification a
TrueSpec
getCoerceSpec ::
TypeSpec (KeyHash krole) ->
Specification (KeyHash 'Witness)
getCoerceSpec :: TypeSpec (KeyHash krole) -> Specification (KeyHash 'Witness)
getCoerceSpec TypeSpec (KeyHash krole)
x = forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec TypeSpec (KeyHash krole)
x forall a. Monoid a => a
mempty
instance CoercibleLike (CompactForm Coin) Word64 where
coerceSpec :: Specification Word64 -> Specification (CompactForm Coin)
coerceSpec (TypeSpec (NumSpecInterval Maybe Word64
lo Maybe Word64
hi) [Word64]
excl) =
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec (forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval Maybe Word64
lo Maybe Word64
hi) forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word64]
excl
coerceSpec (MemberSpec NonEmpty Word64
s) = forall a. NonEmpty a -> Specification a
MemberSpec forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty Word64
s
coerceSpec (ErrorSpec NonEmpty [Char]
e) = forall a. NonEmpty [Char] -> Specification a
ErrorSpec NonEmpty [Char]
e
coerceSpec (SuspendedSpec Var Word64
x Pred
p) = forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained forall a b. (a -> b) -> a -> b
$ \Term (CompactForm Coin)
x' ->
[ Pred
p
, forall a b p.
(HasSpec a, HasSpec b, IsPred p) =>
Term a -> (a -> b) -> (Term b -> p) -> Pred
reify Term (CompactForm Coin)
x' CompactForm Coin -> Word64
unCompactCoin (forall a. HasSpec a => Term a -> Term a -> Term Bool
==. forall a. HasSpec a => Var a -> Term a
V Var Word64
x)
]
coerceSpec Specification Word64
TrueSpec = forall a. Specification a
TrueSpec
coerceSpec (ExplainSpec [[Char]]
es Specification Word64
x) = forall a. [[Char]] -> Specification a -> Specification a
ExplainSpec [[Char]]
es (forall a b. CoercibleLike a b => Specification b -> Specification a
coerceSpec Specification Word64
x)
getCoerceSpec ::
TypeSpec (CompactForm Coin) ->
Specification Word64
getCoerceSpec :: TypeSpec (CompactForm Coin) -> Specification Word64
getCoerceSpec (NumSpecInterval Maybe Word64
a Maybe Word64
b) = forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec (forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval Maybe Word64
a Maybe Word64
b) forall a. Monoid a => a
mempty
data CoercibleW (s :: Symbol) (args :: [Type]) (res :: Type) where
CoerceW :: (CoercibleLike a b, Coercible a b) => CoercibleW "coerce_" '[a] b
deriving instance Show (CoercibleW sym args res)
deriving instance Eq (CoercibleW sym args res)
instance Syntax CoercibleW
instance Semantics CoercibleW where
semantics :: forall (s :: Symbol) (d :: [*]) r. CoercibleW s d r -> FunTy d r
semantics = \case
CoercibleW s d r
CoerceW -> coerce :: forall a b. Coercible a b => a -> b
coerce
instance (Typeable a, Typeable b, CoercibleLike a b) => Logic "coerce_" CoercibleW '[a] b where
propagate :: forall hole.
Context "coerce_" CoercibleW '[a] b hole
-> Specification b -> Specification hole
propagate Context "coerce_" CoercibleW '[a] b hole
ctxt (ExplainSpec [] Specification b
s) = forall (s :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
rng hole.
Logic s t dom rng =>
Context s t dom rng hole -> Specification rng -> Specification hole
propagate Context "coerce_" CoercibleW '[a] b hole
ctxt Specification b
s
propagate Context "coerce_" CoercibleW '[a] b hole
ctxt (ExplainSpec [[Char]]
es Specification b
s) = forall a. [[Char]] -> Specification a -> Specification a
ExplainSpec [[Char]]
es forall a b. (a -> b) -> a -> b
$ forall (s :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
rng hole.
Logic s t dom rng =>
Context s t dom rng hole -> Specification rng -> Specification hole
propagate Context "coerce_" CoercibleW '[a] b hole
ctxt Specification b
s
propagate Context "coerce_" CoercibleW '[a] b hole
_ Specification b
TrueSpec = forall a. Specification a
TrueSpec
propagate Context "coerce_" CoercibleW '[a] b hole
_ (ErrorSpec NonEmpty [Char]
msgs) = forall a. NonEmpty [Char] -> Specification a
ErrorSpec NonEmpty [Char]
msgs
propagate (Context CoercibleW "coerce_" '[a] b
CoerceW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) (SuspendedSpec Var b
v Pred
ps) =
forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained forall a b. (a -> b) -> a -> b
$ \Term hole
v' -> forall a. Term a -> Binder a -> Pred
Let (forall (sym :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
a.
AppRequires sym t dom a =>
t sym dom a -> List Term dom -> Term a
App forall a b.
(CoercibleLike a b, Coercible a b) =>
CoercibleW "coerce_" '[a] b
CoerceW (Term hole
v' forall {k} (f :: k -> *) (a :: k) (as1 :: [k]).
f a -> List f as1 -> List f (a : as1)
:> forall {k} (f :: k -> *). List f '[]
Nil)) (Var b
v forall a. HasSpec a => Var a -> Pred -> Binder a
:-> Pred
ps)
propagate (Context CoercibleW "coerce_" '[a] b
CoerceW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) Specification b
spec = forall a b. CoercibleLike a b => Specification b -> Specification a
coerceSpec @a @b Specification b
spec
propagate Context "coerce_" CoercibleW '[a] b hole
ctx Specification b
_ =
forall a. NonEmpty [Char] -> Specification a
ErrorSpec forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char]
"Logic instance for CoerceW with wrong number of arguments. " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Context "coerce_" CoercibleW '[a] b hole
ctx)
mapTypeSpec :: forall a b.
('[a] ~ '[a], b ~ b, HasSpec a, HasSpec b) =>
CoercibleW "coerce_" '[a] b -> TypeSpec a -> Specification b
mapTypeSpec CoercibleW "coerce_" '[a] b
CoerceW TypeSpec a
ss = forall a b. CoercibleLike a b => TypeSpec a -> Specification b
getCoerceSpec @a TypeSpec a
ss
coerce_ ::
forall a b.
( HasSpec a
, HasSpec b
, CoercibleLike a b
) =>
Term a ->
Term b
coerce_ :: forall a b.
(HasSpec a, HasSpec b, CoercibleLike a b) =>
Term a -> Term b
coerce_ = forall (sym :: Symbol) (t :: Symbol -> [*] -> * -> *) (ds :: [*])
r.
AppRequires sym t ds r =>
t sym ds r -> FunTy (MapList Term ds) (Term r)
appTerm forall a b.
(CoercibleLike a b, Coercible a b) =>
CoercibleW "coerce_" '[a] b
CoerceW
data CoinW (s :: Symbol) (ds :: [Type]) (res :: Type) where
ToDeltaW :: CoinW "toDelta_" '[Coin] DeltaCoin
deriving instance Show (CoinW s args res)
deriving instance Eq (CoinW s args res)
instance Syntax CoinW
instance Semantics CoinW where
semantics :: forall (s :: Symbol) (d :: [*]) r. CoinW s d r -> FunTy d r
semantics = \case
CoinW s d r
ToDeltaW -> Integer -> DeltaCoin
DeltaCoin forall b c a. (b -> c) -> (a -> b) -> a -> c
. Coin -> Integer
unCoin
toDelta_ ::
Term Coin ->
Term DeltaCoin
toDelta_ :: Term Coin -> Term DeltaCoin
toDelta_ = forall (sym :: Symbol) (t :: Symbol -> [*] -> * -> *) (ds :: [*])
r.
AppRequires sym t ds r =>
t sym ds r -> FunTy (MapList Term ds) (Term r)
appTerm CoinW "toDelta_" '[Coin] DeltaCoin
ToDeltaW
instance Logic "toDelta_" CoinW '[Coin] DeltaCoin where
propagate :: forall hole.
Context "toDelta_" CoinW '[Coin] DeltaCoin hole
-> Specification DeltaCoin -> Specification hole
propagate Context "toDelta_" CoinW '[Coin] DeltaCoin hole
ctxt (ExplainSpec [[Char]]
es Specification DeltaCoin
s) = forall a. [[Char]] -> Specification a -> Specification a
ExplainSpec [[Char]]
es forall a b. (a -> b) -> a -> b
$ forall (s :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
rng hole.
Logic s t dom rng =>
Context s t dom rng hole -> Specification rng -> Specification hole
propagate Context "toDelta_" CoinW '[Coin] DeltaCoin hole
ctxt Specification DeltaCoin
s
propagate Context "toDelta_" CoinW '[Coin] DeltaCoin hole
_ Specification DeltaCoin
TrueSpec = forall a. Specification a
TrueSpec
propagate Context "toDelta_" CoinW '[Coin] DeltaCoin hole
_ (ErrorSpec NonEmpty [Char]
msgs) = forall a. NonEmpty [Char] -> Specification a
ErrorSpec NonEmpty [Char]
msgs
propagate (Context CoinW "toDelta_" '[Coin] DeltaCoin
ToDeltaW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) (SuspendedSpec Var DeltaCoin
v Pred
ps) =
forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained forall a b. (a -> b) -> a -> b
$ \Term hole
v' -> forall a. Term a -> Binder a -> Pred
Let (forall (sym :: Symbol) (t :: Symbol -> [*] -> * -> *) (dom :: [*])
a.
AppRequires sym t dom a =>
t sym dom a -> List Term dom -> Term a
App CoinW "toDelta_" '[Coin] DeltaCoin
ToDeltaW (Term hole
v' forall {k} (f :: k -> *) (a :: k) (as1 :: [k]).
f a -> List f as1 -> List f (a : as1)
:> forall {k} (f :: k -> *). List f '[]
Nil)) (Var DeltaCoin
v forall a. HasSpec a => Var a -> Pred -> Binder a
:-> Pred
ps)
propagate (Context CoinW "toDelta_" '[Coin] DeltaCoin
ToDeltaW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) (MemberSpec NonEmpty DeltaCoin
xs) = forall a. NonEmpty a -> Specification a
MemberSpec (forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map DeltaCoin -> Coin
deltaToCoin NonEmpty DeltaCoin
xs)
propagate (Context CoinW "toDelta_" '[Coin] DeltaCoin
ToDeltaW (Ctx hole y
HOLE :<> CList 'Post as1 Any Any
forall i j. CList 'Post as1 i j
End)) (TypeSpec (NumSpecInterval Maybe Integer
l Maybe Integer
h) [DeltaCoin]
cant) =
( forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec
(forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer
l) (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer
h))
(forall a b. (a -> b) -> [a] -> [b]
map DeltaCoin -> Coin
deltaToCoin [DeltaCoin]
cant)
)
propagate Context "toDelta_" CoinW '[Coin] DeltaCoin hole
ctx Specification DeltaCoin
_ =
forall a. NonEmpty [Char] -> Specification a
ErrorSpec forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char]
"Logic instance for ToDeltaW with wrong number of arguments. " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Context "toDelta_" CoinW '[Coin] DeltaCoin hole
ctx)
mapTypeSpec :: forall a b.
('[Coin] ~ '[a], DeltaCoin ~ b, HasSpec a, HasSpec b) =>
CoinW "toDelta_" '[a] b -> TypeSpec a -> Specification b
mapTypeSpec CoinW "toDelta_" '[a] b
ToDeltaW (NumSpecInterval Maybe Word64
l Maybe Word64
h) = forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec (forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Word64
l) (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Word64
h))
deltaToCoin :: DeltaCoin -> Coin
deltaToCoin :: DeltaCoin -> Coin
deltaToCoin (DeltaCoin Integer
i) = Integer -> Coin
Coin Integer
i
instance Typeable era => HasSimpleRep (ShelleyGovState era)
instance (EraTxOut era, EraGov era, EraSpecPParams era) => HasSpec (ShelleyGovState era)
instance HasSimpleRep ShelleyDelegCert
instance HasSpec ShelleyDelegCert
instance HasSimpleRep MIRCert
instance HasSpec MIRCert
instance HasSimpleRep MIRTarget
instance HasSpec MIRTarget
instance HasSimpleRep MIRPot
instance HasSpec MIRPot
instance HasSimpleRep (ShelleyTxCert era)
instance Era era => HasSpec (ShelleyTxCert era)
instance HasSimpleRep GenesisDelegCert
instance HasSpec GenesisDelegCert