{-# 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 PartialTypeSignatures #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
-- GHC9.2.8 needs this
{-# OPTIONS_GHC -Wno-redundant-constraints #-}

-- | This module provides the necessary instances of `HasSpec`
-- and `HasSimpleRep` to write specs for the environments,
-- states, and signals in the STS rules of the Ledger. Note some simple
-- types used in the PParams (Coin, EpochInterval, etc.) have their
-- instances defined in Test.Cardano.Ledger.Constrained.Conway.Instances.Basic
-- and they are reexported here.
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.Hash hiding (Blake2b_224)
import Cardano.Crypto.Hashing (AbstractHash, abstractHashFromBytes)
import Cardano.Ledger.Address
import Cardano.Ledger.Allegra.Scripts
import Cardano.Ledger.Allegra.TxAuxData (AllegraTxAuxData (..))
import Cardano.Ledger.Alonzo.Scripts (AlonzoScript (..))
import Cardano.Ledger.Alonzo.Tx
import Cardano.Ledger.Alonzo.TxAuxData (AlonzoTxAuxData (..))
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.NumSpec
import Constrained.Spec.Map
import Constrained.Spec.Tree ()
import Constrained.SumList (genListWithSize)
import Constrained.TheKnot qualified as C
import Control.DeepSeq (NFData)
import Crypto.Hash (Blake2b_224)
import Data.ByteString qualified as BS
import Data.ByteString.Short (ShortByteString)
import Data.ByteString.Short qualified as SBS
import Data.Coerce
import Data.Foldable
import Data.Int
import Data.Kind
import Data.List.NonEmpty qualified as NE
import Data.Map (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.OMap.Strict qualified as OMap
import Data.OSet.Strict qualified as SOS
import Data.Sequence (Seq)
import Data.Sequence qualified as Seq
import Data.Sequence.Strict (StrictSeq)
import Data.Sequence.Strict qualified as StrictSeq
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Tree
import Data.Typeable
import Data.VMap (VMap)
import Data.VMap qualified as VMap
import Data.Word
import GHC.Generics (Generic)
import PlutusLedgerApi.V1 qualified as PV1
import Test.Cardano.Ledger.Allegra.Arbitrary ()
import Test.Cardano.Ledger.Alonzo.Arbitrary ()
import Test.Cardano.Ledger.Constrained.Conway.Instances.Basic
import Test.Cardano.Ledger.Constrained.Conway.Instances.PParams ()
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)

-- ==========================================================
-- TxBody HasSpec instance ------------------------------------------------

-- NOTE: this is a representation of the `ConwayTxBody` type. You can't
-- simply use the generics to derive the `SimpleRep` for `ConwayTxBody`
-- because the type is memoized. So instead we say that the representation
-- is the same as what you would get from using the `ConwayTxBody` pattern.
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 (TxBody ConwayEra)

instance HasSimpleRep (TxBody ConwayEra) where
  type TheSop (TxBody ConwayEra) = '["ConwayTxBody" ::: ConwayTxBodyTypes]
  toSimpleRep :: TxBody ConwayEra -> SimpleRep (TxBody ConwayEra)
toSimpleRep ConwayTxBody {OSet (TxCert ConwayEra)
OSet (ProposalProcedure ConwayEra)
Set (KeyHash 'Witness)
Set TxIn
StrictMaybe ScriptIntegrityHash
StrictMaybe TxAuxDataHash
StrictMaybe Coin
StrictMaybe (Sized (TxOut ConwayEra))
StrictMaybe Network
ValidityInterval
Withdrawals
VotingProcedures ConwayEra
Coin
StrictSeq (Sized (TxOut ConwayEra))
MultiAsset
ctbSpendInputs :: Set TxIn
ctbCollateralInputs :: Set TxIn
ctbReferenceInputs :: Set TxIn
ctbOutputs :: StrictSeq (Sized (TxOut ConwayEra))
ctbCollateralReturn :: StrictMaybe (Sized (TxOut ConwayEra))
ctbTotalCollateral :: StrictMaybe Coin
ctbCerts :: OSet (TxCert ConwayEra)
ctbWithdrawals :: Withdrawals
ctbTxfee :: Coin
ctbVldt :: ValidityInterval
ctbReqSignerHashes :: Set (KeyHash 'Witness)
ctbMint :: MultiAsset
ctbScriptIntegrityHash :: StrictMaybe ScriptIntegrityHash
ctbAdHash :: StrictMaybe TxAuxDataHash
ctbTxNetworkId :: StrictMaybe Network
ctbVotingProcedures :: VotingProcedures ConwayEra
ctbProposalProcedures :: OSet (ProposalProcedure ConwayEra)
ctbCurrentTreasuryValue :: StrictMaybe Coin
ctbTreasuryDonation :: Coin
ctbSpendInputs :: TxBody ConwayEra -> Set TxIn
ctbCollateralInputs :: TxBody ConwayEra -> Set TxIn
ctbReferenceInputs :: TxBody ConwayEra -> Set TxIn
ctbOutputs :: TxBody ConwayEra -> StrictSeq (Sized (TxOut ConwayEra))
ctbCollateralReturn :: TxBody ConwayEra -> StrictMaybe (Sized (TxOut ConwayEra))
ctbTotalCollateral :: TxBody ConwayEra -> StrictMaybe Coin
ctbCerts :: TxBody ConwayEra -> OSet (TxCert ConwayEra)
ctbWithdrawals :: TxBody ConwayEra -> Withdrawals
ctbTxfee :: TxBody ConwayEra -> Coin
ctbVldt :: TxBody ConwayEra -> ValidityInterval
ctbReqSignerHashes :: TxBody ConwayEra -> Set (KeyHash 'Witness)
ctbMint :: TxBody ConwayEra -> MultiAsset
ctbScriptIntegrityHash :: TxBody ConwayEra -> StrictMaybe ScriptIntegrityHash
ctbAdHash :: TxBody ConwayEra -> StrictMaybe TxAuxDataHash
ctbTxNetworkId :: TxBody ConwayEra -> StrictMaybe Network
ctbVotingProcedures :: TxBody ConwayEra -> VotingProcedures ConwayEra
ctbProposalProcedures :: TxBody ConwayEra -> OSet (ProposalProcedure ConwayEra)
ctbCurrentTreasuryValue :: TxBody ConwayEra -> StrictMaybe Coin
ctbTreasuryDonation :: TxBody ConwayEra -> Coin
..} =
    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))
StrictSeq (Sized (BabbageTxOut ConwayEra))
ctbOutputs
      StrictMaybe (Sized (TxOut ConwayEra))
StrictMaybe (Sized (BabbageTxOut ConwayEra))
ctbCollateralReturn
      StrictMaybe Coin
ctbTotalCollateral
      OSet (TxCert ConwayEra)
OSet (ConwayTxCert 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 (TxBody ConwayEra) -> TxBody ConwayEra
fromSimpleRep SimpleRep (TxBody ConwayEra)
rep =
    forall (constrs :: [*]) r.
SOPLike constrs r =>
SOP constrs -> ALG constrs r
algebra @'["ConwayTxBody" ::: ConwayTxBodyTypes] SOP '["ConwayTxBody" ::: ConwayTxBodyTypes]
SimpleRep (TxBody ConwayEra)
rep Set TxIn
-> Set TxIn
-> Set TxIn
-> StrictSeq (Sized (TxOut ConwayEra))
-> StrictMaybe (Sized (TxOut ConwayEra))
-> StrictMaybe Coin
-> OSet (TxCert ConwayEra)
-> Withdrawals
-> Coin
-> ValidityInterval
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> VotingProcedures ConwayEra
-> OSet (ProposalProcedure ConwayEra)
-> StrictMaybe Coin
-> Coin
-> TxBody ConwayEra
Set TxIn
-> Set TxIn
-> Set TxIn
-> StrictSeq (Sized (BabbageTxOut ConwayEra))
-> StrictMaybe (Sized (BabbageTxOut ConwayEra))
-> StrictMaybe Coin
-> OSet (ConwayTxCert ConwayEra)
-> Withdrawals
-> Coin
-> ValidityInterval
-> Set (KeyHash 'Witness)
-> MultiAsset
-> StrictMaybe ScriptIntegrityHash
-> StrictMaybe TxAuxDataHash
-> StrictMaybe Network
-> VotingProcedures ConwayEra
-> OSet (ProposalProcedure ConwayEra)
-> StrictMaybe Coin
-> Coin
-> TxBody ConwayEra
ConwayTxBody

instance HasSimpleRep DeltaCoin where
  type SimpleRep DeltaCoin = Integer
  fromSimpleRep :: SimpleRep DeltaCoin -> DeltaCoin
fromSimpleRep = Integer -> DeltaCoin
SimpleRep DeltaCoin -> DeltaCoin
DeltaCoin
  toSimpleRep :: DeltaCoin -> SimpleRep DeltaCoin
toSimpleRep (DeltaCoin Integer
c) = Integer
SimpleRep DeltaCoin
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' = (Integer -> DeltaCoin) -> [Integer] -> [DeltaCoin]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> DeltaCoin
SimpleRep DeltaCoin -> DeltaCoin
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep ([Integer] -> [DeltaCoin])
-> GenT m [Integer] -> GenT m [DeltaCoin]
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 (Specification DeltaCoin -> Specification (SimpleRep DeltaCoin)
forall a.
GenericRequires a =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
s) (Specification DeltaCoin -> Specification (SimpleRep DeltaCoin)
forall a.
GenericRequires a =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
s')
  theAddFn :: IntW '[DeltaCoin, DeltaCoin] DeltaCoin
theAddFn = IntW '[DeltaCoin, DeltaCoin] DeltaCoin
forall b. NumLike b => IntW '[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 =
    (Integer -> DeltaCoin) -> [Integer] -> [DeltaCoin]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> DeltaCoin
SimpleRep DeltaCoin -> DeltaCoin
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep
      ([Integer] -> [DeltaCoin])
-> GenT m [Integer] -> GenT m [DeltaCoin]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a (m :: * -> *).
(Complete a, TypeSpec a ~ NumSpec a, MonadGenError m, Random a,
 Integral a, Arbitrary a, MaybeBounded a, Complete Integer,
 TypeSpec Integer ~ NumSpec Integer) =>
Specification Integer
-> Specification a -> Specification a -> GenT m [a]
genListWithSize @Integer Specification Integer
sz (Specification DeltaCoin -> Specification (SimpleRep DeltaCoin)
forall a.
GenericRequires a =>
Specification a -> Specification (SimpleRep a)
toSimpleRepSpec Specification DeltaCoin
elemSpec) (Specification DeltaCoin -> Specification (SimpleRep DeltaCoin)
forall a.
GenericRequires 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)
_ = Specification (SafeHash index)
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (SafeHash index) -> GenT m (SafeHash index)
genFromTypeSpec TypeSpec (SafeHash index)
_ = Gen (SafeHash index) -> GenT m (SafeHash index)
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen (SafeHash index)
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec (SafeHash index) -> Specification Integer
cardinalTypeSpec TypeSpec (SafeHash index)
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec (SafeHash index) -> SafeHash index -> [SafeHash index]
shrinkWithTypeSpec TypeSpec (SafeHash index)
_ = SafeHash index -> [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)
_ = Bool -> Pred
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 = StrictSeq a -> [a]
StrictSeq a -> SimpleRep (StrictSeq a)
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
  fromSimpleRep :: SimpleRep (StrictSeq a) -> StrictSeq a
fromSimpleRep = [a] -> StrictSeq a
SimpleRep (StrictSeq a) -> StrictSeq a
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 = Seq a -> [a]
Seq a -> SimpleRep (Seq a)
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList
  fromSimpleRep :: SimpleRep (Seq a) -> Seq a
fromSimpleRep = [a] -> Seq a
SimpleRep (Seq a) -> Seq a
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, GenericRequires 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, GenericRequires 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] SOP '["ShelleyTxOut" ::: ShelleyTxOutTypes era]
SimpleRep (ShelleyTxOut era)
rep Addr -> Value era -> ShelleyTxOut era
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 DataHash
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 DataHash
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] SOP '["AlonzoTxOut" ::: AlonzoTxOutTypes era]
SimpleRep (AlonzoTxOut era)
rep Addr -> Value era -> StrictMaybe DataHash -> AlonzoTxOut era
forall era.
(Era era, Val (Value era), HasCallStack) =>
Addr -> Value era -> StrictMaybe DataHash -> 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] SOP '["BabbageTxOut" ::: BabbageTxOutTypes era]
SimpleRep (BabbageTxOut era)
rep Addr
-> Value era
-> Datum era
-> StrictMaybe (Script era)
-> BabbageTxOut era
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, GenericRequires 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 = a -> SimpleRep a
forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep (a -> SimpleRep a)
-> (CompactForm a -> a) -> CompactForm a -> SimpleRep a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompactForm a -> a
forall a. Compactible a => CompactForm a -> a
fromCompact
  fromSimpleRep :: SimpleRep (CompactForm a) -> CompactForm a
fromSimpleRep SimpleRep (CompactForm a)
x = CompactForm a -> Maybe (CompactForm a) -> CompactForm a
forall a. a -> Maybe a -> a
fromMaybe CompactForm a
err (Maybe (CompactForm a) -> CompactForm a)
-> (a -> Maybe (CompactForm a)) -> a -> CompactForm a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe (CompactForm a)
forall a. Compactible a => a -> Maybe (CompactForm a)
toCompact (a -> CompactForm a) -> a -> CompactForm a
forall a b. (a -> b) -> a -> b
$ SimpleRep a -> a
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep SimpleRep a
SimpleRep (CompactForm a)
x
    where
      err :: CompactForm a
err = [Char] -> CompactForm a
forall a. HasCallStack => [Char] -> a
error ([Char] -> CompactForm a) -> [Char] -> CompactForm a
forall a b. (a -> b) -> a -> b
$ [Char]
"toCompact @" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ TypeRep -> [Char]
forall a. Show a => a -> [Char]
show (SimpleRep a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf SimpleRep a
SimpleRep (CompactForm a)
x) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ SimpleRep a -> [Char]
forall a. Show a => a -> [Char]
show SimpleRep a
SimpleRep (CompactForm a)
x

instance
  ( Compactible a
  , GenericallyInstantiated (CompactForm 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
SimpleRep MaryValue
c
  fromSimpleRep :: SimpleRep MaryValue -> MaryValue
fromSimpleRep SimpleRep MaryValue
c = Coin -> MultiAsset -> MaryValue
MaryValue Coin
SimpleRep MaryValue
c MultiAsset
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, GenericRequires 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
_ = Specification Data
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Data -> GenT m Data
genFromTypeSpec TypeSpec Data
_ = Gen Data -> GenT m Data
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen Data
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec Data -> Specification Integer
cardinalTypeSpec TypeSpec Data
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec Data -> Data -> [Data]
shrinkWithTypeSpec TypeSpec Data
_ = Data -> [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
_ = Bool -> Pred
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 = Data era -> SimpleRep (Data era)
Data era -> Data
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 (PlutusData era -> Data era)
-> (Data -> PlutusData era) -> Data -> Data era
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Data -> PlutusData era
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 = BinaryData era -> Data era
BinaryData era -> SimpleRep (BinaryData era)
forall era. Era era => BinaryData era -> Data era
binaryDataToData
  fromSimpleRep :: SimpleRep (BinaryData era) -> BinaryData era
fromSimpleRep = Data era -> BinaryData era
SimpleRep (BinaryData era) -> BinaryData era
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)

-- TODO: here we are cheating to get out of having to deal with Plutus scripts
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
SimpleRep (AlonzoScript era)
tl
  toSimpleRep (PlutusScript PlutusScript era
_) = [Char] -> Timelock era
forall a. HasCallStack => [Char] -> a
error [Char]
"toSimpleRep for AlonzoScript on a PlutusScript"
  fromSimpleRep :: SimpleRep (AlonzoScript era) -> AlonzoScript era
fromSimpleRep = Timelock era -> AlonzoScript era
SimpleRep (AlonzoScript era) -> AlonzoScript era
forall era. Timelock era -> AlonzoScript era
TimelockScript

instance
  ( AlonzoEraScript era
  , Script era ~ AlonzoScript era
  , NativeScript era ~ Timelock era
  ) =>
  HasSpec (AlonzoScript era)

{-
NOTE:
You might think that you could do something like this for `Timelock`.
However, when you do that some questions arise:
  (1) How are you going to write constraints over recursive types
      that don't blow up to infinity?
  (2) How are you going to generate recursive values?

(2) you could imagine solving with some tricks for controlling how we generate
Sum and Prod things (with some global index of sizes: `TypeRep -> Int`). Potentially
you could solve this by having size constraints in the language. There the question is
how you design those constraints - their semantics could be `const True` while still
changing the `Specification` - thus giving you the ability to provide a generation time hint!

Solving (1) is more tricky however. The best guess I have is that you would need
to push any constraint you have into functions `MyConstraint :: MyUniv '[Timelock era] Bool`
and implement everything "offline". This is highly non-satisfactory - but it's hard to see
how else you would do it.

type TimelockTypes era =
  '[ -- RequireSignature
     '[KeyHash 'Witness ]
     -- RequireAllOf
   , '[StrictSeq (Timelock era)]
     -- RequireAnyOf
   , '[StrictSeq (Timelock era)]
     -- RequireMOf
   , '[Int, StrictSeq (Timelock era)]
     -- RequireTimeExpire
   , '[SlotNo]
     -- RequireTimeStart
   , '[SlotNo]
   ]

instance Era era => HasSimpleRep (Timelock era) where
  type SimpleRep (Timelock era) = SOP (TimelockTypes era)

  toSimpleRep (RequireSignature h)  = inject @0 @(TimelockTypes era) h
  toSimpleRep (RequireAllOf ts)     = inject @1 @(TimelockTypes era) ts
  toSimpleRep (RequireAnyOf ts)     = inject @2 @(TimelockTypes era) ts
  toSimpleRep (RequireMOf m ts)     = inject @3 @(TimelockTypes era) m ts
  toSimpleRep (RequireTimeExpire s) = inject @4 @(TimelockTypes era) s
  toSimpleRep (RequireTimeStart s)  = inject @5 @(TimelockTypes era) s

  fromSimpleRep rep =
    algebra @(TimelockTypes era) rep
      RequireSignature
      RequireAllOf
      RequireAnyOf
      RequireMOf
      RequireTimeExpire
      RequireTimeStart
-}

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)
_ = Specification (Timelock era)
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (Timelock era) -> GenT m (Timelock era)
genFromTypeSpec TypeSpec (Timelock era)
_ = Gen (Timelock era) -> GenT m (Timelock era)
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen (Timelock era)
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec (Timelock era) -> Specification Integer
cardinalTypeSpec TypeSpec (Timelock era)
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec (Timelock era) -> Timelock era -> [Timelock era]
shrinkWithTypeSpec TypeSpec (Timelock era)
_ = Timelock era -> [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)
_ = Bool -> Pred
forall p. IsPred p => p -> Pred
toPred Bool
True

instance HasSimpleRep CompactAddr where
  type SimpleRep CompactAddr = SimpleRep Addr
  toSimpleRep :: CompactAddr -> SimpleRep CompactAddr
toSimpleRep = Addr -> SimpleRep Addr
Addr
-> Sum
     (Prod Network (Prod (Credential 'Payment) StakeReference))
     BootstrapAddress
forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep (Addr
 -> Sum
      (Prod Network (Prod (Credential 'Payment) StakeReference))
      BootstrapAddress)
-> (CompactAddr -> Addr)
-> CompactAddr
-> Sum
     (Prod Network (Prod (Credential 'Payment) StakeReference))
     BootstrapAddress
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => CompactAddr -> Addr
CompactAddr -> Addr
decompactAddr
  fromSimpleRep :: SimpleRep CompactAddr -> CompactAddr
fromSimpleRep = Addr -> CompactAddr
compactAddr (Addr -> CompactAddr)
-> (Sum
      (Prod Network (Prod (Credential 'Payment) StakeReference))
      BootstrapAddress
    -> Addr)
-> Sum
     (Prod Network (Prod (Credential 'Payment) StakeReference))
     BootstrapAddress
-> CompactAddr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleRep Addr -> Addr
Sum
  (Prod Network (Prod (Credential 'Payment) StakeReference))
  BootstrapAddress
-> Addr
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) SOP (TheSop BootstrapAddress)
SimpleRep BootstrapAddress
rep ((AbstractHash Blake2b_224 Address'
  -> NetworkMagic -> AddrType -> BootstrapAddress)
 -> BootstrapAddress)
-> (AbstractHash Blake2b_224 Address'
    -> NetworkMagic -> AddrType -> BootstrapAddress)
-> BootstrapAddress
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 (AddrAttributes -> UnparsedFields -> Attributes AddrAttributes
forall h. h -> UnparsedFields -> Attributes h
Attributes (Maybe HDAddressPayload -> NetworkMagic -> AddrAttributes
AddrAttributes Maybe HDAddressPayload
forall a. Maybe a
Nothing NetworkMagic
magic) (Map Word8 ByteString -> UnparsedFields
UnparsedFields Map Word8 ByteString
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)
_ = Specification (AbstractHash Blake2b_224 b)
forall deps a. SpecificationD deps 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 <- Gen [Word8] -> GenT m [Word8]
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen (Gen [Word8] -> GenT m [Word8]) -> Gen [Word8] -> GenT m [Word8]
forall a b. (a -> b) -> a -> b
$ Int -> Gen Word8 -> Gen [Word8]
forall a. Int -> Gen a -> Gen [a]
vectorOf Int
28 Gen Word8
forall a. Arbitrary a => Gen a
arbitrary
    AbstractHash Blake2b_224 b -> GenT m (AbstractHash Blake2b_224 b)
forall a. a -> GenT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AbstractHash Blake2b_224 b -> GenT m (AbstractHash Blake2b_224 b))
-> AbstractHash Blake2b_224 b
-> GenT m (AbstractHash Blake2b_224 b)
forall a b. (a -> b) -> a -> b
$ Maybe (AbstractHash Blake2b_224 b) -> AbstractHash Blake2b_224 b
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe (AbstractHash Blake2b_224 b) -> AbstractHash Blake2b_224 b)
-> Maybe (AbstractHash Blake2b_224 b) -> AbstractHash Blake2b_224 b
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe (AbstractHash Blake2b_224 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)
_ = Specification Integer
forall deps a. SpecificationD deps 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)
_ = Bool -> Pred
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
CertIx -> SimpleRep CertIx
unCertIx
  fromSimpleRep :: SimpleRep CertIx -> CertIx
fromSimpleRep = Word16 -> CertIx
SimpleRep CertIx -> 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)),
 r ~ FunTy (MapList Term (ConstrOf c (TheSop a))) (Term a),
 ResultType r ~ Term a, SOPTerm c (TheSop a),
 ConstrTerm (ConstrOf c (TheSop a)), GenericRequires 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)),
 r ~ FunTy (MapList Term (ConstrOf c (TheSop a))) (Term a),
 ResultType r ~ Term a, SOPTerm c (TheSop a),
 ConstrTerm (ConstrOf c (TheSop a)), GenericRequires 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)
  Int -> Gen a -> Gen a
forall n a. Integral n => n -> Gen a -> Gen a
variant Int
seed Gen a
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 =
  [Gen (Hash h b)] -> Gen (Hash h b)
forall a. HasCallStack => [Gen a] -> Gen a
oneof
    [ Int -> Gen (Hash h b)
forall a. Arbitrary a => Int -> Gen a
pickFromFixedPool Int
20
    , Gen (Hash h b)
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)
_ = Specification (VRFVerKeyHash r)
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (VRFVerKeyHash r) -> GenT m (VRFVerKeyHash r)
genFromTypeSpec TypeSpec (VRFVerKeyHash r)
_ = Gen (VRFVerKeyHash r) -> GenT m (VRFVerKeyHash r)
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen (Gen (VRFVerKeyHash r) -> GenT m (VRFVerKeyHash r))
-> Gen (VRFVerKeyHash r) -> GenT m (VRFVerKeyHash r)
forall a b. (a -> b) -> a -> b
$ Hash HASH KeyRoleVRF -> VRFVerKeyHash r
forall (r :: KeyRoleVRF). Hash HASH KeyRoleVRF -> VRFVerKeyHash r
VRFVerKeyHash (Hash HASH KeyRoleVRF -> VRFVerKeyHash r)
-> Gen (Hash HASH KeyRoleVRF) -> Gen (VRFVerKeyHash r)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Hash HASH KeyRoleVRF)
forall h b. HashAlgorithm h => Gen (Hash h b)
genHashWithDuplicates
  cardinalTypeSpec :: TypeSpec (VRFVerKeyHash r) -> Specification Integer
cardinalTypeSpec TypeSpec (VRFVerKeyHash r)
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec (VRFVerKeyHash r) -> VRFVerKeyHash r -> [VRFVerKeyHash r]
shrinkWithTypeSpec TypeSpec (VRFVerKeyHash r)
_ = VRFVerKeyHash r -> [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)
_ = Bool -> Pred
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)
_ = Specification (Hash a b)
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (Hash a b) -> GenT m (Hash a b)
genFromTypeSpec TypeSpec (Hash a b)
_ = Gen (Hash a b) -> GenT m (Hash a b)
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen (Hash a b)
forall h b. HashAlgorithm h => Gen (Hash h b)
genHashWithDuplicates
  cardinalTypeSpec :: TypeSpec (Hash a b) -> Specification Integer
cardinalTypeSpec TypeSpec (Hash a b)
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec (Hash a b) -> Hash a b -> [Hash a b]
shrinkWithTypeSpec TypeSpec (Hash a b)
_ = Hash a b -> [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)
_ = Bool -> Pred
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
_ = Specification StakePoolRelay
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec StakePoolRelay -> GenT m StakePoolRelay
genFromTypeSpec TypeSpec StakePoolRelay
_ = Gen StakePoolRelay -> GenT m StakePoolRelay
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen StakePoolRelay
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec StakePoolRelay -> Specification Integer
cardinalTypeSpec TypeSpec StakePoolRelay
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec StakePoolRelay -> StakePoolRelay -> [StakePoolRelay]
shrinkWithTypeSpec TypeSpec StakePoolRelay
_ = StakePoolRelay -> [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
_ = Bool -> Pred
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
_ = Specification Url
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Url -> GenT m Url
genFromTypeSpec TypeSpec Url
_ = Gen Url -> GenT m Url
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen Url
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec Url -> Specification Integer
cardinalTypeSpec TypeSpec Url
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec Url -> Url -> [Url]
shrinkWithTypeSpec TypeSpec Url
_ = Url -> [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
_ = Bool -> Pred
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
_ = Specification Text
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Text -> GenT m Text
genFromTypeSpec TypeSpec Text
_ = Gen Text -> GenT m Text
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen Text
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec Text -> Specification Integer
cardinalTypeSpec TypeSpec Text
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec Text -> Text -> [Text]
shrinkWithTypeSpec TypeSpec Text
_ = Text -> [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
_ = Bool -> Pred
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 Specification Int -> Specification Int -> Specification Int
forall a. Semigroup a => a -> a -> a
<> Specification Int
len')

instance Monoid StringSpec where
  mempty :: StringSpec
mempty = Specification Int -> StringSpec
StringSpec Specification Int
forall deps a. SpecificationD deps a
TrueSpec

instance HasSpec ByteString where
  type TypeSpec ByteString = StringSpec
  emptySpec :: TypeSpec ByteString
emptySpec = TypeSpec ByteString
StringSpec
forall a. Monoid a => a
mempty
  combineSpec :: TypeSpec ByteString
-> TypeSpec ByteString -> Specification ByteString
combineSpec TypeSpec ByteString
s TypeSpec ByteString
s' = TypeSpec ByteString -> Specification ByteString
forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec (TypeSpec ByteString -> Specification ByteString)
-> TypeSpec ByteString -> Specification ByteString
forall a b. (a -> b) -> a -> b
$ TypeSpec ByteString
StringSpec
s StringSpec -> StringSpec -> StringSpec
forall a. Semigroup a => a -> a -> a
<> TypeSpec ByteString
StringSpec
s'
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec ByteString -> GenT m ByteString
genFromTypeSpec (StringSpec Specification Int
ls) = do
    Int
len <- Specification Int -> GenT m Int
forall a (m :: * -> *).
(HasCallStack, HasSpec a, MonadGenError m) =>
Specification a -> GenT m a
genFromSpecT Specification Int
ls
    [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> GenT m [Word8] -> GenT m ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> GenT GE Word8 -> GenT m [Word8]
forall (m :: * -> *) a.
MonadGenError m =>
Int -> GenT GE a -> GenT m [a]
vectorOfT Int
len (Gen Word8 -> GenT GE Word8
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen Word8
forall a. Arbitrary a => Gen a
arbitrary)
  shrinkWithTypeSpec :: TypeSpec ByteString -> ByteString -> [ByteString]
shrinkWithTypeSpec TypeSpec ByteString
_ = ByteString -> [ByteString]
forall a. Arbitrary a => a -> [a]
shrink
  cardinalTypeSpec :: TypeSpec ByteString -> Specification Integer
cardinalTypeSpec TypeSpec ByteString
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  conformsTo :: HasCallStack => ByteString -> TypeSpec ByteString -> Bool
conformsTo ByteString
bs (StringSpec Specification Int
ls) = ByteString -> Int
BS.length ByteString
bs Int -> Specification Int -> Bool
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) = Term Int -> Specification Int -> Pred
forall a. HasSpec a => Term a -> Specification a -> Pred
satisfies (Term ByteString -> Term Int
forall s. (HasSpec s, StringLike s) => Term s -> Term Int
strLen_ Term ByteString
str) Specification Int
len

instance HasSpec ShortByteString where
  type TypeSpec ShortByteString = StringSpec
  emptySpec :: TypeSpec ShortByteString
emptySpec = TypeSpec ShortByteString
StringSpec
forall a. Monoid a => a
mempty
  combineSpec :: TypeSpec ShortByteString
-> TypeSpec ShortByteString -> Specification ShortByteString
combineSpec TypeSpec ShortByteString
s TypeSpec ShortByteString
s' = TypeSpec ShortByteString -> Specification ShortByteString
forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec (TypeSpec ShortByteString -> Specification ShortByteString)
-> TypeSpec ShortByteString -> Specification ShortByteString
forall a b. (a -> b) -> a -> b
$ TypeSpec ShortByteString
StringSpec
s StringSpec -> StringSpec -> StringSpec
forall a. Semigroup a => a -> a -> a
<> TypeSpec ShortByteString
StringSpec
s'
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec ShortByteString -> GenT m ShortByteString
genFromTypeSpec (StringSpec Specification Int
ls) = do
    Int
len <- Specification Int -> GenT m Int
forall a (m :: * -> *).
(HasCallStack, HasSpec a, MonadGenError m) =>
Specification a -> GenT m a
genFromSpecT Specification Int
ls
    [Word8] -> ShortByteString
SBS.pack ([Word8] -> ShortByteString)
-> GenT m [Word8] -> GenT m ShortByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> GenT GE Word8 -> GenT m [Word8]
forall (m :: * -> *) a.
MonadGenError m =>
Int -> GenT GE a -> GenT m [a]
vectorOfT Int
len (Gen Word8 -> GenT GE Word8
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen Word8
forall a. Arbitrary a => Gen a
arbitrary)
  shrinkWithTypeSpec :: TypeSpec ShortByteString -> ShortByteString -> [ShortByteString]
shrinkWithTypeSpec TypeSpec ShortByteString
_ = ShortByteString -> [ShortByteString]
forall a. Arbitrary a => a -> [a]
shrink
  cardinalTypeSpec :: TypeSpec ShortByteString -> Specification Integer
cardinalTypeSpec TypeSpec ShortByteString
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  conformsTo :: HasCallStack => ShortByteString -> TypeSpec ShortByteString -> Bool
conformsTo ShortByteString
bs (StringSpec Specification Int
ls) = ShortByteString -> Int
SBS.length ShortByteString
bs Int -> Specification Int -> Bool
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) = Term Int -> Specification Int -> Pred
forall a. HasSpec a => Term a -> Specification a -> Pred
satisfies (Term ShortByteString -> Term Int
forall s. (HasSpec s, StringLike s) => Term s -> Term Int
strLen_ Term ShortByteString
str) Specification Int
len

instance StringLike ByteString where
  lengthSpec :: Specification Int -> TypeSpec ByteString
lengthSpec = Specification Int -> TypeSpec ByteString
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 -> TypeSpec ShortByteString
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 :: [Type] -> Type -> Type where
  StrLenW :: StringLike s => StringW '[s] Int

deriving instance Show (StringW as b)

deriving instance Eq (StringW as b)

strLen_ :: (HasSpec s, StringLike s) => Term s -> Term Int
strLen_ :: forall s. (HasSpec s, StringLike s) => Term s -> Term Int
strLen_ = StringW '[s] Int -> FunTy (MapList Term '[s]) (Term Int)
forall (t :: [*] -> * -> *) (ds :: [*]) r.
AppRequires t ds r =>
t ds r -> FunTy (MapList Term ds) (Term r)
appTerm StringW '[s] Int
forall a. StringLike a => StringW '[a] Int
StrLenW

instance Syntax StringW

instance Semantics StringW where
  semantics :: forall (d :: [*]) r. StringW d r -> FunTy d r
semantics StringW d r
StrLenW = FunTy d r
s -> Int
forall s. StringLike s => s -> Int
getLength

-- | In this instance there is no way to bring the type variable `s` into scope
--   so we introduce some local functions that have a signature that bring it into scope.
instance Logic StringW where
  propagateTypeSpec :: forall (as :: [*]) b a.
(AppRequires StringW as b, HasSpec a) =>
StringW as b
-> ListCtx Value as (HOLE a)
-> TypeSpec b
-> [b]
-> Specification a
propagateTypeSpec StringW as b
StrLenW (Unary HOLE a s
HOLE) TypeSpec b
ts [b]
cant = NumSpec Int -> [Int] -> Specification a
forall s.
(HasSpec s, StringLike s) =>
NumSpec Int -> [Int] -> Specification s
foo TypeSpec b
NumSpec Int
ts [b]
[Int]
cant
    where
      foo :: forall s. (HasSpec s, StringLike s) => NumSpec Int -> [Int] -> Specification s
      foo :: forall s.
(HasSpec s, StringLike s) =>
NumSpec Int -> [Int] -> Specification s
foo NumSpec Int
t [Int]
c = TypeSpec s -> Specification s
forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec (TypeSpec s -> Specification s) -> TypeSpec s -> Specification s
forall a b. (a -> b) -> a -> b
$ forall s. StringLike s => Specification Int -> TypeSpec s
lengthSpec @s (TypeSpec Int -> [Int] -> Specification Int
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec TypeSpec Int
NumSpec Int
t [Int]
c)
  propagateMemberSpec :: forall (as :: [*]) b a.
(AppRequires StringW as b, HasSpec a) =>
StringW as b
-> ListCtx Value as (HOLE a) -> NonEmpty b -> Specification a
propagateMemberSpec StringW as b
StrLenW (Unary HOLE a s
HOLE) NonEmpty b
xs = NonEmpty Int -> Specification a
forall s.
(HasSpec s, StringLike s) =>
NonEmpty Int -> Specification s
bar NonEmpty b
NonEmpty Int
xs
    where
      bar :: forall s. (HasSpec s, StringLike s) => NonEmpty Int -> Specification s
      bar :: forall s.
(HasSpec s, StringLike s) =>
NonEmpty Int -> Specification s
bar NonEmpty Int
ys = TypeSpec s -> Specification s
forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec (TypeSpec s -> Specification s) -> TypeSpec s -> Specification s
forall a b. (a -> b) -> a -> b
$ forall s. StringLike s => Specification Int -> TypeSpec s
lengthSpec @s (NonEmpty Int -> Specification Int
forall a deps. NonEmpty a -> SpecificationD deps a
MemberSpec NonEmpty Int
ys)

  mapTypeSpec :: forall a b. (HasSpec a, HasSpec b) => StringW '[a] b -> TypeSpec a -> Specification b
  mapTypeSpec :: forall a b.
(HasSpec a, HasSpec b) =>
StringW '[a] b -> TypeSpec a -> Specification b
mapTypeSpec StringW '[a] b
StrLenW TypeSpec a
ss = forall s. StringLike s => TypeSpec s -> Specification Int
getLengthSpec @a 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 =
    MapSpec PolicyID (Map AssetName Integer)
forall k v. Ord k => MapSpec k v
defaultMapSpec
      { mapSpecElem = constrained' $ \TermD Deps PolicyID
_ Term (Map AssetName Integer)
innerMap ->
          Term (Map AssetName Integer)
-> (Term (AssetName, Integer) -> Term Bool) -> Pred
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 ((Term (AssetName, Integer) -> Term Bool) -> Pred)
-> (Term (AssetName, Integer) -> Term Bool) -> Pred
forall a b. (a -> b) -> a -> b
$ \Term (AssetName, Integer)
kv' ->
            Integer -> Term Integer
forall a. HasSpec a => a -> Term a
lit Integer
0 Term Integer -> Term Integer -> Term Bool
forall a. OrdLike a => Term a -> Term a -> Term Bool
<=. Term (AssetName, Integer) -> Term Integer
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
SimpleRep AssetName
sbs
  fromSimpleRep :: SimpleRep AssetName -> AssetName
fromSimpleRep SimpleRep AssetName
sbs = ShortByteString -> AssetName
AssetName ShortByteString
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
  -- TODO: consider `SimpleRep Coin` instead if this is annoying
  type SimpleRep CoinPerByte = Coin
  fromSimpleRep :: SimpleRep CoinPerByte -> CoinPerByte
fromSimpleRep = Coin -> CoinPerByte
SimpleRep CoinPerByte -> CoinPerByte
CoinPerByte
  toSimpleRep :: CoinPerByte -> SimpleRep CoinPerByte
toSimpleRep = CoinPerByte -> Coin
CoinPerByte -> SimpleRep CoinPerByte
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
_ = Specification Char
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec Char -> GenT m Char
genFromTypeSpec TypeSpec Char
_ = Gen Char -> GenT m Char
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen Char
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec Char -> Specification Integer
cardinalTypeSpec TypeSpec Char
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec Char -> Char -> [Char]
shrinkWithTypeSpec TypeSpec Char
_ = Char -> [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
_ = Bool -> Pred
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
_ = Specification CostModel
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec CostModel -> GenT m CostModel
genFromTypeSpec TypeSpec CostModel
_ = Gen CostModel -> GenT m CostModel
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen CostModel
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec CostModel -> Specification Integer
cardinalTypeSpec TypeSpec CostModel
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec CostModel -> CostModel -> [CostModel]
shrinkWithTypeSpec TypeSpec CostModel
_ = CostModel -> [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
_ = Bool -> Pred
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 = StrictMaybe a -> THKD tag StrictMaybe a
HKD StrictMaybe a -> THKD tag StrictMaybe a
forall (t :: PPGroups) (f :: * -> *) a. HKD f a -> THKD t f a
THKD (StrictMaybe a -> THKD tag StrictMaybe a)
-> (Sum () a -> StrictMaybe a)
-> Sum () a
-> THKD tag StrictMaybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimpleRep (StrictMaybe a) -> StrictMaybe a
Sum () a -> StrictMaybe a
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep
  toSimpleRep :: THKD tag StrictMaybe a -> SimpleRep (THKD tag StrictMaybe a)
toSimpleRep (THKD HKD StrictMaybe a
sm) = StrictMaybe a -> SimpleRep (StrictMaybe a)
forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep StrictMaybe a
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 = HKD Identity a -> THKD tag Identity a
SimpleRep (THKD tag Identity a) -> THKD tag Identity a
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
SimpleRep (THKD tag Identity a)
a

instance
  ( IsNormalType a
  , Typeable tag
  , HasSpec a
  , GenericallyInstantiated (THKD tag Identity a)
  ) =>
  HasSpec (THKD tag Identity a)

instance HasSimpleRep GovActionPurpose

instance HasSpec GovActionPurpose

instance HasSimpleRep Voter

instance HasSpec Voter

-- TODO: this might be a problem considering duplicates in the list! This
-- type might require having its own `HasSpec` at some point
instance (Typeable a, Ord a) => HasSimpleRep (SOS.OSet a) where
  type SimpleRep (SOS.OSet a) = [a]
  fromSimpleRep :: SimpleRep (OSet a) -> OSet a
fromSimpleRep = StrictSeq a -> OSet a
forall a. Ord a => StrictSeq a -> OSet a
SOS.fromStrictSeq (StrictSeq a -> OSet a) -> ([a] -> StrictSeq a) -> [a] -> OSet a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> StrictSeq a
forall a. [a] -> StrictSeq a
StrictSeq.fromList
  toSimpleRep :: OSet a -> SimpleRep (OSet a)
toSimpleRep = StrictSeq a -> [a]
forall a. StrictSeq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList (StrictSeq a -> [a]) -> (OSet a -> StrictSeq a) -> OSet a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OSet a -> StrictSeq a
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, GenericRequires 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, GenericRequires 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] SOP '["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]]
      (CompactForm Coin -> SimpleRep (CompactForm Coin)
forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep CompactForm Coin
rew)
      (CompactForm Coin -> SimpleRep (CompactForm Coin)
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]]
      SOP '["RDPair" ::: '[SimpleRep Coin, SimpleRep Coin]]
SimpleRep RDPair
rep
      ( \Word64
rew Word64
dep ->
          CompactForm Coin -> CompactForm Coin -> RDPair
RDPair
            (SimpleRep (CompactForm Coin) -> CompactForm Coin
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep Word64
SimpleRep (CompactForm Coin)
rew)
            (SimpleRep (CompactForm Coin) -> CompactForm Coin
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep Word64
SimpleRep (CompactForm Coin)
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, GenericRequires 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, GenericRequires 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, GenericRequires 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, GenericRequires a) =>
Term a -> Term (At n as)
sel @4

-- =====================================================================
-- Proposals from Cardano.Ledger.Conway.Governance.Proposals
-- =====================================================================
-- The correct way to think of Proposals (definition for reference below)
--
-- data Proposals era = Proposals
--  { pProps :: !(OMap.OMap (GovActionId ) (GovActionState era))
--  , pRoots :: !(GovRelation PRoot era)
--  , pGraph :: !(GovRelation PGraph era)
--  }
--  is four copies of the following abstract type: ProposalType
--  one for each @`GovActionPurpose`@ (PParamUpdate,HardFork,Committee,Constitution)
--  See the extensive notes in Cardano.Ledger.Conway.Governance.Proposals
--
--  data ProposalTree a = Node (StrictMaybe a) [ProposalTree a]
--
--  In Haskell this abstration of Proposals would look something like
--
--  data ProposalsType = ProposalsType ProposalTree ProposalTree ProposalTree ProposalTree  [GAS]
--
--  Thus the SimpleRep for Proposals is a Sum type with 5 different cases, thus we need to provde
--  toSimpleRep and fromSimpleRep methods to make the HasSimpleRep instance.

type GAS era = GovActionState era

type ProposalTree era = (StrictMaybe GovActionId, [Tree (GAS era)])

type ProposalsType era =
  '[ ProposalTree era -- PParamUpdate
   , ProposalTree era -- HardFork
   , ProposalTree era -- Committee
   , ProposalTree era -- Constitution
   , [GAS era] -- Everything else (TreasuryWithdrawals, Info) which can't be grouped into one of the 4 purposes.
   -- TODO - in order to improve the distribution of orders in the OMap
   -- one could try doing something like this as well to materialize the order:
   -- , TotalOrder (GovActionId )
   -- However, (1) I have no clue how this would work in detail and (2) the approach
   -- of DFS gives us a lot of testing already, and there are bigger fish to fry than
   -- this right now.
   ]

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 (TreeMaybe GovActionId
 -> (StrictMaybe GovActionId, [Tree (GAS era)]))
-> TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
forall a b. (a -> b) -> a -> b
$ TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate)
      (TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
buildProposalTree (TreeMaybe GovActionId
 -> (StrictMaybe GovActionId, [Tree (GAS era)]))
-> TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
forall a b. (a -> b) -> a -> b
$ TreeMaybe (GovPurposeId 'HardForkPurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'HardForkPurpose era)
grHardFork)
      (TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
buildProposalTree (TreeMaybe GovActionId
 -> (StrictMaybe GovActionId, [Tree (GAS era)]))
-> TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
forall a b. (a -> b) -> a -> b
$ TreeMaybe (GovPurposeId 'CommitteePurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'CommitteePurpose era)
grCommittee)
      (TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
buildProposalTree (TreeMaybe GovActionId
 -> (StrictMaybe GovActionId, [Tree (GAS era)]))
-> TreeMaybe GovActionId
-> (StrictMaybe GovActionId, [Tree (GAS era)])
forall a b. (a -> b) -> a -> b
$ TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
grConstitution)
      (Map GovActionId (GAS era) -> [GAS era]
forall k a. Map k a -> [a]
Map.elems (Map GovActionId (GAS era) -> [GAS era])
-> Map GovActionId (GAS era) -> [GAS era]
forall a b. (a -> b) -> a -> b
$ Map GovActionId (GAS era)
-> Set GovActionId -> Map GovActionId (GAS era)
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)
grPParamUpdate :: TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
grHardFork :: TreeMaybe (GovPurposeId 'HardForkPurpose era)
grCommittee :: TreeMaybe (GovPurposeId 'CommitteePurpose era)
grConstitution :: TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
grPParamUpdate :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grHardFork :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grCommittee :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grConstitution :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
..} = Proposals era -> GovRelation TreeMaybe era
forall era.
(Era era, HasCallStack) =>
Proposals era -> GovRelation TreeMaybe era
toGovRelationTree Proposals era
props
      idMap :: Map GovActionId (GAS era)
idMap = Proposals era -> Map GovActionId (GAS era)
forall era. Proposals era -> Map GovActionId (GovActionState era)
proposalsActionsMap Proposals era
props

      treeKeys :: Set GovActionId
treeKeys =
        (TreeMaybe GovActionId -> Set GovActionId)
-> [TreeMaybe GovActionId] -> Set GovActionId
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap
          TreeMaybe GovActionId -> Set GovActionId
keys
          [ TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate
          , TreeMaybe (GovPurposeId 'HardForkPurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'HardForkPurpose era)
grHardFork
          , TreeMaybe (GovPurposeId 'CommitteePurpose era)
-> TreeMaybe GovActionId
forall a b. Coercible a b => a -> b
coerce TreeMaybe (GovPurposeId 'CommitteePurpose era)
grCommittee
          , TreeMaybe (GovPurposeId 'ConstitutionPurpose era)
-> TreeMaybe GovActionId
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, (Tree (StrictMaybe GovActionId) -> Tree (GAS era))
-> [Tree (StrictMaybe GovActionId)] -> [Tree (GAS era)]
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 <- GovActionId -> Map GovActionId (GAS era) -> Maybe (GAS era)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup GovActionId
gid Map GovActionId (GAS era)
idMap = GAS era -> [Tree (GAS era)] -> Tree (GAS era)
forall a. a -> [Tree a] -> Tree a
Node GAS era
gas ((Tree (StrictMaybe GovActionId) -> Tree (GAS era))
-> [Tree (StrictMaybe GovActionId)] -> [Tree (GAS era)]
forall a b. (a -> b) -> [a] -> [b]
map Tree (StrictMaybe GovActionId) -> Tree (GAS era)
buildTree [Tree (StrictMaybe GovActionId)]
cs)
      buildTree Tree (StrictMaybe GovActionId)
_ =
        [Char] -> Tree (GAS era)
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) = (StrictMaybe GovActionId -> Set GovActionId)
-> Tree (StrictMaybe GovActionId) -> Set GovActionId
forall m a. Monoid m => (a -> m) -> Tree a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Set GovActionId
-> (GovActionId -> Set GovActionId)
-> StrictMaybe GovActionId
-> Set GovActionId
forall a b. a -> (b -> a) -> StrictMaybe b -> a
strictMaybe Set GovActionId
forall a. Monoid a => a
mempty GovActionId -> Set GovActionId
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]
      SOP '["Proposals" ::: ProposalsType era]
SimpleRep (Proposals era)
rep
      (((StrictMaybe GovActionId, [Tree (GAS era)])
  -> (StrictMaybe GovActionId, [Tree (GAS era)])
  -> (StrictMaybe GovActionId, [Tree (GAS era)])
  -> (StrictMaybe GovActionId, [Tree (GAS era)])
  -> [GAS era]
  -> Proposals era)
 -> Proposals era)
-> ((StrictMaybe GovActionId, [Tree (GAS era)])
    -> (StrictMaybe GovActionId, [Tree (GAS era)])
    -> (StrictMaybe GovActionId, [Tree (GAS era)])
    -> (StrictMaybe GovActionId, [Tree (GAS era)])
    -> [GAS era]
    -> Proposals era)
-> Proposals era
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 = StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> GovRelation StrictMaybe era
forall (f :: * -> *) era.
f (GovPurposeId 'PParamUpdatePurpose era)
-> f (GovPurposeId 'HardForkPurpose era)
-> f (GovPurposeId 'CommitteePurpose era)
-> f (GovPurposeId 'ConstitutionPurpose era)
-> GovRelation f era
GovRelation (StrictMaybe GovActionId
-> StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rPPUp) (StrictMaybe GovActionId
-> StrictMaybe (GovPurposeId 'HardForkPurpose era)
forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rHF) (StrictMaybe GovActionId
-> StrictMaybe (GovPurposeId 'CommitteePurpose era)
forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rCom) (StrictMaybe GovActionId
-> StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
forall a b. Coercible a b => a -> b
coerce StrictMaybe GovActionId
rCon)
            -- TODO: note, this doesn't roundtrip and the distribution is a bit iffy. See the TODO
            -- above for ideas on how to deal with this.
            oMap :: OMap GovActionId (GAS era)
oMap = ([Tree (GAS era)] -> OMap GovActionId (GAS era))
-> [[Tree (GAS era)]] -> OMap GovActionId (GAS era)
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Tree (GAS era) -> OMap GovActionId (GAS era))
-> [Tree (GAS era)] -> OMap GovActionId (GAS era)
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Tree (GAS era) -> OMap GovActionId (GAS era)
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] OMap GovActionId (GAS era)
-> OMap GovActionId (GAS era) -> OMap GovActionId (GAS era)
forall a. Semigroup a => a -> a -> a
<> [GAS era] -> OMap GovActionId (GAS era)
forall (f :: * -> *) k v.
(Foldable f, HasOKey k v) =>
f v -> OMap k v
OMap.fromFoldable [GAS era]
others
         in GovRelation StrictMaybe era
-> OMap GovActionId (GAS era) -> Proposals era
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 v -> OMap k v -> OMap k v
forall k v. HasOKey k v => v -> OMap k v -> OMap k v
OMap.<| (Tree v -> OMap k v) -> [Tree v] -> OMap k v
forall m a. Monoid m => (a -> m) -> [a] -> m
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 = Proposals era -> [Proposals era]
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, GenericRequires 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 -> [Char] -> [Char]
[ProposalsSplit] -> [Char] -> [Char]
ProposalsSplit -> [Char]
(Int -> ProposalsSplit -> [Char] -> [Char])
-> (ProposalsSplit -> [Char])
-> ([ProposalsSplit] -> [Char] -> [Char])
-> Show ProposalsSplit
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: Int -> ProposalsSplit -> [Char] -> [Char]
showsPrec :: Int -> ProposalsSplit -> [Char] -> [Char]
$cshow :: ProposalsSplit -> [Char]
show :: ProposalsSplit -> [Char]
$cshowList :: [ProposalsSplit] -> [Char] -> [Char]
showList :: [ProposalsSplit] -> [Char] -> [Char]
Show, ProposalsSplit -> ProposalsSplit -> Bool
(ProposalsSplit -> ProposalsSplit -> Bool)
-> (ProposalsSplit -> ProposalsSplit -> Bool) -> Eq ProposalsSplit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProposalsSplit -> ProposalsSplit -> Bool
== :: ProposalsSplit -> ProposalsSplit -> Bool
$c/= :: ProposalsSplit -> ProposalsSplit -> Bool
/= :: ProposalsSplit -> ProposalsSplit -> Bool
Eq, (forall x. ProposalsSplit -> Rep ProposalsSplit x)
-> (forall x. Rep ProposalsSplit x -> ProposalsSplit)
-> Generic ProposalsSplit
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
$cfrom :: forall x. ProposalsSplit -> Rep ProposalsSplit x
from :: forall x. ProposalsSplit -> Rep ProposalsSplit x
$cto :: forall x. Rep ProposalsSplit x -> ProposalsSplit
to :: forall x. Rep ProposalsSplit x -> ProposalsSplit
Generic)

instance EncCBOR ProposalsSplit where
  encCBOR :: ProposalsSplit -> Encoding
encCBOR x :: ProposalsSplit
x@(ProposalsSplit Integer
_ Integer
_ Integer
_ Integer
_ Integer
_) =
    let ProposalsSplit {Integer
psPPChange :: ProposalsSplit -> Integer
psHFInitiation :: ProposalsSplit -> Integer
psUpdateCommittee :: ProposalsSplit -> Integer
psNewConstitution :: ProposalsSplit -> Integer
psOthers :: ProposalsSplit -> Integer
psPPChange :: Integer
psHFInitiation :: Integer
psUpdateCommittee :: Integer
psNewConstitution :: Integer
psOthers :: Integer
..} = ProposalsSplit
x
     in Encode ('Closed 'Dense) ProposalsSplit -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode ('Closed 'Dense) ProposalsSplit -> Encoding)
-> Encode ('Closed 'Dense) ProposalsSplit -> Encoding
forall a b. (a -> b) -> a -> b
$
          (Integer
 -> Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
-> Encode
     ('Closed 'Dense)
     (Integer
      -> Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
forall t. t -> Encode ('Closed 'Dense) t
Rec Integer
-> Integer -> Integer -> Integer -> Integer -> ProposalsSplit
ProposalsSplit
            Encode
  ('Closed 'Dense)
  (Integer
   -> Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
-> Encode ('Closed 'Dense) Integer
-> Encode
     ('Closed 'Dense)
     (Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psPPChange
            Encode
  ('Closed 'Dense)
  (Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
-> Encode ('Closed 'Dense) Integer
-> Encode
     ('Closed 'Dense) (Integer -> Integer -> Integer -> ProposalsSplit)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psHFInitiation
            Encode
  ('Closed 'Dense) (Integer -> Integer -> Integer -> ProposalsSplit)
-> Encode ('Closed 'Dense) Integer
-> Encode ('Closed 'Dense) (Integer -> Integer -> ProposalsSplit)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psUpdateCommittee
            Encode ('Closed 'Dense) (Integer -> Integer -> ProposalsSplit)
-> Encode ('Closed 'Dense) Integer
-> Encode ('Closed 'Dense) (Integer -> ProposalsSplit)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psNewConstitution
            Encode ('Closed 'Dense) (Integer -> ProposalsSplit)
-> Encode ('Closed 'Dense) Integer
-> Encode ('Closed 'Dense) ProposalsSplit
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Integer -> Encode ('Closed 'Dense) Integer
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Integer
psOthers

instance DecCBOR ProposalsSplit where
  decCBOR :: forall s. Decoder s ProposalsSplit
decCBOR =
    Decode ('Closed 'Dense) ProposalsSplit -> Decoder s ProposalsSplit
forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t
decode (Decode ('Closed 'Dense) ProposalsSplit
 -> Decoder s ProposalsSplit)
-> Decode ('Closed 'Dense) ProposalsSplit
-> Decoder s ProposalsSplit
forall a b. (a -> b) -> a -> b
$
      (Integer
 -> Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
-> Decode
     ('Closed 'Dense)
     (Integer
      -> Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
forall t. t -> Decode ('Closed 'Dense) t
RecD Integer
-> Integer -> Integer -> Integer -> Integer -> ProposalsSplit
ProposalsSplit
        Decode
  ('Closed 'Dense)
  (Integer
   -> Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
-> Decode ('Closed Any) Integer
-> Decode
     ('Closed 'Dense)
     (Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
        Decode
  ('Closed 'Dense)
  (Integer -> Integer -> Integer -> Integer -> ProposalsSplit)
-> Decode ('Closed Any) Integer
-> Decode
     ('Closed 'Dense) (Integer -> Integer -> Integer -> ProposalsSplit)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
        Decode
  ('Closed 'Dense) (Integer -> Integer -> Integer -> ProposalsSplit)
-> Decode ('Closed Any) Integer
-> Decode ('Closed 'Dense) (Integer -> Integer -> ProposalsSplit)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
        Decode ('Closed 'Dense) (Integer -> Integer -> ProposalsSplit)
-> Decode ('Closed Any) Integer
-> Decode ('Closed 'Dense) (Integer -> ProposalsSplit)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
        Decode ('Closed 'Dense) (Integer -> ProposalsSplit)
-> Decode ('Closed Any) Integer
-> Decode ('Closed 'Dense) ProposalsSplit
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Integer
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
psPPChange :: ProposalsSplit -> Integer
psHFInitiation :: ProposalsSplit -> Integer
psUpdateCommittee :: ProposalsSplit -> Integer
psNewConstitution :: ProposalsSplit -> Integer
psOthers :: ProposalsSplit -> Integer
psPPChange :: Integer
psHFInitiation :: Integer
psUpdateCommittee :: Integer
psNewConstitution :: Integer
psOthers :: Integer
..} =
  [Integer] -> Integer
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
    [ Integer
psPPChange
    , Integer
psHFInitiation
    , Integer
psUpdateCommittee
    , Integer
psNewConstitution
    , Integer
psOthers
    ]

-- | Randomly splits a number into the given number of terms. Might undershoot
-- due to rounding
splitInto :: Integer -> Int -> Gen [Integer]
splitInto :: Integer -> Int -> Gen [Integer]
splitInto Integer
budget Int
numSplits = do
  [NonNegative Int]
splits <- Int -> Gen (NonNegative Int) -> Gen [NonNegative Int]
forall a. Int -> Gen a -> Gen [a]
vectorOf Int
numSplits (Gen (NonNegative Int) -> Gen [NonNegative Int])
-> Gen (NonNegative Int) -> Gen [NonNegative Int]
forall a b. (a -> b) -> a -> b
$ forall a. Arbitrary a => Gen a
arbitrary @(NonNegative Int)
  let unwrappedSplits :: [Int]
unwrappedSplits = (NonNegative Int -> Int) -> [NonNegative Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonNegative Int -> Int
forall a. NonNegative a -> a
getNonNegative [NonNegative Int]
splits
  let splitsTotal :: Integer
splitsTotal = Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Int -> Integer
forall a b. (a -> b) -> a -> b
$ [Int] -> Int
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
unwrappedSplits
  [Integer] -> Gen [Integer]
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Integer] -> Gen [Integer]) -> [Integer] -> Gen [Integer]
forall a b. (a -> b) -> a -> b
$
    if Integer
splitsTotal Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 Bool -> Bool -> Bool
|| Integer
budget Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0
      then Int -> Integer -> [Integer]
forall a. Int -> a -> [a]
replicate Int
numSplits Integer
0
      else (Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* (Integer
budget Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
splitsTotal)) (Integer -> Integer) -> (Int -> Integer) -> Int -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> [Int] -> [Integer]
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 <- (Integer, Integer) -> Gen Integer
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
      ] -> ProposalsSplit -> Gen ProposalsSplit
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ProposalsSplit {Integer
psPPChange :: Integer
psHFInitiation :: Integer
psUpdateCommittee :: Integer
psNewConstitution :: Integer
psOthers :: Integer
psPPChange :: Integer
psHFInitiation :: Integer
psUpdateCommittee :: Integer
psNewConstitution :: Integer
psOthers :: Integer
..}
    [Integer]
l ->
      [Char] -> Gen ProposalsSplit
forall a. HasCallStack => [Char] -> a
error ([Char] -> Gen ProposalsSplit) -> [Char] -> Gen ProposalsSplit
forall a b. (a -> b) -> a -> b
$
        [Char]
"impossible: should have exactly 5 values, but has "
          [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show ([Integer] -> Int
forall a. [a] -> Int
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
psPPChange :: ProposalsSplit -> Integer
psHFInitiation :: ProposalsSplit -> Integer
psUpdateCommittee :: ProposalsSplit -> Integer
psNewConstitution :: ProposalsSplit -> Integer
psOthers :: ProposalsSplit -> Integer
psPPChange :: Integer
psHFInitiation :: Integer
psUpdateCommittee :: Integer
psNewConstitution :: Integer
psOthers :: Integer
..} = FunTy (MapList Term (Args (SimpleRep (Proposals era)))) [[Pred]]
-> Specification (Proposals era)
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, IsProductType a, IsPred p,
 GenericRequires a, ProdAsListComputes a) =>
FunTy (MapList Term (Args (SimpleRep a))) p -> Specification a
constrained' (FunTy (MapList Term (Args (SimpleRep (Proposals era)))) [[Pred]]
 -> Specification (Proposals era))
-> FunTy (MapList Term (Args (SimpleRep (Proposals era)))) [[Pred]]
-> Specification (Proposals era)
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 ->
    [ Hint [Tree (GovActionState ConwayEra)]
-> Term
     (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
-> [Pred]
forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
 HasGenHint t, HasGenHint a, Num a, Show a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
Hint [Tree (GovActionState ConwayEra)]
psPPChange Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
ppuTree
    , Hint [Tree (GovActionState ConwayEra)]
-> Term
     (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
-> [Pred]
forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
 HasGenHint t, HasGenHint a, Num a, Show a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
Hint [Tree (GovActionState ConwayEra)]
psHFInitiation Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
hfTree
    , Hint [Tree (GovActionState ConwayEra)]
-> Term
     (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
-> [Pred]
forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
 HasGenHint t, HasGenHint a, Num a, Show a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
Hint [Tree (GovActionState ConwayEra)]
psUpdateCommittee Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
comTree
    , Hint [Tree (GovActionState ConwayEra)]
-> Term
     (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
-> [Pred]
forall {a} {a} {t} {x}.
(Hint a ~ (Maybe a, Hint t), Forallable t a, HasSpec x,
 HasGenHint t, HasGenHint a, Num a, Show a) =>
Hint t -> Term (x, t) -> [Pred]
limitForest Integer
Hint [Tree (GovActionState ConwayEra)]
psNewConstitution Term (StrictMaybe GovActionId, [Tree (GovActionState ConwayEra)])
conTree
    , [Hint [GovActionState ConwayEra]
-> Term [GovActionState ConwayEra] -> Pred
forall t. HasGenHint t => Hint t -> Term t -> Pred
genHint Integer
Hint [GovActionState ConwayEra]
psOthers Term [GovActionState ConwayEra]
others]
    ]
    where
      limitForest :: Hint t -> Term (x, t) -> [Pred]
limitForest Hint t
limit Term (x, t)
forest =
        [ Hint t -> Term t -> Pred
forall t. HasGenHint t => Hint t -> Term t -> Pred
genHint Hint t
limit (Term (x, t) -> Term t
forall x y. (HasSpec x, HasSpec y) => Term (x, y) -> Term y
snd_ Term (x, t)
forest)
        , Term t -> (Term a -> Pred) -> Pred
forall t a p.
(Forallable t a, HasSpec t, HasSpec a, IsPred p) =>
Term t -> (Term a -> p) -> Pred
forAll (Term (x, t) -> Term t
forall x y. (HasSpec x, HasSpec y) => Term (x, y) -> Term y
snd_ Term (x, t)
forest) ((Term a -> Pred) -> Pred) -> (Term a -> Pred) -> Pred
forall a b. (a -> b) -> a -> b
$ Hint a -> Term a -> Pred
forall t. HasGenHint t => Hint t -> Term t -> Pred
genHint (a -> Maybe a
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 = VMap vk vv k v -> Map k v
VMap vk vv k v -> SimpleRep (VMap vk vv k v)
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 = Map k v -> VMap vk vv k v
SimpleRep (VMap vk vv k v) -> VMap vk vv k v
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 (KeyHash 'StakePool) PoolParams
Map DRep (CompactForm Coin)
Map (Credential 'Staking) (CompactForm Coin)
Map (Credential 'DRepRole) DRepState
PoolDistr
CommitteeState ConwayEra
InstantStake ConwayEra
EnactState ConwayEra
StrictSeq (GovActionState ConwayEra)
EpochNo
Globals
UMap
dpPulseSize :: Int
dpUMap :: UMap
dpIndex :: Int
dpInstantStake :: InstantStake ConwayEra
dpStakePoolDistr :: PoolDistr
dpDRepDistr :: Map DRep (CompactForm Coin)
dpDRepState :: Map (Credential 'DRepRole) DRepState
dpCurrentEpoch :: EpochNo
dpCommitteeState :: CommitteeState ConwayEra
dpEnactState :: EnactState ConwayEra
dpProposals :: StrictSeq (GovActionState ConwayEra)
dpProposalDeposits :: Map (Credential 'Staking) (CompactForm Coin)
dpGlobals :: Globals
dpPoolParams :: Map (KeyHash 'StakePool) PoolParams
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
..} =
    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
ConwayInstantStake 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]
      SOP '["DRepPulser" ::: DRepPulserTypes]
SimpleRep (DRepPulser ConwayEra Identity (RatifyState ConwayEra))
rep
      ((Int
  -> UMap
  -> Int
  -> ConwayInstantStake 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
  -> DRepPulser ConwayEra Identity (RatifyState ConwayEra))
 -> DRepPulser ConwayEra Identity (RatifyState ConwayEra))
-> (Int
    -> UMap
    -> Int
    -> ConwayInstantStake 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
    -> DRepPulser ConwayEra Identity (RatifyState ConwayEra))
-> DRepPulser ConwayEra Identity (RatifyState ConwayEra)
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 ->
        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)
-> Globals
-> Map (KeyHash 'StakePool) PoolParams
-> DRepPulser ConwayEra Identity (RatifyState ConwayEra)
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 InstantStake ConwayEra
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)

-- ================================================================
-- All the Tx instances

-- Unlike ShelleyTx, AlonzoTx is just a data type, and the generic instances work fine
-- BUT, all the type families inside need constraints

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)

-- NOTE: this is a representation of the `ShelleyTx` type. You can't
-- simply use the generics to derive the `SimpleRep` for `ShelleyTx`
-- because the type is memoized. So instead we say that the representation
-- is the same as what you would get from using the `ShelleyTx` pattern.
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
      (StrictMaybe (TxAuxData era) -> Maybe (TxAuxData era)
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]
      SOP '["ShelleyTx" ::: ShelleyTxTypes era]
SimpleRep (ShelleyTx era)
rep
      (\TxBody era
body TxWits era
wits Maybe (TxAuxData era)
aux -> TxBody era
-> TxWits era -> StrictMaybe (TxAuxData era) -> ShelleyTx era
forall era.
EraTx era =>
TxBody era
-> TxWits era -> StrictMaybe (TxAuxData era) -> ShelleyTx era
ShelleyTx TxBody era
body TxWits era
wits (Maybe (TxAuxData era) -> StrictMaybe (TxAuxData era)
forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe (TxAuxData era)
aux))

instance HasSimpleRep IsValid

instance HasSpec IsValid

-- ===============================================================
-- All the TxAuxData instances

-- NOTE: we don't generate or talk about plutus scripts (yet!)
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] SOP '["AlonzoTxAuxData" ::: AlonzoTxAuxDataTypes era]
SimpleRep (AlonzoTxAuxData era)
rep ((Map Word64 Metadatum
  -> StrictSeq (Timelock era) -> AlonzoTxAuxData era)
 -> AlonzoTxAuxData era)
-> (Map Word64 Metadatum
    -> StrictSeq (Timelock era) -> AlonzoTxAuxData era)
-> AlonzoTxAuxData era
forall a b. (a -> b) -> a -> b
$
      \Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq -> Map Word64 Metadatum
-> StrictSeq (Timelock era)
-> Map Language (NonEmpty PlutusBinary)
-> AlonzoTxAuxData era
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 Map Language (NonEmpty PlutusBinary)
forall a. Monoid a => a
mempty

instance
  ( Era era
  , AlonzoEraScript era
  , NativeScript era ~ Timelock era
  ) =>
  HasSpec (AlonzoTxAuxData era)

-- NOTE: we don't generate or talk about plutus scripts (yet!)
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] SOP '["AllegraTxAuxData" ::: AllegraTxAuxDataTypes era]
SimpleRep (AllegraTxAuxData era)
rep ((Map Word64 Metadatum
  -> StrictSeq (Timelock era) -> AllegraTxAuxData era)
 -> AllegraTxAuxData era)
-> (Map Word64 Metadatum
    -> StrictSeq (Timelock era) -> AllegraTxAuxData era)
-> AllegraTxAuxData era
forall a b. (a -> b) -> a -> b
$
      \Map Word64 Metadatum
metaMap StrictSeq (Timelock era)
tsSeq -> Map Word64 Metadatum
-> StrictSeq (Timelock era) -> AllegraTxAuxData era
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] SOP '["ShelleyTxAuxData" ::: ShelleyTxAuxDataTypes era]
SimpleRep (ShelleyTxAuxData era)
rep ((Map Word64 Metadatum -> ShelleyTxAuxData era)
 -> ShelleyTxAuxData era)
-> (Map Word64 Metadatum -> ShelleyTxAuxData era)
-> ShelleyTxAuxData era
forall a b. (a -> b) -> a -> b
$
      \Map Word64 Metadatum
metaMap -> Map Word64 Metadatum -> ShelleyTxAuxData era
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

-- ===============================================================
-- All the TxWits instances

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] SOP '["AlonzoTxWits" ::: AlonzoTxWitsTypes]
SimpleRep (AlonzoTxWits era)
rep ((Set (WitVKey 'Witness)
  -> Set BootstrapWitness -> AlonzoTxWits era)
 -> AlonzoTxWits era)
-> (Set (WitVKey 'Witness)
    -> Set BootstrapWitness -> AlonzoTxWits era)
-> AlonzoTxWits era
forall a b. (a -> b) -> a -> b
$
      \Set (WitVKey 'Witness)
vkeyWits Set BootstrapWitness
bootstrapWits -> Set (WitVKey 'Witness)
-> Set BootstrapWitness
-> Map ScriptHash (Script era)
-> TxDats era
-> Redeemers era
-> AlonzoTxWits era
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 Map ScriptHash (Script era)
forall a. Monoid a => a
mempty (Map DataHash (Data era) -> TxDats era
forall era. Era era => Map DataHash (Data era) -> TxDats era
TxDats Map DataHash (Data era)
forall a. Monoid a => a
mempty) (Map (PlutusPurpose AsIx era) (Data era, ExUnits) -> Redeemers era
forall era.
AlonzoEraScript era =>
Map (PlutusPurpose AsIx era) (Data era, ExUnits) -> Redeemers era
Redeemers Map (PlutusPurpose AsIx era) (Data era, ExUnits)
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] SOP '["ShelleyTxWits" ::: AlonzoTxWitsTypes]
SimpleRep (ShelleyTxWits era)
rep ((Set (WitVKey 'Witness)
  -> Set BootstrapWitness -> ShelleyTxWits era)
 -> ShelleyTxWits era)
-> (Set (WitVKey 'Witness)
    -> Set BootstrapWitness -> ShelleyTxWits era)
-> ShelleyTxWits era
forall a b. (a -> b) -> a -> b
$
      \Set (WitVKey 'Witness)
vkeyWits Set BootstrapWitness
bootstrapWits -> Set (WitVKey 'Witness)
-> Map ScriptHash (Script era)
-> Set BootstrapWitness
-> ShelleyTxWits era
forall era.
EraScript era =>
Set (WitVKey 'Witness)
-> Map ScriptHash (Script era)
-> Set BootstrapWitness
-> ShelleyTxWits era
ShelleyTxWits Set (WitVKey 'Witness)
vkeyWits Map ScriptHash (Script era)
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)
_ = Specification (WitVKey r)
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec (WitVKey r) -> GenT m (WitVKey r)
genFromTypeSpec TypeSpec (WitVKey r)
_ = Gen (WitVKey r) -> GenT m (WitVKey r)
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen (WitVKey r)
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec (WitVKey r) -> Specification Integer
cardinalTypeSpec TypeSpec (WitVKey r)
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec (WitVKey r) -> WitVKey r -> [WitVKey r]
shrinkWithTypeSpec TypeSpec (WitVKey r)
_ = WitVKey r -> [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)
_ = Bool -> Pred
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
_ = Specification BootstrapWitness
forall deps a. SpecificationD deps a
TrueSpec
  genFromTypeSpec :: forall (m :: * -> *).
(HasCallStack, MonadGenError m) =>
TypeSpec BootstrapWitness -> GenT m BootstrapWitness
genFromTypeSpec TypeSpec BootstrapWitness
_ = Gen BootstrapWitness -> GenT m BootstrapWitness
forall (m :: * -> *) a. Applicative m => Gen a -> GenT m a
pureGen Gen BootstrapWitness
forall a. Arbitrary a => Gen a
arbitrary
  cardinalTypeSpec :: TypeSpec BootstrapWitness -> Specification Integer
cardinalTypeSpec TypeSpec BootstrapWitness
_ = Specification Integer
forall deps a. SpecificationD deps a
TrueSpec
  shrinkWithTypeSpec :: TypeSpec BootstrapWitness -> BootstrapWitness -> [BootstrapWitness]
shrinkWithTypeSpec TypeSpec BootstrapWitness
_ = BootstrapWitness -> [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
_ = Bool -> Pred
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 = Term (StrictMaybe a)
-> FunTy
     (MapList
        (Weighted (BinderD Deps)) (Cases (SimpleRep (StrictMaybe a))))
     Pred
forall a.
(GenericRequires a, SimpleRep a ~ SumOver (Cases (SimpleRep a)),
 TypeList (Cases (SimpleRep a))) =>
Term a
-> FunTy
     (MapList (Weighted (BinderD Deps)) (Cases (SimpleRep a))) Pred
caseOn Term (StrictMaybe a)
tm (FunTy (MapList Term (Args ())) Bool -> Weighted (BinderD Deps) ()
forall p a.
(HasSpec a, All HasSpec (Args a), IsPred p, IsProd a) =>
FunTy (MapList Term (Args a)) p -> Weighted (BinderD Deps) a
branch (FunTy (MapList Term (Args ())) Bool -> Weighted (BinderD Deps) ())
-> FunTy (MapList Term (Args ())) Bool
-> Weighted (BinderD Deps) ()
forall a b. (a -> b) -> a -> b
$ Bool -> TermD Deps () -> Bool
forall a b. a -> b -> a
const Bool
True) (FunTy (MapList Term (Args a)) p -> Weighted (BinderD Deps) a
forall p a.
(HasSpec a, All HasSpec (Args a), IsPred p, IsProd a) =>
FunTy (MapList Term (Args a)) p -> Weighted (BinderD Deps) a
branch FunTy (MapList Term (Args a)) p
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 = Term (Sized a)
-> FunTy (MapList Term (ProductAsList (Sized a))) p -> Pred
forall p a.
(IsProductType a, IsPred p, GenericRequires a,
 ProdAsListComputes a) =>
Term a -> FunTy (MapList Term (ProductAsList a)) p -> Pred
match Term (Sized a)
sz (FunTy (MapList Term (ProductAsList (Sized a))) p -> Pred)
-> FunTy (MapList Term (ProductAsList (Sized a))) p -> Pred
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) = RewardUpdate -> SimpleRep RewardUpdate
forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep RewardUpdate
x
  toSimpleRep x :: PulsingRewUpdate
x@(Pulsing RewardSnapShot
_ Pulser
_) = RewardUpdate -> SimpleRep RewardUpdate
forall a. HasSimpleRep a => a -> SimpleRep a
toSimpleRep (ShelleyBase RewardUpdate -> RewardUpdate
forall a. ShelleyBase a -> a
runShelleyBase ((RewardUpdate, Map (Credential 'Staking) (Set Reward))
-> RewardUpdate
forall a b. (a, b) -> a
fst ((RewardUpdate, Map (Credential 'Staking) (Set Reward))
 -> RewardUpdate)
-> ReaderT
     Globals
     Identity
     (RewardUpdate, Map (Credential 'Staking) (Set Reward))
-> ShelleyBase RewardUpdate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PulsingRewUpdate
-> ReaderT
     Globals
     Identity
     (RewardUpdate, Map (Credential 'Staking) (Set Reward))
completeRupd PulsingRewUpdate
x))
  fromSimpleRep :: SimpleRep PulsingRewUpdate -> PulsingRewUpdate
fromSimpleRep SimpleRep PulsingRewUpdate
x = RewardUpdate -> PulsingRewUpdate
Complete (SimpleRep RewardUpdate -> RewardUpdate
forall a. HasSimpleRep a => SimpleRep a -> a
fromSimpleRep SimpleRep PulsingRewUpdate
SimpleRep RewardUpdate
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]
      SOP '["Pulser" ::: PulserTypes]
SimpleRep Pulser
rep
      Int
-> FreeVars
-> VMap VB VP (Credential 'Staking) (CompactForm Coin)
-> RewardAns
-> Pulser
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)

-- CompactForm

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) = [[Char]]
-> Specification (KeyHash krole) -> Specification (KeyHash krole)
forall a. [[Char]] -> Specification a -> Specification a
explainSpecOpt [[Char]]
es (Specification (KeyHash 'Witness) -> Specification (KeyHash krole)
forall a b. CoercibleLike a b => Specification b -> Specification a
coerceSpec Specification (KeyHash 'Witness)
x)
  coerceSpec (TypeSpec TypeSpec (KeyHash 'Witness)
z [KeyHash 'Witness]
excl) = TypeSpec (KeyHash krole)
-> [KeyHash krole] -> Specification (KeyHash krole)
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec TypeSpec (KeyHash krole)
TypeSpec (KeyHash 'Witness)
z ([KeyHash krole] -> Specification (KeyHash krole))
-> [KeyHash krole] -> Specification (KeyHash krole)
forall a b. (a -> b) -> a -> b
$ KeyHash 'Witness -> KeyHash krole
forall (r :: KeyRole) (r' :: KeyRole). KeyHash r -> KeyHash r'
forall (a :: KeyRole -> *) (r :: KeyRole) (r' :: KeyRole).
HasKeyRole a =>
a r -> a r'
coerceKeyRole (KeyHash 'Witness -> KeyHash krole)
-> [KeyHash 'Witness] -> [KeyHash krole]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [KeyHash 'Witness]
excl
  coerceSpec (MemberSpec NonEmpty (KeyHash 'Witness)
s) = NonEmpty (KeyHash krole) -> Specification (KeyHash krole)
forall a deps. NonEmpty a -> SpecificationD deps a
MemberSpec (NonEmpty (KeyHash krole) -> Specification (KeyHash krole))
-> NonEmpty (KeyHash krole) -> Specification (KeyHash krole)
forall a b. (a -> b) -> a -> b
$ KeyHash 'Witness -> KeyHash krole
forall (r :: KeyRole) (r' :: KeyRole). KeyHash r -> KeyHash r'
forall (a :: KeyRole -> *) (r :: KeyRole) (r' :: KeyRole).
HasKeyRole a =>
a r -> a r'
coerceKeyRole (KeyHash 'Witness -> KeyHash krole)
-> NonEmpty (KeyHash 'Witness) -> NonEmpty (KeyHash krole)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (KeyHash 'Witness)
s
  coerceSpec (ErrorSpec NonEmpty [Char]
e) = NonEmpty [Char] -> Specification (KeyHash krole)
forall deps a. NonEmpty [Char] -> SpecificationD deps a
ErrorSpec NonEmpty [Char]
e
  coerceSpec (SuspendedSpec Var (KeyHash 'Witness)
x Pred
p) = (Term (KeyHash krole) -> [Pred]) -> Specification (KeyHash krole)
forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained ((Term (KeyHash krole) -> [Pred]) -> Specification (KeyHash krole))
-> (Term (KeyHash krole) -> [Pred])
-> Specification (KeyHash krole)
forall a b. (a -> b) -> a -> b
$ \Term (KeyHash krole)
x' ->
    [ Pred
p
    , Term (KeyHash krole)
-> (KeyHash krole -> KeyHash 'Witness)
-> (Term (KeyHash 'Witness) -> Term Bool)
-> Pred
forall a b p.
(HasSpec a, HasSpec b, IsPred p) =>
Term a -> (a -> b) -> (Term b -> p) -> Pred
reify Term (KeyHash krole)
x' KeyHash krole -> KeyHash 'Witness
forall (r :: KeyRole) (r' :: KeyRole). KeyHash r -> KeyHash r'
forall (a :: KeyRole -> *) (r :: KeyRole) (r' :: KeyRole).
HasKeyRole a =>
a r -> a r'
coerceKeyRole (Term (KeyHash 'Witness) -> Term (KeyHash 'Witness) -> Term Bool
forall a. HasSpec a => Term a -> Term a -> Term Bool
==. Var (KeyHash 'Witness) -> Term (KeyHash 'Witness)
forall deps a.
(HasSpecD deps a, Typeable a) =>
Var a -> TermD deps a
V Var (KeyHash 'Witness)
x)
    ]
  coerceSpec Specification (KeyHash 'Witness)
TrueSpec = Specification (KeyHash krole)
forall deps a. SpecificationD deps a
TrueSpec

  getCoerceSpec ::
    TypeSpec (KeyHash krole) ->
    Specification (KeyHash 'Witness)
  getCoerceSpec :: TypeSpec (KeyHash krole) -> Specification (KeyHash 'Witness)
getCoerceSpec TypeSpec (KeyHash krole)
x = TypeSpec (KeyHash 'Witness)
-> [KeyHash 'Witness] -> Specification (KeyHash 'Witness)
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec TypeSpec (KeyHash krole)
TypeSpec (KeyHash 'Witness)
x [KeyHash 'Witness]
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) =
    TypeSpec (CompactForm Coin)
-> [CompactForm Coin] -> Specification (CompactForm Coin)
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec (Maybe Word64 -> Maybe Word64 -> NumSpec Word64
forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval Maybe Word64
lo Maybe Word64
hi) ([CompactForm Coin] -> Specification (CompactForm Coin))
-> [CompactForm Coin] -> Specification (CompactForm Coin)
forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin (Word64 -> CompactForm Coin) -> [Word64] -> [CompactForm Coin]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Word64]
excl
  coerceSpec (MemberSpec NonEmpty Word64
s) = NonEmpty (CompactForm Coin) -> Specification (CompactForm Coin)
forall a deps. NonEmpty a -> SpecificationD deps a
MemberSpec (NonEmpty (CompactForm Coin) -> Specification (CompactForm Coin))
-> NonEmpty (CompactForm Coin) -> Specification (CompactForm Coin)
forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin (Word64 -> CompactForm Coin)
-> NonEmpty Word64 -> NonEmpty (CompactForm Coin)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty Word64
s
  coerceSpec (ErrorSpec NonEmpty [Char]
e) = NonEmpty [Char] -> Specification (CompactForm Coin)
forall deps a. NonEmpty [Char] -> SpecificationD deps a
ErrorSpec NonEmpty [Char]
e
  coerceSpec (SuspendedSpec Var Word64
x Pred
p) = (Term (CompactForm Coin) -> [Pred])
-> Specification (CompactForm Coin)
forall a p.
(IsPred p, HasSpec a) =>
(Term a -> p) -> Specification a
constrained ((Term (CompactForm Coin) -> [Pred])
 -> Specification (CompactForm Coin))
-> (Term (CompactForm Coin) -> [Pred])
-> Specification (CompactForm Coin)
forall a b. (a -> b) -> a -> b
$ \Term (CompactForm Coin)
x' ->
    [ Pred
p
    , Term (CompactForm Coin)
-> (CompactForm Coin -> Word64)
-> (Term Word64 -> Term Bool)
-> Pred
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 (Term Word64 -> Term Word64 -> Term Bool
forall a. HasSpec a => Term a -> Term a -> Term Bool
==. Var Word64 -> Term Word64
forall deps a.
(HasSpecD deps a, Typeable a) =>
Var a -> TermD deps a
V Var Word64
x)
    ]
  coerceSpec Specification Word64
TrueSpec = Specification (CompactForm Coin)
forall deps a. SpecificationD deps a
TrueSpec
  coerceSpec (ExplainSpec [[Char]]
es Specification Word64
x) = [[Char]]
-> Specification (CompactForm Coin)
-> Specification (CompactForm Coin)
forall deps a.
[[Char]] -> SpecificationD deps a -> SpecificationD deps a
ExplainSpec [[Char]]
es (Specification Word64 -> Specification (CompactForm Coin)
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) = TypeSpec Word64 -> [Word64] -> Specification Word64
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec (Maybe Word64 -> Maybe Word64 -> NumSpec Word64
forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval Maybe Word64
a Maybe Word64
b) [Word64]
forall a. Monoid a => a
mempty

data CoercibleW (args :: [Type]) (res :: Type) where
  CoerceW :: (CoercibleLike a b, Coercible a b) => CoercibleW '[a] b

deriving instance Show (CoercibleW args res)

deriving instance Eq (CoercibleW args res)

instance Syntax CoercibleW

instance Semantics CoercibleW where
  semantics :: forall (d :: [*]) r. CoercibleW d r -> FunTy d r
semantics = \case
    CoercibleW d r
CoerceW -> FunTy d r
a -> r
forall a b. Coercible a b => a -> b
coerce

instance Logic CoercibleW where
  propagateMemberSpec :: forall (as :: [*]) b a.
(AppRequires CoercibleW as b, HasSpec a) =>
CoercibleW as b
-> ListCtx Value as (HOLE a) -> NonEmpty b -> Specification a
propagateMemberSpec CoercibleW as b
CoerceW (Unary HOLE a a
HOLE) NonEmpty b
xs = Specification b -> Specification a
forall a b. CoercibleLike a b => Specification b -> Specification a
coerceSpec (Specification b -> Specification a)
-> Specification b -> Specification a
forall a b. (a -> b) -> a -> b
$ NonEmpty b -> Specification b
forall a deps. NonEmpty a -> SpecificationD deps a
MemberSpec NonEmpty b
xs
  propagateTypeSpec :: forall (as :: [*]) b a.
(AppRequires CoercibleW as b, HasSpec a) =>
CoercibleW as b
-> ListCtx Value as (HOLE a)
-> TypeSpec b
-> [b]
-> Specification a
propagateTypeSpec CoercibleW as b
CoerceW (Unary HOLE a a
HOLE) TypeSpec b
ts [b]
cant = Specification b -> Specification a
forall a b. CoercibleLike a b => Specification b -> Specification a
coerceSpec (Specification b -> Specification a)
-> Specification b -> Specification a
forall a b. (a -> b) -> a -> b
$ TypeSpec b -> [b] -> Specification b
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec TypeSpec b
ts [b]
cant

  mapTypeSpec ::
    forall a b. (HasSpec a, HasSpec b) => CoercibleW '[a] b -> TypeSpec a -> Specification b
  mapTypeSpec :: forall a b.
(HasSpec a, HasSpec b) =>
CoercibleW '[a] b -> TypeSpec a -> Specification b
mapTypeSpec CoercibleW '[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_ = CoercibleW '[a] b -> FunTy (MapList Term '[a]) (TermD Deps b)
forall (t :: [*] -> * -> *) (ds :: [*]) r.
AppRequires t ds r =>
t ds r -> FunTy (MapList Term ds) (Term r)
appTerm CoercibleW '[a] b
forall a b. (CoercibleLike a b, Coercible a b) => CoercibleW '[a] b
CoerceW

-- ==============================================================

data CoinW (ds :: [Type]) (res :: Type) where
  ToDeltaW :: CoinW '[Coin] DeltaCoin

deriving instance Show (CoinW args res)

deriving instance Eq (CoinW args res)

instance Syntax CoinW

instance Semantics CoinW where
  semantics :: forall (d :: [*]) r. CoinW d r -> FunTy d r
semantics = \case
    CoinW d r
ToDeltaW -> Integer -> DeltaCoin
DeltaCoin (Integer -> DeltaCoin) -> (Coin -> Integer) -> Coin -> 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_ = CoinW '[Coin] DeltaCoin
-> FunTy (MapList Term '[Coin]) (Term DeltaCoin)
forall (t :: [*] -> * -> *) (ds :: [*]) r.
AppRequires t ds r =>
t ds r -> FunTy (MapList Term ds) (Term r)
appTerm CoinW '[Coin] DeltaCoin
ToDeltaW

instance Logic CoinW where
  propagateMemberSpec :: forall (as :: [*]) b a.
(AppRequires CoinW as b, HasSpec a) =>
CoinW as b
-> ListCtx Value as (HOLE a) -> NonEmpty b -> Specification a
propagateMemberSpec CoinW as b
ToDeltaW (Unary HOLE a Coin
HOLE) NonEmpty b
xs = NonEmpty a -> SpecificationD Deps a
forall a deps. NonEmpty a -> SpecificationD deps a
MemberSpec ((DeltaCoin -> a) -> NonEmpty DeltaCoin -> NonEmpty a
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map DeltaCoin -> a
DeltaCoin -> Coin
deltaToCoin NonEmpty b
NonEmpty DeltaCoin
xs)

  propagateTypeSpec :: forall (as :: [*]) b a.
(AppRequires CoinW as b, HasSpec a) =>
CoinW as b
-> ListCtx Value as (HOLE a)
-> TypeSpec b
-> [b]
-> Specification a
propagateTypeSpec CoinW as b
ToDeltaW (Unary HOLE a Coin
HOLE) (NumSpecInterval Maybe Integer
l Maybe Integer
h) [b]
cant =
    TypeSpec a -> [a] -> Specification a
forall a. HasSpec a => TypeSpec a -> [a] -> Specification a
TypeSpec
      (Maybe Word64 -> Maybe Word64 -> NumSpec Word64
forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval (Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word64) -> Maybe Integer -> Maybe Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer
l) (Integer -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> Word64) -> Maybe Integer -> Maybe Word64
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer
h))
      ((DeltaCoin -> a) -> [DeltaCoin] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map DeltaCoin -> a
DeltaCoin -> Coin
deltaToCoin [b]
[DeltaCoin]
cant)

  mapTypeSpec :: forall a b.
(HasSpec a, HasSpec b) =>
CoinW '[a] b -> TypeSpec a -> Specification b
mapTypeSpec CoinW '[a] b
ToDeltaW (NumSpecInterval Maybe Word64
l Maybe Word64
h) = TypeSpec b -> Specification b
forall a. HasSpec a => TypeSpec a -> Specification a
typeSpec (Maybe Integer -> Maybe Integer -> NumSpec Integer
forall n. Maybe n -> Maybe n -> NumSpec n
NumSpecInterval (Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Integer) -> Maybe Word64 -> Maybe Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Word64
l) (Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Integer) -> Maybe Word64 -> Maybe Integer
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