Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Cooked
Description
Re-exports the entirety of the library, which is always eventually necessary when writing large test-suites.
Synopsis
- data Test a prop = Test {
- testTrace :: StagedMockChain a
- testInitDist :: InitialDistribution
- testSizeProp :: SizeProp prop
- testFailureProp :: FailureProp prop
- testSuccessProp :: SuccessProp a prop
- testPrettyOpts :: PrettyCookedOpts
- type family (xs :: [a]) ∪ (ys :: [a]) :: [a] where ...
- type family (el :: a) ∉ (els :: [a]) :: Constraint where ...
- data Mint where
- Mint :: ToVersioned MintingPolicy a => {..} -> Mint
- data Ltl a
- data InitialDistribution where
- InitialDistribution :: {..} -> InitialDistribution
- class Monad m => MonadModal m where
- type Modification m :: Type
- modifyLtl :: Ltl (Modification m) -> m a -> m a
- type MockChain = MockChainT Identity
- class ShowBS a where
- showBS :: a -> BuiltinString
- type Wallet = MockWallet
- data AddTokenLbl = AddTokenLbl
- newtype DatumHijackingLbl = DatumHijackingLbl Credential
- type DoubleSatDelta = (Map TxOutRef TxSkelRedeemer, [TxSkelOut], TxSkelMints)
- data DoubleSatLbl = DoubleSatLbl
- data DupTokenLbl = DupTokenLbl
- data MockChainState = MockChainState {}
- type UtxoSearch m a = ListT m (TxOutRef, a)
- data MockChainError
- = MCEValidationError ValidationPhase ValidationError
- | MCEUnbalanceable Wallet Value
- | MCEMissingBalancingWallet String
- | MCENoSuitableCollateral Integer Integer Value
- | MCEToCardanoError String ToCardanoError
- | MCEWrongReferenceScriptError TxOutRef ScriptHash (Maybe ScriptHash)
- | MCEUnknownOutRef TxOutRef
- | MCEPastSlot Slot Slot
- | MCEUnsupportedFeature String
- | FailWith String
- class (MonadFail m, MonadError MockChainError m) => MonadBlockChainBalancing m where
- class MonadBlockChainBalancing m => MonadBlockChainWithoutValidation m where
- allUtxos :: m [(TxOutRef, TxSkelOut)]
- setParams :: Params -> m ()
- waitNSlots :: Integral i => i -> m Slot
- define :: ToHash a => String -> a -> m a
- setConstitutionScript :: ToVersioned Script s => s -> m ()
- getConstitutionScript :: m (Maybe (Versioned Script))
- registerStakingCred :: ToCredential c => c -> Integer -> Integer -> m ()
- class MonadBlockChainWithoutValidation m => MonadBlockChain m where
- validateTxSkel :: TxSkel -> m CardanoTx
- forceOutputs :: [TxSkelOut] -> m [TxOutRef]
- newtype AsTrans t (m :: Type -> Type) a = AsTrans {
- getTrans :: t m a
- data MockChainBook = MockChainBook {}
- type MonadModalBlockChain m = (MonadBlockChain m, MonadModal m, Modification m ~ UntypedTweak InterpMockChain)
- class IsProp prop where
- testCounterexample :: String -> prop -> prop
- testConjoin :: [prop] -> prop
- testDisjoin :: [prop] -> prop
- testFailure :: prop
- testSuccess :: prop
- testFailureMsg :: String -> prop
- data UtxoPayloadDatum where
- NoUtxoPayloadDatum :: UtxoPayloadDatum
- SomeUtxoPayloadDatum :: DatumConstrs dat => dat -> Bool -> UtxoPayloadDatum
- type DocCooked = Doc ()
- class PrettyCooked a where
- prettyCookedOpt :: PrettyCookedOpts -> a -> DocCooked
- prettyCooked :: a -> DocCooked
- class PrettyCookedList a where
- prettyCookedOptList :: PrettyCookedOpts -> a -> [DocCooked]
- prettyCookedOptListMaybe :: PrettyCookedOpts -> a -> [Maybe DocCooked]
- prettyCookedList :: a -> [DocCooked]
- class PrettyCookedMaybe a where
- prettyCookedOptMaybe :: PrettyCookedOpts -> a -> Maybe DocCooked
- prettyCookedMaybe :: a -> Maybe DocCooked
- class ToHash a where
- toHash :: a -> BuiltinByteString
- data PrettyCookedOpts = PrettyCookedOpts {}
- data PrettyCookedHashOpts = PrettyCookedHashOpts {}
- data PCOptTxOutRefs
- data TxSkel where
- data Payable :: [Symbol] -> Type where
- VisibleHashedDatum :: DatumConstrs a => a -> Payable '["Datum"]
- InlineDatum :: DatumConstrs a => a -> Payable '["Datum"]
- HiddenHashedDatum :: DatumConstrs a => a -> Payable '["Datum"]
- ReferenceScript :: ReferenceScriptConstrs s => s -> Payable '["Reference Script"]
- Value :: ToValue a => a -> Payable '["Value"]
- FixedValue :: ToValue a => a -> Payable '["Value"]
- StakingCredential :: ToMaybeStakingCredential cred => cred -> Payable '["Staking Credential"]
- PayableAnd :: els ⩀ els' => Payable els -> Payable els' -> Payable (els ∪ els')
- type DatumConstrs datum = (Show datum, PrettyCooked datum, ToData datum, FromData datum, Eq datum, Typeable datum)
- data DatumResolved
- data DatumKind
- data TxSkelOutDatum where
- NoTxSkelOutDatum :: TxSkelOutDatum
- SomeTxSkelOutDatum :: DatumConstrs dat => dat -> DatumKind -> TxSkelOutDatum
- type LabelConstrs x = (PrettyCooked x, Show x, Typeable x, Eq x, Ord x)
- data TxSkelLabel where
- TxSkelLabel :: LabelConstrs x => x -> TxSkelLabel
- type TxSkelMints = Map (Versioned MintingPolicy) (TxSkelRedeemer, NEMap TokenName (NonZero Integer))
- data BalanceOutputPolicy
- data FeePolicy
- data BalancingPolicy
- data BalancingUtxos
- data CollateralUtxos
- data AnchorResolution
- data TxSkelOpts = TxSkelOpts {
- txSkelOptAutoSlotIncrease :: Bool
- txSkelOptModTx :: Tx ConwayEra -> Tx ConwayEra
- txSkelOptBalancingPolicy :: BalancingPolicy
- txSkelOptFeePolicy :: FeePolicy
- txSkelOptBalanceOutputPolicy :: BalanceOutputPolicy
- txSkelOptBalancingUtxos :: BalancingUtxos
- txSkelOptModParams :: Params -> Params
- txSkelOptCollateralUtxos :: CollateralUtxos
- txSkelOptAnchorResolution :: AnchorResolution
- data TxSkelOut where
- TxSkelOut :: OwnerConstrs owner => {..} -> TxSkelOut
- class IsTxSkelOutAllowedOwner a where
- toPKHOrValidator :: a -> Either PubKeyHash (Versioned Validator)
- type OwnerConstrs owner = (IsTxSkelOutAllowedOwner owner, Typeable owner, Show owner)
- type family (els :: [a]) ⩀ (els' :: [a]) :: Constraint where ...
- data TxParameterChange where
- FeePerByte :: Integer -> TxParameterChange
- FeeFixed :: Integer -> TxParameterChange
- MaxBlockBodySize :: Integer -> TxParameterChange
- MaxTxSize :: Integer -> TxParameterChange
- MaxBlockHeaderSize :: Integer -> TxParameterChange
- KeyDeposit :: Integer -> TxParameterChange
- PoolDeposit :: Integer -> TxParameterChange
- PoolRetirementMaxEpoch :: Integer -> TxParameterChange
- PoolNumber :: Integer -> TxParameterChange
- PoolInfluence :: Rational -> TxParameterChange
- MonetaryExpansion :: Rational -> TxParameterChange
- TreasuryCut :: Rational -> TxParameterChange
- MinPoolCost :: Integer -> TxParameterChange
- CoinsPerUTxOByte :: Integer -> TxParameterChange
- CostModels :: {..} -> TxParameterChange
- Prices :: {..} -> TxParameterChange
- MaxTxExUnits :: {..} -> TxParameterChange
- MaxBlockExUnits :: {..} -> TxParameterChange
- MaxValSize :: Integer -> TxParameterChange
- CollateralPercentage :: Integer -> TxParameterChange
- MaxCollateralInputs :: Integer -> TxParameterChange
- PoolVotingThresholds :: {..} -> TxParameterChange
- DRepVotingThresholds :: {..} -> TxParameterChange
- CommitteeMinSize :: Integer -> TxParameterChange
- CommitteeMaxTermLength :: Integer -> TxParameterChange
- GovActionLifetime :: Integer -> TxParameterChange
- GovActionDeposit :: Integer -> TxParameterChange
- DRepRegistrationDeposit :: Integer -> TxParameterChange
- DRepActivity :: Integer -> TxParameterChange
- MinFeeRefScriptCostPerByte :: Rational -> TxParameterChange
- data TxGovAction where
- TxGovActionParameterChange :: [TxParameterChange] -> TxGovAction
- TxGovActionHardForkInitiation :: ProtocolVersion -> TxGovAction
- TxGovActionTreasuryWithdrawals :: Map Credential Lovelace -> TxGovAction
- TxGovActionNoConfidence :: TxGovAction
- TxGovActionUpdateCommittee :: [ColdCommitteeCredential] -> Map ColdCommitteeCredential Integer -> Rational -> TxGovAction
- TxGovActionNewConstitution :: Constitution -> TxGovAction
- data TxSkelProposal where
- TxSkelProposal :: {..} -> TxSkelProposal
- data TxSkelRedeemer where
- TxSkelRedeemer :: RedeemerConstrs redeemer => {..} -> TxSkelRedeemer
- type RedeemerConstrs redeemer = (ToData redeemer, FromData redeemer, Show redeemer, PrettyCooked redeemer, Eq redeemer, Typeable redeemer)
- type ReferenceScriptConstrs refScript = (ToVersioned Script refScript, Typeable refScript)
- data TxSkelOutReferenceScript where
- type TxSkelWithdrawals = Map (Either (Versioned Script) PubKeyHash) (TxSkelRedeemer, Lovelace)
- class (MonadPlus m, MonadBlockChainWithoutValidation m) => MonadTweak m where
- data PermutOutTweakMode
- = KeepIdentity (Maybe Int)
- | OmitIdentity (Maybe Int)
- data TamperDatumLbl = TamperDatumLbl
- data MalformDatumLbl = MalformDatumLbl
- newtype MockChainT m a = MockChainT {}
- type FailureProp prop = PrettyCookedOpts -> [MockChainLogEntry] -> MockChainError -> UtxoState -> prop
- type SuccessProp a prop = PrettyCookedOpts -> [MockChainLogEntry] -> a -> UtxoState -> prop
- type SizeProp prop = Integer -> prop
- type JournalProp prop = PrettyCookedOpts -> [MockChainLogEntry] -> prop
- type StateProp prop = PrettyCookedOpts -> UtxoState -> prop
- pattern MCLogSubmittedTxSkel :: TxSkel -> MockChainLogEntry
- pattern MCLogAdjustedTxSkel :: TxSkel -> Integer -> Maybe (Set TxOutRef, Wallet) -> MockChainLogEntry
- pattern MCLogNewTx :: TxId -> Integer -> MockChainLogEntry
- pattern MCLogDiscardedUtxos :: Integer -> String -> MockChainLogEntry
- pattern MCLogUnusedCollaterals :: Either Wallet (Set TxOutRef) -> MockChainLogEntry
- pattern MCLogAddedReferenceScript :: TxSkelRedeemer -> TxOutRef -> ScriptHash -> MockChainLogEntry
- pattern MCLogAdjustedTxSkelOut :: TxSkelOut -> Lovelace -> MockChainLogEntry
- (.&&.) :: IsProp prop => prop -> prop -> prop
- (.||.) :: IsProp prop => prop -> prop -> prop
- forAll :: Show a => Gen a -> (a -> Property) -> Property
- renderString :: (a -> DocCooked) -> a -> String
- currentSlot :: MonadBlockChainWithoutValidation m => m Slot
- awaitSlot :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m Slot
- (<&&>) :: els ⩀ els' => Payable els -> Payable els' -> Payable (els ∪ els')
- (.==.) :: (IsProp prop, Eq a) => a -> a -> prop
- there :: MonadModalBlockChain m => Integer -> Tweak InterpMockChain b -> m a -> m a
- everywhere :: MonadModalBlockChain m => Tweak InterpMockChain b -> m a -> m a
- somewhere :: MonadModalBlockChain m => Tweak InterpMockChain b -> m a -> m a
- withAnchor :: TxSkelProposal -> String -> TxSkelProposal
- ltlDelay :: Integer -> Ltl a -> Ltl a
- addTokenAttack :: (MonadTweak m, OwnerConstrs o) => (Versioned MintingPolicy -> [(TokenName, Integer)]) -> o -> m Value
- redirectOutputTweakAny :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => (TxSkelOut -> Maybe owner') -> (Integer -> Bool) -> m TxSkelOut
- datumHijackingAttackAny :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => (TxSkelOut -> Bool) -> (Integer -> Bool) -> owner' -> m TxSkelOut
- datumHijackingAttack :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => owner' -> m TxSkelOut
- redirectOutputTweakAll :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => (TxSkelOut -> Maybe owner') -> (Integer -> Bool) -> m [TxSkelOut]
- datumHijackingAttackAll :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => (TxSkelOut -> Bool) -> (Integer -> Bool) -> owner' -> m [TxSkelOut]
- doubleSatAttack :: (MonadTweak m, Eq is, Is k A_Traversal) => ([is] -> [[is]]) -> Optic' k (WithIx is) TxSkel a -> (is -> a -> m [(a, DoubleSatDelta)]) -> Wallet -> m ()
- dupTokenAttack :: (MonadTweak m, OwnerConstrs o) => (AssetClass -> Integer -> Integer) -> o -> m Value
- distributionFromList :: [(Wallet, [Value])] -> InitialDistribution
- balanceTxSkel :: MonadBlockChainBalancing m => TxSkel -> m (TxSkel, Integer, Maybe (Set TxOutRef, Wallet))
- getMinAndMaxFee :: MonadBlockChainBalancing m => Integer -> m (Integer, Integer)
- estimateTxSkelFee :: MonadBlockChainBalancing m => TxSkel -> Integer -> Maybe (Set TxOutRef, Wallet) -> m Integer
- currentMSRange :: MonadBlockChainWithoutValidation m => m (POSIXTime, POSIXTime)
- utxosFromCardanoTx :: MonadBlockChainBalancing m => CardanoTx -> m [(TxOutRef, TxSkelOut)]
- getEnclosingSlot :: MonadBlockChainWithoutValidation m => POSIXTime -> m Slot
- awaitEnclosingSlot :: MonadBlockChainWithoutValidation m => POSIXTime -> m Slot
- waitNMSFromSlotLowerBound :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m Slot
- waitNMSFromSlotUpperBound :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m Slot
- slotRangeBefore :: MonadBlockChainWithoutValidation m => POSIXTime -> m SlotRange
- slotRangeAfter :: MonadBlockChainWithoutValidation m => POSIXTime -> m SlotRange
- slotToMSRange :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m (POSIXTime, POSIXTime)
- txSkelInputValidators :: MonadBlockChainBalancing m => TxSkel -> m [Versioned Validator]
- txSkelInputValue :: MonadBlockChainBalancing m => TxSkel -> m Value
- lookupUtxos :: MonadBlockChainBalancing m => [TxOutRef] -> m (Map TxOutRef TxSkelOut)
- validateTxSkel' :: MonadBlockChain m => TxSkel -> m [TxOutRef]
- validateTxSkel_ :: MonadBlockChain m => TxSkel -> m ()
- txSkelProposalsDeposit :: MonadBlockChainBalancing m => TxSkel -> m Lovelace
- govActionDeposit :: MonadBlockChainBalancing m => m Lovelace
- defineM :: (MonadBlockChainWithoutValidation m, ToHash a) => String -> m a -> m a
- txSkelAllScripts :: MonadBlockChainBalancing m => TxSkel -> m [Versioned Script]
- previewByRef :: (MonadBlockChainBalancing m, Is af An_AffineFold) => Optic' af is TxSkelOut c -> TxOutRef -> m (Maybe c)
- viewByRef :: (MonadBlockChainBalancing m, Is g A_Getter) => Optic' g is TxSkelOut c -> TxOutRef -> m c
- toTxSkelOutWithMinAda :: MonadBlockChainBalancing m => TxSkelOut -> m TxSkelOut
- toTxSkelWithMinAda :: MonadBlockChainBalancing m => TxSkel -> m TxSkel
- getTxSkelOutMinAda :: MonadBlockChainBalancing m => TxSkelOut -> m Integer
- interpretAndRunWith :: (forall m. Monad m => MockChainT m a -> m res) -> StagedMockChain a -> [res]
- interpretAndRun :: StagedMockChain a -> [MockChainReturn a]
- runTweakFrom :: InitialDistribution -> Tweak InterpMockChain a -> TxSkel -> [MockChainReturn (a, TxSkel)]
- runTweak :: Tweak InterpMockChain a -> TxSkel -> [MockChainReturn (a, TxSkel)]
- withTweak :: MonadModalBlockChain m => m x -> Tweak InterpMockChain a -> m x
- runUtxoSearch :: Monad m => UtxoSearch m a -> m [(TxOutRef, a)]
- allUtxosSearch :: MonadBlockChain m => UtxoSearch m TxSkelOut
- utxosOwnedBySearch :: (MonadBlockChainBalancing m, ToAddress addr) => addr -> UtxoSearch m TxSkelOut
- utxosFromCardanoTxSearch :: MonadBlockChainBalancing m => CardanoTx -> UtxoSearch m TxSkelOut
- txSkelOutByRefSearch :: MonadBlockChainBalancing m => [TxOutRef] -> UtxoSearch m TxSkelOut
- filterWith :: Monad m => UtxoSearch m a -> (a -> m (Maybe b)) -> UtxoSearch m b
- filterWithPure :: Monad m => UtxoSearch m a -> (a -> Maybe b) -> UtxoSearch m b
- filterWithOptic :: (Is k An_AffineFold, Monad m) => UtxoSearch m a -> Optic' k is a b -> UtxoSearch m b
- filterWithPred :: Monad m => UtxoSearch m a -> (a -> Bool) -> UtxoSearch m a
- filterWithValuePred :: Monad m => UtxoSearch m TxSkelOut -> (Value -> Bool) -> UtxoSearch m TxSkelOut
- filterWithOnlyAda :: Monad m => UtxoSearch m TxSkelOut -> UtxoSearch m TxSkelOut
- filterWithNotOnlyAda :: Monad m => UtxoSearch m TxSkelOut -> UtxoSearch m TxSkelOut
- onlyValueOutputsAtSearch :: (MonadBlockChainBalancing m, ToAddress addr) => addr -> UtxoSearch m TxSkelOut
- vanillaOutputsAtSearch :: (MonadBlockChainBalancing m, ToAddress addr) => addr -> UtxoSearch m TxSkelOut
- filterWithAlways :: Monad m => UtxoSearch m a -> (a -> b) -> UtxoSearch m b
- referenceScriptOutputsSearch :: (MonadBlockChain m, ToScriptHash s) => s -> UtxoSearch m TxSkelOut
- filterWithPureRev :: Monad m => UtxoSearch m a -> (a -> Maybe b) -> UtxoSearch m a
- holdsInState :: ToAddress a => a -> UtxoState -> Value
- printCookedOpt :: PrettyCooked a => PrettyCookedOpts -> a -> IO ()
- printCooked :: PrettyCooked a => a -> IO ()
- prettyHash :: ToHash a => PrettyCookedOpts -> a -> DocCooked
- prettyItemize :: PrettyCookedList a => PrettyCookedOpts -> DocCooked -> DocCooked -> a -> DocCooked
- prettyItemizeNoTitle :: PrettyCookedList a => PrettyCookedOpts -> DocCooked -> a -> DocCooked
- prettyItemizeNonEmpty :: PrettyCookedList a => PrettyCookedOpts -> DocCooked -> DocCooked -> a -> Maybe DocCooked
- hashNamesFromList :: ToHash a => [(a, String)] -> Map BuiltinByteString String
- defaultHashNames :: Map BuiltinByteString String
- addHashNames :: Map BuiltinByteString String -> PrettyCookedOpts -> PrettyCookedOpts
- txSkelLabelL :: Lens' TxSkel (Set TxSkelLabel)
- txSkelOptsL :: Lens' TxSkel TxSkelOpts
- txSkelMintsL :: Lens' TxSkel TxSkelMints
- txSkelValidityRangeL :: Lens' TxSkel SlotRange
- txSkelProposalsL :: Lens' TxSkel [TxSkelProposal]
- txSkelSignersL :: Lens' TxSkel [Wallet]
- txSkelInsL :: Lens' TxSkel (Map TxOutRef TxSkelRedeemer)
- txSkelInsReferenceL :: Lens' TxSkel (Set TxOutRef)
- txSkelOutsL :: Lens' TxSkel [TxSkelOut]
- txSkelWithdrawalsL :: Lens' TxSkel TxSkelWithdrawals
- txSkelTemplate :: TxSkel
- txSkelKnownTxOutRefs :: TxSkel -> Set TxOutRef
- txSkelWithdrawnValue :: TxSkel -> Value
- txSkelWithdrawingScripts :: TxSkel -> [Versioned Script]
- txSkelValueInOutputs :: TxSkel -> Value
- txSkelInsReferenceInRedeemers :: TxSkel -> Set TxOutRef
- txSkelProposingScripts :: TxSkel -> [Versioned Script]
- txSkelMintingScripts :: TxSkel -> [Versioned Script]
- datumKindResolvedP :: Prism' DatumKind DatumResolved
- txSkelOutDatumKindAT :: AffineTraversal' TxSkelOutDatum DatumKind
- txSkelOutDatumResolvedAT :: AffineTraversal' TxSkelOutDatum DatumResolved
- txSkelOutDatumTypedAT :: (DatumConstrs a, DatumConstrs b) => AffineTraversal TxSkelOutDatum TxSkelOutDatum a b
- txSkelOutDatumDatumAF :: AffineFold TxSkelOutDatum Datum
- txSkelOutDatumDatumHashAF :: AffineFold TxSkelOutDatum DatumHash
- txSkelOutDatumOutputDatumG :: Getter TxSkelOutDatum OutputDatum
- txSkelLabelTypedP :: LabelConstrs a => Prism' TxSkelLabel a
- mintRedeemerL :: Lens' Mint TxSkelRedeemer
- mintTokensL :: Lens' Mint [(TokenName, Integer)]
- mint :: ToVersioned MintingPolicy a => a -> TxSkelRedeemer -> TokenName -> Integer -> Mint
- burn :: ToVersioned MintingPolicy a => a -> TxSkelRedeemer -> TokenName -> Integer -> Mint
- txSkelMintsValueG :: Getter TxSkelMints Value
- txSkelMintsListI :: Iso' TxSkelMints [Mint]
- mintVersionedScriptL :: Lens' Mint (Versioned Script)
- txSkelMintsAssetClassAmountL :: ToVersioned MintingPolicy mp => mp -> TokenName -> Lens' TxSkelMints (Maybe TxSkelRedeemer, Integer)
- txSkelMintsFromList :: [Mint] -> TxSkelMints
- txSkelMintsValue :: TxSkelMints -> Value
- txSkelOptModTxL :: Lens' TxSkelOpts (Tx ConwayEra -> Tx ConwayEra)
- txSkelOptAutoSlotIncreaseL :: Lens' TxSkelOpts Bool
- txSkelOptBalancingPolicyL :: Lens' TxSkelOpts BalancingPolicy
- txSkelOptBalanceOutputPolicyL :: Lens' TxSkelOpts BalanceOutputPolicy
- txSkelOptFeePolicyL :: Lens' TxSkelOpts FeePolicy
- txSkelOptBalancingUtxosL :: Lens' TxSkelOpts BalancingUtxos
- txSkelOptModParamsL :: Lens' TxSkelOpts (Params -> Params)
- txSkelOptCollateralUtxosL :: Lens' TxSkelOpts CollateralUtxos
- txSkelOptAnchorResolutionL :: Lens' TxSkelOpts AnchorResolution
- txSkelOptAddModTx :: (Tx ConwayEra -> Tx ConwayEra) -> TxSkelOpts -> TxSkelOpts
- txSkelOptAddModParams :: (Params -> Params) -> TxSkelOpts -> TxSkelOpts
- receives :: OwnerConstrs owner => owner -> Payable els -> TxSkelOut
- txSkelOutValueL :: Lens' TxSkelOut Value
- txSkelOutValueAutoAdjustL :: Lens' TxSkelOut Bool
- txSkelOutDatumL :: Lens' TxSkelOut TxSkelOutDatum
- txSkelOutReferenceScriptL :: Lens' TxSkelOut TxSkelOutReferenceScript
- txSkelOutStakingCredentialL :: Lens' TxSkelOut (Maybe StakingCredential)
- txSkelOutValidatorAT :: AffineTraversal' TxSkelOut (Versioned Validator)
- txSkelOutCredentialG :: Getter TxSkelOut Credential
- txSkelOutAddressG :: Getter TxSkelOut Address
- txSkelOutPKHashAT :: AffineTraversal' TxSkelOut PubKeyHash
- txSkelOutTypedOwnerAT :: (OwnerConstrs a, OwnerConstrs b) => AffineTraversal TxSkelOut TxSkelOut a b
- txSkelOutValidatorHashAF :: AffineFold TxSkelOut ValidatorHash
- valueAssetClassAmountL :: ToMintingPolicyHash mp => mp -> TokenName -> Lens' Value Integer
- lovelaceIntegerI :: Iso' Lovelace Integer
- valueLovelaceL :: Lens' Value Lovelace
- valueAssetClassAmountP :: ToMintingPolicyHash mp => mp -> TokenName -> Prism' Value Integer
- valueLovelaceP :: Prism' Value Lovelace
- ownerCredentialG :: IsTxSkelOutAllowedOwner owner => Getter owner Credential
- txSkelProposalAddressL :: Lens' TxSkelProposal Address
- txSkelProposalActionL :: Lens' TxSkelProposal TxGovAction
- txSkelProposalWitnessL :: Lens' TxSkelProposal (Maybe (Versioned Script, TxSkelRedeemer))
- txSkelProposalAnchorL :: Lens' TxSkelProposal (Maybe String)
- txSkelProposalAutoConstitutionL :: Lens' TxSkelProposal Bool
- simpleTxSkelProposal :: ToAddress a => a -> TxGovAction -> TxSkelProposal
- withWitness :: ToVersioned Script a => TxSkelProposal -> (a, TxSkelRedeemer) -> TxSkelProposal
- withConstitution :: ToVersioned Script a => TxSkelProposal -> Maybe a -> TxSkelProposal
- updateConstitution :: ToVersioned Script a => TxSkelProposal -> Maybe a -> TxSkelProposal
- withReferenceInput :: TxSkelRedeemer -> TxOutRef -> TxSkelRedeemer
- someTxSkelRedeemer :: RedeemerConstrs redeemer => redeemer -> TxSkelRedeemer
- emptyTxSkelRedeemer :: TxSkelRedeemer
- txSkelRedeemerReferenceInputL :: Lens' TxSkelRedeemer (Maybe TxOutRef)
- txSkelRedeemerAutoFillL :: Lens' TxSkelRedeemer Bool
- txSkelRedeemerTypedAT :: (RedeemerConstrs a, RedeemerConstrs b) => AffineTraversal TxSkelRedeemer TxSkelRedeemer a b
- someTxSkelRedeemerNoAutoFill :: RedeemerConstrs redeemer => redeemer -> TxSkelRedeemer
- emptyTxSkelRedeemerNoAutoFill :: TxSkelRedeemer
- txSkelRedeemerBuiltinDataL :: Lens' TxSkelRedeemer BuiltinData
- txSkelOutReferenceScriptHashAF :: AffineFold TxSkelOutReferenceScript ScriptHash
- txSkelOutReferenceScriptTypedP :: (ReferenceScriptConstrs a, ReferenceScriptConstrs b) => Prism TxSkelOutReferenceScript TxSkelOutReferenceScript a b
- txSkelOutReferenceScriptVersionedP :: Prism' TxSkelOutReferenceScript (Versioned Script)
- pkWithdrawal :: ToPubKeyHash pkh => pkh -> Integer -> TxSkelWithdrawals
- scriptWithdrawal :: ToVersioned Script script => script -> TxSkelRedeemer -> Integer -> TxSkelWithdrawals
- failingTweak :: MonadTweak m => m a
- doNothingTweak :: MonadTweak m => m ()
- viewTweak :: (MonadTweak m, Is k A_Getter) => Optic' k is TxSkel a -> m a
- viewAllTweak :: (MonadTweak m, Is k A_Fold) => Optic' k is TxSkel a -> m [a]
- setTweak :: (MonadTweak m, Is k A_Setter) => Optic' k is TxSkel a -> a -> m ()
- overTweak :: (MonadTweak m, Is k A_Setter) => Optic' k is TxSkel a -> (a -> a) -> m ()
- overMaybeTweak :: (MonadTweak m, Is k A_Traversal) => Optic' k is TxSkel a -> (a -> Maybe a) -> m [a]
- overMaybeSelectingTweak :: forall a m k is. (MonadTweak m, Is k A_Traversal) => Optic' k is TxSkel a -> (a -> Maybe a) -> (Integer -> Bool) -> m [a]
- selectP :: (a -> Bool) -> Prism' a a
- combineModsTweak :: (Eq is, Is k A_Traversal, MonadTweak m) => ([is] -> [[is]]) -> Optic' k (WithIx is) TxSkel x -> (is -> x -> m [(x, l)]) -> m [l]
- iviewTweak :: (MonadTweak m, Is k A_Getter) => Optic' k (WithIx is) TxSkel a -> m (is, a)
- ensureInputTweak :: MonadTweak m => TxOutRef -> TxSkelRedeemer -> m (Maybe (TxOutRef, TxSkelRedeemer))
- addInputTweak :: MonadTweak m => TxOutRef -> TxSkelRedeemer -> m ()
- removeInputTweak :: MonadTweak m => (TxOutRef -> TxSkelRedeemer -> Bool) -> m [(TxOutRef, TxSkelRedeemer)]
- modifySpendRedeemersOfTypeTweak :: forall a b m. (RedeemerConstrs a, RedeemerConstrs b, MonadTweak m) => (a -> Maybe b) -> m [TxSkelRedeemer]
- addLabelTweak :: (MonadTweak m, LabelConstrs x) => x -> m ()
- removeLabelTweak :: (MonadTweak m, LabelConstrs x) => x -> m ()
- hasLabelTweak :: (MonadTweak m, LabelConstrs x) => x -> m Bool
- addMintsTweak :: MonadTweak m => [Mint] -> m ()
- removeMintTweak :: MonadTweak m => (Mint -> Bool) -> m [Mint]
- allOutPermutsTweak :: MonadTweak m => PermutOutTweakMode -> m ()
- singleOutPermutTweak :: MonadTweak m => Int -> m ()
- ensureOutputTweak :: MonadTweak m => TxSkelOut -> m (Maybe TxSkelOut)
- addOutputTweak :: MonadTweak m => TxSkelOut -> m ()
- removeOutputTweak :: MonadTweak m => (TxSkelOut -> Bool) -> m [TxSkelOut]
- tamperDatumTweak :: forall a m. (MonadTweak m, DatumConstrs a) => (a -> Maybe a) -> m [a]
- malformDatumTweak :: forall a m. (MonadTweak m, DatumConstrs a) => (a -> [BuiltinData]) -> m ()
- getSignersTweak :: MonadTweak m => m [Wallet]
- modifySignersTweak :: MonadTweak m => ([Wallet] -> [Wallet]) -> m [Wallet]
- setSignersTweak :: MonadTweak m => [Wallet] -> m [Wallet]
- signersSatisfyTweak :: MonadTweak m => ([Wallet] -> Bool) -> m Bool
- isSignerTweak :: MonadTweak m => Wallet -> m Bool
- hasSignersTweak :: MonadTweak m => m Bool
- addFirstSignerTweak :: MonadTweak m => Wallet -> m [Wallet]
- addSignersTweak :: MonadTweak m => [Wallet] -> m [Wallet]
- addLastSignerTweak :: MonadTweak m => Wallet -> m [Wallet]
- removeSignersTweak :: MonadTweak m => [Wallet] -> m [Wallet]
- removeSignerTweak :: MonadTweak m => Wallet -> m [Wallet]
- replaceFirstSignerTweak :: MonadTweak m => Wallet -> m [Wallet]
- getValidityRangeTweak :: MonadTweak m => m SlotRange
- knownWallets :: [Wallet]
- wallet :: Integer -> Wallet
- walletPKHashToId :: PubKeyHash -> Maybe Int
- walletPKHashToWallet :: PubKeyHash -> Maybe Wallet
- walletPK :: Wallet -> PubKey
- walletStakingPK :: Wallet -> Maybe PubKey
- walletStakingPKHash :: Wallet -> Maybe PubKeyHash
- walletSK :: Wallet -> XPrv
- walletStakingSK :: Wallet -> Maybe XPrv
- utxoPayloadSet :: UtxoPayloadSet -> [UtxoPayload]
- utxoPayloadTxOutRef :: UtxoPayload -> TxOutRef
- utxoPayloadValue :: UtxoPayload -> Value
- utxoPayloadDatum :: UtxoPayload -> UtxoPayloadDatum
- utxoPayloadReferenceScript :: UtxoPayload -> Maybe ScriptHash
- combineMockChainT :: (forall a. m a -> m a -> m a) -> MockChainT m x -> MockChainT m x -> MockChainT m x
- mcrValue :: MockChainReturn a -> Either MockChainError a
- mcrOutputs :: MockChainReturn a -> Map TxOutRef (TxSkelOut, Bool)
- mcrUtxoState :: MockChainReturn a -> UtxoState
- mcrJournal :: MockChainReturn a -> [MockChainLogEntry]
- mcrAliases :: MockChainReturn a -> Map BuiltinByteString String
- runMockChainTRaw :: Monad m => MockChainT m a -> m (MockChainReturn a)
- runMockChainTFrom :: Monad m => InitialDistribution -> MockChainT m a -> m (MockChainReturn a)
- runMockChainT :: Monad m => MockChainT m a -> m (MockChainReturn a)
- runMockChainFrom :: InitialDistribution -> MockChain a -> MockChainReturn a
- runMockChain :: MockChain a -> MockChainReturn a
- testBool :: IsProp prop => Bool -> prop
- testAll :: IsProp prop => (a -> prop) -> [a] -> prop
- testAny :: IsProp prop => (a -> prop) -> [a] -> prop
- assertionToMaybe :: Assertion -> IO (Maybe HUnitFailure)
- assertSubset :: (Show a, Eq a) => [a] -> [a] -> Assertion
- assertSameSets :: (Show a, Eq a) => [a] -> [a] -> Assertion
- testToProp :: (IsProp prop, Show a) => Test a prop -> prop
- testCooked :: Show a => String -> Test a Assertion -> TestTree
- testCookedQC :: Show a => String -> Test a Property -> TestTree
- mustSucceedTest :: IsProp prop => StagedMockChain a -> Test a prop
- mustFailTest :: IsProp prop => StagedMockChain a -> Test a prop
- withInitDist :: Test a prop -> InitialDistribution -> Test a prop
- withPrettyOpts :: Test a prop -> PrettyCookedOpts -> Test a prop
- withJournalProp :: IsProp prop => Test a prop -> JournalProp prop -> Test a prop
- withStateProp :: IsProp prop => Test a prop -> StateProp prop -> Test a prop
- withSuccessProp :: IsProp prop => Test a prop -> SuccessProp a prop -> Test a prop
- withResultProp :: IsProp prop => Test a prop -> (a -> prop) -> Test a prop
- withSizeProp :: IsProp prop => Test a prop -> SizeProp prop -> Test a prop
- withFailureProp :: IsProp prop => Test a prop -> FailureProp prop -> Test a prop
- withErrorProp :: IsProp prop => Test a prop -> (MockChainError -> prop) -> Test a prop
- isPhase1Failure :: IsProp prop => FailureProp prop
- isPhase2Failure :: IsProp prop => FailureProp prop
- isPhase1FailureWithMsg :: IsProp prop => String -> FailureProp prop
- isPhase2FailureWithMsg :: IsProp prop => String -> FailureProp prop
- isOfSize :: IsProp prop => Integer -> SizeProp prop
- isAtLeastOfSize :: IsProp prop => Integer -> SizeProp prop
- isAtMostOfSize :: IsProp prop => Integer -> SizeProp prop
- happened :: IsProp prop => String -> JournalProp prop
- didNotHappen :: IsProp prop => String -> JournalProp prop
- isInWallets :: IsProp prop => [(Wallet, [(AssetClass, Integer -> Bool)])] -> SuccessProp a prop
- isInWallet :: IsProp prop => (Wallet, AssetClass, Integer) -> SuccessProp a prop
- mustFailInPhase2Test :: IsProp prop => StagedMockChain a -> Test a prop
- mustFailInPhase2WithMsgTest :: IsProp prop => String -> StagedMockChain a -> Test a prop
- mustFailInPhase1Test :: IsProp prop => StagedMockChain a -> Test a prop
- mustFailInPhase1WithMsgTest :: IsProp prop => String -> StagedMockChain a -> Test a prop
- mustSucceedWithSizeTest :: IsProp prop => Integer -> StagedMockChain a -> Test a prop
- mustFailWithSizeTest :: IsProp prop => Integer -> StagedMockChain a -> Test a prop
- setValidityRangeTweak :: MonadTweak m => SlotRange -> m SlotRange
- setAlwaysValidRangeTweak :: MonadTweak m => m SlotRange
- setValidityStartTweak :: MonadTweak m => Slot -> m SlotRange
- setValidityEndTweak :: MonadTweak m => Slot -> m SlotRange
- validityRangeSatisfiesTweak :: MonadTweak m => (SlotRange -> Bool) -> m Bool
- isValidAtTweak :: MonadTweak m => Slot -> m Bool
- isValidNowTweak :: MonadTweak m => m Bool
- isValidDuringTweak :: MonadTweak m => SlotRange -> m Bool
- hasEmptyTimeRangeTweak :: MonadTweak m => m Bool
- hasFullTimeRangeTweak :: MonadTweak m => m Bool
- intersectValidityRangeTweak :: MonadTweak m => SlotRange -> m SlotRange
- centerAroundValidityRangeTweak :: MonadTweak m => Slot -> Integer -> m SlotRange
- makeValidityRangeSingletonTweak :: MonadTweak m => Slot -> m SlotRange
- makeValidityRangeNowTweak :: MonadTweak m => m SlotRange
- waitUntilValidTweak :: MonadTweak m => m Slot
Documentation
Data structure to test a mockchain trace. a
is the return typed of the
tested trace, prop
is the domain in which the properties live. This is not
enforced here, but it will often be assumed that prop
satisfies IsProp
.
Constructors
Test | |
Fields
|
type family (xs :: [a]) ∪ (ys :: [a]) :: [a] where ... Source #
type family (el :: a) ∉ (els :: [a]) :: Constraint where ... Source #
Constraint that a given type does not appear in a list of types
A description of a new entry to be added in a TxSkelMints
. The users
should be using lists of those (using txSkelMintsFromList
) instead of
building a TxSkelMints
directly.
Constructors
Mint | |
Fields
|
Instances
PrettyCooked Mint Source # | Prints a minting specification Example: > #abcdef - Redeemer: red - Reference script at: txOutRef - Foo: 500 - Bar: 1000 |
Defined in Cooked.Pretty.Skeleton Methods prettyCookedOpt :: PrettyCookedOpts -> Mint -> DocCooked Source # prettyCooked :: Mint -> DocCooked Source # |
Type of LTL formulas with atomic formulas of type a
. Think of a
as a
type of "modifications", then a value of type Ltl a
describes where to
apply modifications. Since it does not make (obvious) sense to talk of a
negated modification or of one modification (possibly in the future) to imply
another modification, implication and negation are absent.
Constructors
LtlTruth | The "do nothing" modification that never fails |
LtlFalsity | The modification that never applies (i.e. always fails) |
LtlAtom a | The modification that applies a given atomic modification at the | current time step |
LtlOr (Ltl a) (Ltl a) | Disjunction will be interpreted in an "intuitionistic" way, i.e. as branching into the "timeline" where the left disjunct holds and the one where the right disjunct holds. In that sense, it is an exclusive or, as it does not introduce the branch where both disjuncts hold. |
LtlAnd (Ltl a) (Ltl a) | Conjunction will be interpreted as "apply both modifications". Attention: The "apply both" operation will be user-defined for atomic modifications, so that conjunction may for example fail to be commutative if the operation on atomic modification is not commutative. |
LtlNext (Ltl a) | Assert that the given formula holds at the next time step. |
LtlUntil (Ltl a) (Ltl a) | Assert that the first formula holds at least until the second one begins to hold, which must happen eventually. The formulas a `LtlUntil` b and
> b are equivalent. |
LtlRelease (Ltl a) (Ltl a) | Assert that the second formula has to be true up to and including the
point when the first one becomes true; if that never happens, the second
formula has to remain true forever. View this as dual to a `LtlRelease` b and
> b are equivalent. |
data InitialDistribution where Source #
Describes the initial distribution of UTxOs per wallet. This is important
since transaction validation must specify a collateral. Hence, wallets must
have more than one UTxO to begin with in order to execute a transaction and
have some collateral option. The txCollateral
is transferred to the node
operator in case the transaction fails to validate.
The following specifies a starting state where wallet 1
owns two UTxOs,
one with 42 Ada and one with 2 Ada and one TOK token; wallet 2
owns a
single UTxO with 10 Ada and wallet 3
has 10 Ada and a permanent value. See
Cooked.Currencies for more information on quick and permanent values.
i0 = distributionFromList $ [ (wallet 1 , [ ada 42 , ada 2 <> quickValue "TOK" 1 ] , (wallet 2 , [ ada 10 ]) , (wallet 3 , [ ada 10 <> permanentValue "XYZ" 10]) ]
Note that initial distribution can lead to payments that would not be accepted if part of an actual transaction, such as payment without enough ada to sustain themselves.
Constructors
InitialDistribution | |
Fields
|
Instances
Monoid InitialDistribution Source # | |
Defined in Cooked.InitialDistribution Methods mempty :: InitialDistribution # mappend :: InitialDistribution -> InitialDistribution -> InitialDistribution # | |
Semigroup InitialDistribution Source # | |
Defined in Cooked.InitialDistribution Methods (<>) :: InitialDistribution -> InitialDistribution -> InitialDistribution # sconcat :: NonEmpty InitialDistribution -> InitialDistribution # stimes :: Integral b => b -> InitialDistribution -> InitialDistribution # | |
Default InitialDistribution Source # | 4 UTxOs with 100 Ada each, for each of the first 4 |
Defined in Cooked.InitialDistribution Methods |
class Monad m => MonadModal m where Source #
Monads that allow modifications with LTL formulas.
Associated Types
type Modification m :: Type Source #
Methods
modifyLtl :: Ltl (Modification m) -> m a -> m a Source #
Instances
MonadModal (Staged (LtlOp modification builtin)) Source # | |
type MockChain = MockChainT Identity Source #
analogue of Haskell's Show
class to be use in Plutus scripts.
Instances
type Wallet = MockWallet Source #
A Wallet
is a MockWallet
from plutus-ledger
data AddTokenLbl Source #
A label that is added to a TxSkel
that has successfully been modified by
addTokenAttack
Constructors
AddTokenLbl |
Instances
Show AddTokenLbl Source # | |
Defined in Cooked.Attack.AddToken Methods showsPrec :: Int -> AddTokenLbl -> ShowS # show :: AddTokenLbl -> String # showList :: [AddTokenLbl] -> ShowS # | |
PrettyCooked AddTokenLbl Source # | |
Defined in Cooked.Attack.AddToken Methods prettyCookedOpt :: PrettyCookedOpts -> AddTokenLbl -> DocCooked Source # prettyCooked :: AddTokenLbl -> DocCooked Source # | |
Eq AddTokenLbl Source # | |
Defined in Cooked.Attack.AddToken | |
Ord AddTokenLbl Source # | |
Defined in Cooked.Attack.AddToken Methods compare :: AddTokenLbl -> AddTokenLbl -> Ordering # (<) :: AddTokenLbl -> AddTokenLbl -> Bool # (<=) :: AddTokenLbl -> AddTokenLbl -> Bool # (>) :: AddTokenLbl -> AddTokenLbl -> Bool # (>=) :: AddTokenLbl -> AddTokenLbl -> Bool # max :: AddTokenLbl -> AddTokenLbl -> AddTokenLbl # min :: AddTokenLbl -> AddTokenLbl -> AddTokenLbl # |
newtype DatumHijackingLbl Source #
A label that is added to a TxSkel
that has successfully been modified by
any of the datum hijacking attacks
Constructors
DatumHijackingLbl Credential |
Instances
type DoubleSatDelta = (Map TxOutRef TxSkelRedeemer, [TxSkelOut], TxSkelMints) Source #
A triplet of transaction inputs, transaction outputs, and minted value. This is what we can add to the transaction in order to try a double satisfaction attack.
data DoubleSatLbl Source #
A label that is added to a TxSkel
that has successfully been modified by
the doubleSatAttack
Constructors
DoubleSatLbl |
Instances
Show DoubleSatLbl Source # | |
Defined in Cooked.Attack.DoubleSat Methods showsPrec :: Int -> DoubleSatLbl -> ShowS # show :: DoubleSatLbl -> String # showList :: [DoubleSatLbl] -> ShowS # | |
PrettyCooked DoubleSatLbl Source # | |
Defined in Cooked.Attack.DoubleSat Methods prettyCookedOpt :: PrettyCookedOpts -> DoubleSatLbl -> DocCooked Source # prettyCooked :: DoubleSatLbl -> DocCooked Source # | |
Eq DoubleSatLbl Source # | |
Defined in Cooked.Attack.DoubleSat | |
Ord DoubleSatLbl Source # | |
Defined in Cooked.Attack.DoubleSat Methods compare :: DoubleSatLbl -> DoubleSatLbl -> Ordering # (<) :: DoubleSatLbl -> DoubleSatLbl -> Bool # (<=) :: DoubleSatLbl -> DoubleSatLbl -> Bool # (>) :: DoubleSatLbl -> DoubleSatLbl -> Bool # (>=) :: DoubleSatLbl -> DoubleSatLbl -> Bool # max :: DoubleSatLbl -> DoubleSatLbl -> DoubleSatLbl # min :: DoubleSatLbl -> DoubleSatLbl -> DoubleSatLbl # |
data DupTokenLbl Source #
A label that is added to a TxSkel
that has successfully been modified by
the dupTokenAttack
Constructors
DupTokenLbl |
Instances
Show DupTokenLbl Source # | |
Defined in Cooked.Attack.DupToken Methods showsPrec :: Int -> DupTokenLbl -> ShowS # show :: DupTokenLbl -> String # showList :: [DupTokenLbl] -> ShowS # | |
PrettyCooked DupTokenLbl Source # | |
Defined in Cooked.Attack.DupToken Methods prettyCookedOpt :: PrettyCookedOpts -> DupTokenLbl -> DocCooked Source # prettyCooked :: DupTokenLbl -> DocCooked Source # | |
Eq DupTokenLbl Source # | |
Defined in Cooked.Attack.DupToken | |
Ord DupTokenLbl Source # | |
Defined in Cooked.Attack.DupToken Methods compare :: DupTokenLbl -> DupTokenLbl -> Ordering # (<) :: DupTokenLbl -> DupTokenLbl -> Bool # (<=) :: DupTokenLbl -> DupTokenLbl -> Bool # (>) :: DupTokenLbl -> DupTokenLbl -> Bool # (>=) :: DupTokenLbl -> DupTokenLbl -> Bool # max :: DupTokenLbl -> DupTokenLbl -> DupTokenLbl # min :: DupTokenLbl -> DupTokenLbl -> DupTokenLbl # |
data MockChainState Source #
The state used to run the simulation in Direct
Constructors
MockChainState | |
Fields
|
Instances
Show MockChainState Source # | |
Defined in Cooked.MockChain.MockChainState Methods showsPrec :: Int -> MockChainState -> ShowS # show :: MockChainState -> String # showList :: [MockChainState] -> ShowS # | |
Default MockChainState Source # | |
Defined in Cooked.MockChain.MockChainState Methods def :: MockChainState # | |
Monad m => MonadState MockChainState (MockChainT m) Source # | |
Defined in Cooked.MockChain.Direct Methods get :: MockChainT m MockChainState # put :: MockChainState -> MockChainT m () # state :: (MockChainState -> (a, MockChainState)) -> MockChainT m a # |
type UtxoSearch m a = ListT m (TxOutRef, a) Source #
If a UTxO is a TxOutRef
with some additional information, this type
captures a "stream" of UTxOs.
data MockChainError Source #
Errors that can be produced by the blockchain
Constructors
MCEValidationError ValidationPhase ValidationError | Validation errors, either in Phase 1 or Phase 2 |
MCEUnbalanceable Wallet Value | The balancing wallet does not have enough funds |
MCEMissingBalancingWallet String | The balancing wallet is required but missing |
MCENoSuitableCollateral Integer Integer Value | No suitable collateral could be associated with a skeleton |
MCEToCardanoError String ToCardanoError | Translating a skeleton element to its Cardano counterpart failed |
MCEWrongReferenceScriptError TxOutRef ScriptHash (Maybe ScriptHash) | The required reference script is missing from a witness utxo |
MCEUnknownOutRef TxOutRef | A UTxO is missing from the mockchain state |
MCEPastSlot Slot Slot | A jump in time would result in a past slot |
MCEUnsupportedFeature String | An attempt to invoke an unsupported feature has been made |
FailWith String | Used to provide |
Instances
class (MonadFail m, MonadError MockChainError m) => MonadBlockChainBalancing m where Source #
This is the first layer of our blockchain, which provides the minimal subset of primitives required to perform balancing.
Minimal complete definition
Methods
getParams :: m Params Source #
Returns the emulator parameters, including protocol parameters
utxosAt :: ToAddress a => a -> m [(TxOutRef, TxSkelOut)] Source #
Returns a list of all UTxOs at a certain address.
txSkelOutByRef :: TxOutRef -> m TxSkelOut Source #
Returns an output given a reference to it. If the output does not exist,
throws a MCEUnknownOutRef
error.
Instances
class MonadBlockChainBalancing m => MonadBlockChainWithoutValidation m where Source #
This is the second layer of our blockchain, which provides all the other
blockchain primitives not needed for balancing, except transaction
validation. This layers is the one where
Tweak
s are plugged to.
Methods
allUtxos :: m [(TxOutRef, TxSkelOut)] Source #
Returns a list of all currently known outputs.
setParams :: Params -> m () Source #
Updates parameters
waitNSlots :: Integral i => i -> m Slot Source #
Wait a certain amount of slot. Throws MCEPastSlot
if the input integer
is negative. Returns the slot after jumping in time.
define :: ToHash a => String -> a -> m a Source #
Binds a hashable quantity of type a
to a variable in the mockchain,
while registering its alias for printing purposes.
setConstitutionScript :: ToVersioned Script s => s -> m () Source #
Sets the current script to act as the official constitution script
getConstitutionScript :: m (Maybe (Versioned Script)) Source #
Gets the current official constitution script
registerStakingCred :: ToCredential c => c -> Integer -> Integer -> m () Source #
Registers a staking credential with a given reward and deposit
Instances
class MonadBlockChainWithoutValidation m => MonadBlockChain m where Source #
The final layer of our blockchain, adding transaction validation to the mix. This is the only primitive that actually modifies the ledger state.
Methods
validateTxSkel :: TxSkel -> m CardanoTx Source #
Generates, balances and validates a transaction from a skeleton. It returns the validated transaction and updates the state of the blockchain.
forceOutputs :: [TxSkelOut] -> m [TxOutRef] Source #
Forces the generation of utxos corresponding to certain TxSkelOut
Instances
newtype AsTrans t (m :: Type -> Type) a Source #
A newtype wrapper to be used with '-XDerivingVia' to derive instances of
MonadBlockChain
for any MonadTransControl
.
For example, to derive 'MonadBlockChain m => MonadBlockChain (ReaderT r m)', you'd write
deriving via (AsTrans (ReaderT r) m) instance MonadBlockChain m => MonadBlockChain (ReaderT r m)
and avoid the trouble of defining all the class methods yourself.
Instances
data MockChainBook Source #
This represents elements that can be emitted throughout a MockChain
run. These elements are either log entries corresponding to internal events
worth logging, or aliases for hashables corresponding to elements users
wishes to be properly displayed when printed with
PrettyCooked
Constructors
MockChainBook | |
Fields
|
Instances
Monoid MockChainBook Source # | |
Defined in Cooked.MockChain.Direct Methods mempty :: MockChainBook # mappend :: MockChainBook -> MockChainBook -> MockChainBook # mconcat :: [MockChainBook] -> MockChainBook # | |
Semigroup MockChainBook Source # | |
Defined in Cooked.MockChain.Direct Methods (<>) :: MockChainBook -> MockChainBook -> MockChainBook # sconcat :: NonEmpty MockChainBook -> MockChainBook # stimes :: Integral b => b -> MockChainBook -> MockChainBook # | |
Monad m => MonadWriter MockChainBook (MockChainT m) Source # | |
Defined in Cooked.MockChain.Direct Methods writer :: (a, MockChainBook) -> MockChainT m a # tell :: MockChainBook -> MockChainT m () # listen :: MockChainT m a -> MockChainT m (a, MockChainBook) # pass :: MockChainT m (a, MockChainBook -> MockChainBook) -> MockChainT m a # |
type MonadModalBlockChain m = (MonadBlockChain m, MonadModal m, Modification m ~ UntypedTweak InterpMockChain) Source #
A modal mock chain is a mock chain that allows us to use LTL modifications
with Tweak
s
class IsProp prop where Source #
IsProp
is a common interface for HUnit and QuickCheck tests. It abstracts
uses of Assertion
and Property
for (IsProp prop) => prop
, then
provide instances for both HU.Asserton
and QC.Property
.
Minimal complete definition
Methods
testCounterexample :: String -> prop -> prop Source #
Displays the string to the user in case of failure
testConjoin :: [prop] -> prop Source #
Conjunction of a number of results
testDisjoin :: [prop] -> prop Source #
Disjunction of a number of results
testFailure :: prop Source #
Flags a failure
testSuccess :: prop Source #
Flags a success
testFailureMsg :: String -> prop Source #
Flags a failure with a message
Instances
IsProp Property Source # | QuickCheck instance of |
Defined in Cooked.MockChain.Testing Methods testCounterexample :: String -> Property -> Property Source # testConjoin :: [Property] -> Property Source # testDisjoin :: [Property] -> Property Source # testFailure :: Property Source # testSuccess :: Property Source # testFailureMsg :: String -> Property Source # | |
IsProp Assertion Source # | HUnit instance of |
Defined in Cooked.MockChain.Testing Methods testCounterexample :: String -> Assertion -> Assertion Source # testConjoin :: [Assertion] -> Assertion Source # testDisjoin :: [Assertion] -> Assertion Source # testFailure :: Assertion Source # testSuccess :: Assertion Source # testFailureMsg :: String -> Assertion Source # |
data UtxoPayloadDatum where Source #
A simplified version of a TxSkelOutDatum
which only
stores the actual datum and whether it is hashed or inline.
Constructors
NoUtxoPayloadDatum :: UtxoPayloadDatum | |
SomeUtxoPayloadDatum :: DatumConstrs dat => dat -> Bool -> UtxoPayloadDatum |
Instances
Show UtxoPayloadDatum Source # | |
Defined in Cooked.MockChain.UtxoState Methods showsPrec :: Int -> UtxoPayloadDatum -> ShowS # show :: UtxoPayloadDatum -> String # showList :: [UtxoPayloadDatum] -> ShowS # | |
Eq UtxoPayloadDatum Source # | |
Defined in Cooked.MockChain.UtxoState Methods (==) :: UtxoPayloadDatum -> UtxoPayloadDatum -> Bool # (/=) :: UtxoPayloadDatum -> UtxoPayloadDatum -> Bool # | |
Ord UtxoPayloadDatum Source # | |
Defined in Cooked.MockChain.UtxoState Methods compare :: UtxoPayloadDatum -> UtxoPayloadDatum -> Ordering # (<) :: UtxoPayloadDatum -> UtxoPayloadDatum -> Bool # (<=) :: UtxoPayloadDatum -> UtxoPayloadDatum -> Bool # (>) :: UtxoPayloadDatum -> UtxoPayloadDatum -> Bool # (>=) :: UtxoPayloadDatum -> UtxoPayloadDatum -> Bool # max :: UtxoPayloadDatum -> UtxoPayloadDatum -> UtxoPayloadDatum # min :: UtxoPayloadDatum -> UtxoPayloadDatum -> UtxoPayloadDatum # |
class PrettyCooked a where Source #
Type class of things that can be pretty printed as a single document. You
need to implement either prettyCookedOpt
or prettyCooked
manually,
otherwise calling either of them will resulting in a infinite loop.
Minimal complete definition
Nothing
Methods
prettyCookedOpt :: PrettyCookedOpts -> a -> DocCooked Source #
Pretty prints an element based on some PrettyCookedOpts
prettyCooked :: a -> DocCooked Source #
Pretty prints an element directly
Instances
class PrettyCookedList a where Source #
Type class of things that can be pretty printed as a list of
documents. Similarly to PrettyCooked
, at least of the functions from this
class needs to be manually implemented to avoid infinite loops.
Minimal complete definition
Nothing
Methods
prettyCookedOptList :: PrettyCookedOpts -> a -> [DocCooked] Source #
Pretty prints an element as a list on some PrettyCookedOpts
prettyCookedOptListMaybe :: PrettyCookedOpts -> a -> [Maybe DocCooked] Source #
Pretty prints an element as a list of optional documents
prettyCookedList :: a -> [DocCooked] Source #
Pretty prints an elements as a list
Instances
class PrettyCookedMaybe a where Source #
Type class of things that can be optionally pretty printed as a document
Minimal complete definition
Nothing
Methods
prettyCookedOptMaybe :: PrettyCookedOpts -> a -> Maybe DocCooked Source #
Pretty prints an optional document on some PrettyCookedOpts
prettyCookedMaybe :: a -> Maybe DocCooked Source #
Pretty prints an option document
Instances
PrettyCookedMaybe TxSkelOutDatum Source # | Prints a |
Defined in Cooked.Pretty.Skeleton Methods prettyCookedOptMaybe :: PrettyCookedOpts -> TxSkelOutDatum -> Maybe DocCooked Source # prettyCookedMaybe :: TxSkelOutDatum -> Maybe DocCooked Source # | |
PrettyCookedMaybe (Maybe DocCooked) Source # | |
Defined in Cooked.Pretty.Class Methods prettyCookedOptMaybe :: PrettyCookedOpts -> Maybe DocCooked -> Maybe DocCooked Source # prettyCookedMaybe :: Maybe DocCooked -> Maybe DocCooked Source # |
Hashable elements can be transformed to BuiltinByteString
Methods
toHash :: a -> BuiltinByteString Source #
Instances
data PrettyCookedOpts Source #
A set of option to pilot pretty printing in cooked-validators
Constructors
PrettyCookedOpts | |
Fields
|
Instances
Show PrettyCookedOpts Source # | |
Defined in Cooked.Pretty.Options Methods showsPrec :: Int -> PrettyCookedOpts -> ShowS # show :: PrettyCookedOpts -> String # showList :: [PrettyCookedOpts] -> ShowS # | |
Default PrettyCookedOpts Source # | |
Defined in Cooked.Pretty.Options Methods def :: PrettyCookedOpts # | |
Eq PrettyCookedOpts Source # | |
Defined in Cooked.Pretty.Options Methods (==) :: PrettyCookedOpts -> PrettyCookedOpts -> Bool # (/=) :: PrettyCookedOpts -> PrettyCookedOpts -> Bool # |
data PrettyCookedHashOpts Source #
A set of options to pilot how hashes are pretty printed
Constructors
PrettyCookedHashOpts | |
Fields
|
Instances
Show PrettyCookedHashOpts Source # | |
Defined in Cooked.Pretty.Options Methods showsPrec :: Int -> PrettyCookedHashOpts -> ShowS # show :: PrettyCookedHashOpts -> String # showList :: [PrettyCookedHashOpts] -> ShowS # | |
Default PrettyCookedHashOpts Source # | |
Defined in Cooked.Pretty.Options Methods | |
Eq PrettyCookedHashOpts Source # | |
Defined in Cooked.Pretty.Options Methods (==) :: PrettyCookedHashOpts -> PrettyCookedHashOpts -> Bool # (/=) :: PrettyCookedHashOpts -> PrettyCookedHashOpts -> Bool # |
data PCOptTxOutRefs Source #
Whether to print transaction outputs references.
Constructors
PCOptTxOutRefsHidden | Hide them |
PCOptTxOutRefsFull | Always show them. Warning: this will disable printing similar UTxOs as a group (for
instance |
PCOptTxOutRefsPartial | Show them for UTxOs which are not grouped with similar others. This
avoids the downside of |
Instances
Show PCOptTxOutRefs Source # | |
Defined in Cooked.Pretty.Options Methods showsPrec :: Int -> PCOptTxOutRefs -> ShowS # show :: PCOptTxOutRefs -> String # showList :: [PCOptTxOutRefs] -> ShowS # | |
Eq PCOptTxOutRefs Source # | |
Defined in Cooked.Pretty.Options Methods (==) :: PCOptTxOutRefs -> PCOptTxOutRefs -> Bool # (/=) :: PCOptTxOutRefs -> PCOptTxOutRefs -> Bool # |
A transaction skeleton. This is cooked-validators's variant of transaction
bodies, eventually translated to Cardano TxBody
.
Constructors
TxSkel | |
Fields
|
Instances
Show TxSkel Source # | |
Eq TxSkel Source # | |
PrettyCookedList (Contextualized TxSkel) Source # | Prints a |
Defined in Cooked.Pretty.Skeleton Methods prettyCookedOptList :: PrettyCookedOpts -> Contextualized TxSkel -> [DocCooked] Source # prettyCookedOptListMaybe :: PrettyCookedOpts -> Contextualized TxSkel -> [Maybe DocCooked] Source # prettyCookedList :: Contextualized TxSkel -> [DocCooked] Source # | |
MonadBlockChainWithoutValidation m => MonadTweak (Tweak m) Source # | |
data Payable :: [Symbol] -> Type where Source #
Payable elements. Created from concrete elements or composed. Notice that
there is no way of building an element of Type Payable '[]
so when using an
element of Type Payable els
we are sure that something was in fact paid.
Constructors
VisibleHashedDatum :: DatumConstrs a => a -> Payable '["Datum"] | Hashed datums visible in the transaction are payable |
InlineDatum :: DatumConstrs a => a -> Payable '["Datum"] | Inline datums are payable |
HiddenHashedDatum :: DatumConstrs a => a -> Payable '["Datum"] | Hashed datums hidden from the transaction are payable |
ReferenceScript :: ReferenceScriptConstrs s => s -> Payable '["Reference Script"] | Reference scripts are payable |
Value :: ToValue a => a -> Payable '["Value"] | Values are payable and are subject to min ada adjustment |
FixedValue :: ToValue a => a -> Payable '["Value"] | Fixed Values are payable but are NOT subject to min ada adjustment |
StakingCredential :: ToMaybeStakingCredential cred => cred -> Payable '["Staking Credential"] | Staking credentials are payable |
PayableAnd :: els ⩀ els' => Payable els -> Payable els' -> Payable (els ∪ els') | Payables can be combined as long as their list of tags are disjoint |
type DatumConstrs datum = (Show datum, PrettyCooked datum, ToData datum, FromData datum, Eq datum, Typeable datum) Source #
Type constraints that must be satisfied by the datum content
data DatumResolved Source #
Whether the datum should be resolved in the transaction
Constructors
NotResolved | Do not resolve the datum (absent from |
Resolved | Resolve the datum (present from |
Instances
Show DatumResolved Source # | |
Defined in Cooked.Skeleton.Datum Methods showsPrec :: Int -> DatumResolved -> ShowS # show :: DatumResolved -> String # showList :: [DatumResolved] -> ShowS # | |
Eq DatumResolved Source # | |
Defined in Cooked.Skeleton.Datum Methods (==) :: DatumResolved -> DatumResolved -> Bool # (/=) :: DatumResolved -> DatumResolved -> Bool # | |
Ord DatumResolved Source # | |
Defined in Cooked.Skeleton.Datum Methods compare :: DatumResolved -> DatumResolved -> Ordering # (<) :: DatumResolved -> DatumResolved -> Bool # (<=) :: DatumResolved -> DatumResolved -> Bool # (>) :: DatumResolved -> DatumResolved -> Bool # (>=) :: DatumResolved -> DatumResolved -> Bool # max :: DatumResolved -> DatumResolved -> DatumResolved # min :: DatumResolved -> DatumResolved -> DatumResolved # |
Options on how to include the datum in the transaction
Constructors
Inline | Include the full datum in the UTxO |
Hashed DatumResolved | Only include the datum hash in the UTxO. Resolve, or do not resolve, the full datum in the transaction body. |
Instances
Show DatumKind Source # | |
Eq DatumKind Source # | |
Ord DatumKind Source # | |
data TxSkelOutDatum where Source #
Datums to be placed in TxSkel
outputs, which are either
empty, or composed of a datum content and its placement
Constructors
NoTxSkelOutDatum :: TxSkelOutDatum | use no datum |
SomeTxSkelOutDatum :: DatumConstrs dat => dat -> DatumKind -> TxSkelOutDatum | use some datum content and associated placement |
Instances
type LabelConstrs x = (PrettyCooked x, Show x, Typeable x, Eq x, Ord x) Source #
These are type constraints that must be satisfied by labels
data TxSkelLabel where Source #
Labels are arbitrary information that can be added to skeleton. They are meant to be pretty-printed. The common use case we currently have is to tag skeletons that have been modified by tweaks and automated attacks.
Constructors
TxSkelLabel :: LabelConstrs x => x -> TxSkelLabel |
Instances
Show TxSkelLabel Source # | |
Defined in Cooked.Skeleton.Label Methods showsPrec :: Int -> TxSkelLabel -> ShowS # show :: TxSkelLabel -> String # showList :: [TxSkelLabel] -> ShowS # | |
PrettyCooked TxSkelLabel Source # | |
Defined in Cooked.Skeleton.Label Methods prettyCookedOpt :: PrettyCookedOpts -> TxSkelLabel -> DocCooked Source # prettyCooked :: TxSkelLabel -> DocCooked Source # | |
Eq TxSkelLabel Source # | |
Defined in Cooked.Skeleton.Label | |
Ord TxSkelLabel Source # | |
Defined in Cooked.Skeleton.Label Methods compare :: TxSkelLabel -> TxSkelLabel -> Ordering # (<) :: TxSkelLabel -> TxSkelLabel -> Bool # (<=) :: TxSkelLabel -> TxSkelLabel -> Bool # (>) :: TxSkelLabel -> TxSkelLabel -> Bool # (>=) :: TxSkelLabel -> TxSkelLabel -> Bool # max :: TxSkelLabel -> TxSkelLabel -> TxSkelLabel # min :: TxSkelLabel -> TxSkelLabel -> TxSkelLabel # |
type TxSkelMints = Map (Versioned MintingPolicy) (TxSkelRedeemer, NEMap TokenName (NonZero Integer)) Source #
A description of what a transaction mints. For every policy, there can only
be one TxSkelRedeemer
, and if there is, there must be some token names, each
with a non-zero amount of tokens.
You'll probably not construct this by hand, but use txSkelMintsFromList
.
data BalanceOutputPolicy Source #
Whether to adjust a potentially existing output to the balancing wallet with the change during transaction balancing.
Constructors
AdjustExistingOutput | Try to adjust an existing public key output with the change. If no suitable output can be found, create a new change output. |
DontAdjustExistingOutput | Do not change the existing outputs, always create a new change output. |
Instances
What fee policy to use in the transaction.
Constructors
AutoFeeComputation | Use automatic fee computation. If balancing is activated, an optimal fee will be computed based on the transaction and existing utxos in the balancing wallet. Otherwise, the maximum transaction fee will be applied. |
ManualFee Integer | Provide a fee to the transaction. If the autobalancing is activated, it will be attempted around this fee, which might lead to failure if it is too low, otherwise, this fee will be given to transaction generation. |
Instances
Show FeePolicy Source # | |
Default FeePolicy Source # | |
Defined in Cooked.Skeleton.Option | |
Eq FeePolicy Source # | |
Ord FeePolicy Source # | |
data BalancingPolicy Source #
Whether to balance the transaction or not, and which wallet to use to provide outputs for balancing.
Constructors
BalanceWithFirstSigner | Balance with the first signer of the list of signers |
BalanceWith Wallet | Balance using a given wallet |
DoNotBalance | Do not perform balancing at all |
Instances
Show BalancingPolicy Source # | |
Defined in Cooked.Skeleton.Option Methods showsPrec :: Int -> BalancingPolicy -> ShowS # show :: BalancingPolicy -> String # showList :: [BalancingPolicy] -> ShowS # | |
Default BalancingPolicy Source # | |
Defined in Cooked.Skeleton.Option Methods def :: BalancingPolicy # | |
Eq BalancingPolicy Source # | |
Defined in Cooked.Skeleton.Option Methods (==) :: BalancingPolicy -> BalancingPolicy -> Bool # (/=) :: BalancingPolicy -> BalancingPolicy -> Bool # | |
Ord BalancingPolicy Source # | |
Defined in Cooked.Skeleton.Option Methods compare :: BalancingPolicy -> BalancingPolicy -> Ordering # (<) :: BalancingPolicy -> BalancingPolicy -> Bool # (<=) :: BalancingPolicy -> BalancingPolicy -> Bool # (>) :: BalancingPolicy -> BalancingPolicy -> Bool # (>=) :: BalancingPolicy -> BalancingPolicy -> Bool # max :: BalancingPolicy -> BalancingPolicy -> BalancingPolicy # min :: BalancingPolicy -> BalancingPolicy -> BalancingPolicy # |
data BalancingUtxos Source #
Which UTxOs to use when balancing. Note that utxos that are already known
by the skeleton being balanced (in the sense of
txSkelKnownTxOutRefs
, i.e. inputs and reference inputs)
will be filtered out during balancing.
Constructors
BalancingUtxosFromBalancingWallet | Use all UTxOs containing only a Value (no datum, no staking credential, and no reference script) belonging to the balancing wallet. |
BalancingUtxosFromSet (Set TxOutRef) | Use the provided UTxOs. UTxOs belonging to scripts will be filtered out |
Instances
Show BalancingUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods showsPrec :: Int -> BalancingUtxos -> ShowS # show :: BalancingUtxos -> String # showList :: [BalancingUtxos] -> ShowS # | |
Default BalancingUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods def :: BalancingUtxos # | |
Eq BalancingUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods (==) :: BalancingUtxos -> BalancingUtxos -> Bool # (/=) :: BalancingUtxos -> BalancingUtxos -> Bool # | |
Ord BalancingUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods compare :: BalancingUtxos -> BalancingUtxos -> Ordering # (<) :: BalancingUtxos -> BalancingUtxos -> Bool # (<=) :: BalancingUtxos -> BalancingUtxos -> Bool # (>) :: BalancingUtxos -> BalancingUtxos -> Bool # (>=) :: BalancingUtxos -> BalancingUtxos -> Bool # max :: BalancingUtxos -> BalancingUtxos -> BalancingUtxos # min :: BalancingUtxos -> BalancingUtxos -> BalancingUtxos # |
data CollateralUtxos Source #
Describe which UTxOs to use as collaterals
Constructors
CollateralUtxosFromBalancingWallet | Rely on automated computation with only-value UTxOs from the balancing wallet. Return collaterals will be sent to this wallet. |
CollateralUtxosFromWallet Wallet | Rely on automated computation with only-value UTxOs from a given wallet. Return collaterals will be sent to this wallet. |
CollateralUtxosFromSet (Set TxOutRef) Wallet | Manually provide a set of candidate UTxOs to be used as collaterals alongside a wallet to send return collaterals back to. |
Instances
Show CollateralUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods showsPrec :: Int -> CollateralUtxos -> ShowS # show :: CollateralUtxos -> String # showList :: [CollateralUtxos] -> ShowS # | |
Default CollateralUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods def :: CollateralUtxos # | |
Eq CollateralUtxos Source # | |
Defined in Cooked.Skeleton.Option Methods (==) :: CollateralUtxos -> CollateralUtxos -> Bool # (/=) :: CollateralUtxos -> CollateralUtxos -> Bool # |
data AnchorResolution Source #
Describes how to resolve anchors in proposal procedures
Constructors
AnchorResolutionLocal (Map String ByteString) | Provide a map between urls and page content as Bytestring |
AnchorResolutionHttp | Allow online fetch of pages from a given URL. Important note: using this option is unsafe, as it requires a web connection and inherently prevents guarantees of reproducibily. Use at your own discretion. |
Instances
Show AnchorResolution Source # | |
Defined in Cooked.Skeleton.Option Methods showsPrec :: Int -> AnchorResolution -> ShowS # show :: AnchorResolution -> String # showList :: [AnchorResolution] -> ShowS # | |
Default AnchorResolution Source # | |
Defined in Cooked.Skeleton.Option Methods def :: AnchorResolution # | |
Eq AnchorResolution Source # | |
Defined in Cooked.Skeleton.Option Methods (==) :: AnchorResolution -> AnchorResolution -> Bool # (/=) :: AnchorResolution -> AnchorResolution -> Bool # |
data TxSkelOpts Source #
Set of options to modify the behavior of generating and validating some transaction.
Constructors
TxSkelOpts | |
Fields
|
Instances
A rich output to be put into a TxSkel
Constructors
TxSkelOut | |
Fields
|
Instances
class IsTxSkelOutAllowedOwner a where Source #
A TxSkelOut
can either be owned by a pubkeyhash or a versioned validator
Methods
toPKHOrValidator :: a -> Either PubKeyHash (Versioned Validator) Source #
Instances
type OwnerConstrs owner = (IsTxSkelOutAllowedOwner owner, Typeable owner, Show owner) Source #
Type constraints over the owner of a TxSkelOut
type family (els :: [a]) ⩀ (els' :: [a]) :: Constraint where ... Source #
Disjoint lists of types
data TxParameterChange where Source #
These are all the protocol parameters. They are taken from https://github.com/IntersectMBO/cardano-ledger/blob/c4fbc05999866fea7c0cb1b211fd5288f286b95d/eras/conway/impl/cddl-files/conway.cddl#L381-L412 and will most likely change in future eras.
Constructors
Instances
Show TxParameterChange Source # | |
Defined in Cooked.Skeleton.Proposal Methods showsPrec :: Int -> TxParameterChange -> ShowS # show :: TxParameterChange -> String # showList :: [TxParameterChange] -> ShowS # | |
PrettyCooked TxParameterChange Source # | |
Defined in Cooked.Pretty.Skeleton Methods prettyCookedOpt :: PrettyCookedOpts -> TxParameterChange -> DocCooked Source # | |
Eq TxParameterChange Source # | |
Defined in Cooked.Skeleton.Proposal Methods (==) :: TxParameterChange -> TxParameterChange -> Bool # (/=) :: TxParameterChange -> TxParameterChange -> Bool # |
data TxGovAction where Source #
This lists the various possible governance actions
Constructors
Instances
Show TxGovAction Source # | |
Defined in Cooked.Skeleton.Proposal Methods showsPrec :: Int -> TxGovAction -> ShowS # show :: TxGovAction -> String # showList :: [TxGovAction] -> ShowS # | |
PrettyCooked TxGovAction Source # | |
Defined in Cooked.Pretty.Skeleton Methods prettyCookedOpt :: PrettyCookedOpts -> TxGovAction -> DocCooked Source # prettyCooked :: TxGovAction -> DocCooked Source # | |
Eq TxGovAction Source # | |
Defined in Cooked.Skeleton.Proposal |
data TxSkelProposal where Source #
This bundles a governance action into an actual proposal
Constructors
TxSkelProposal | |
Fields
|
Instances
Show TxSkelProposal Source # | |
Defined in Cooked.Skeleton.Proposal Methods showsPrec :: Int -> TxSkelProposal -> ShowS # show :: TxSkelProposal -> String # showList :: [TxSkelProposal] -> ShowS # | |
PrettyCookedList TxSkelProposal Source # | |
Defined in Cooked.Pretty.Skeleton Methods prettyCookedOptList :: PrettyCookedOpts -> TxSkelProposal -> [DocCooked] Source # prettyCookedOptListMaybe :: PrettyCookedOpts -> TxSkelProposal -> [Maybe DocCooked] Source # prettyCookedList :: TxSkelProposal -> [DocCooked] Source # | |
Eq TxSkelProposal Source # | |
Defined in Cooked.Skeleton.Proposal Methods (==) :: TxSkelProposal -> TxSkelProposal -> Bool # (/=) :: TxSkelProposal -> TxSkelProposal -> Bool # |
data TxSkelRedeemer where Source #
A bundle around a redeemer which allows to provide a reference input in which the script associated with the redeemer can be found
Constructors
TxSkelRedeemer | |
Fields
|
Instances
type RedeemerConstrs redeemer = (ToData redeemer, FromData redeemer, Show redeemer, PrettyCooked redeemer, Eq redeemer, Typeable redeemer) Source #
These are the constraints that must be satisfied by the inner content of a redeemer, that is the actual data that will be passed to the script as its redeemer during during validation
type ReferenceScriptConstrs refScript = (ToVersioned Script refScript, Typeable refScript) Source #
Reference scripts are typeable and can be converted to versioned scripts.
data TxSkelOutReferenceScript where Source #
Reference scripts used in TxSkelOut
Constructors
NoTxSkelOutReferenceScript :: TxSkelOutReferenceScript | |
SomeTxSkelOutReferenceScript :: ReferenceScriptConstrs a => a -> TxSkelOutReferenceScript |
Instances
Show TxSkelOutReferenceScript Source # | |
Defined in Cooked.Skeleton.ReferenceScript Methods showsPrec :: Int -> TxSkelOutReferenceScript -> ShowS # show :: TxSkelOutReferenceScript -> String # showList :: [TxSkelOutReferenceScript] -> ShowS # | |
Eq TxSkelOutReferenceScript Source # | |
Defined in Cooked.Skeleton.ReferenceScript Methods (==) :: TxSkelOutReferenceScript -> TxSkelOutReferenceScript -> Bool # (/=) :: TxSkelOutReferenceScript -> TxSkelOutReferenceScript -> Bool # |
type TxSkelWithdrawals = Map (Either (Versioned Script) PubKeyHash) (TxSkelRedeemer, Lovelace) Source #
Withdrawals associate either a script or a private key with a redeemer and a certain amount of ada. Note that the redeemer will be ignored in the case of a private key.
class (MonadPlus m, MonadBlockChainWithoutValidation m) => MonadTweak m where Source #
A MonadTweak
is a MonadBlockChainWithoutValidation
where you can also
retrieve and store a TxSkel
data PermutOutTweakMode Source #
Output permutation policy
Constructors
KeepIdentity (Maybe Int) | |
OmitIdentity (Maybe Int) |
data TamperDatumLbl Source #
A label added to a TxSkel
on which the tamperDatumTweak
has been
successfully applied
Constructors
TamperDatumLbl |
Instances
Show TamperDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods showsPrec :: Int -> TamperDatumLbl -> ShowS # show :: TamperDatumLbl -> String # showList :: [TamperDatumLbl] -> ShowS # | |
PrettyCooked TamperDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods prettyCookedOpt :: PrettyCookedOpts -> TamperDatumLbl -> DocCooked Source # | |
Eq TamperDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods (==) :: TamperDatumLbl -> TamperDatumLbl -> Bool # (/=) :: TamperDatumLbl -> TamperDatumLbl -> Bool # | |
Ord TamperDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods compare :: TamperDatumLbl -> TamperDatumLbl -> Ordering # (<) :: TamperDatumLbl -> TamperDatumLbl -> Bool # (<=) :: TamperDatumLbl -> TamperDatumLbl -> Bool # (>) :: TamperDatumLbl -> TamperDatumLbl -> Bool # (>=) :: TamperDatumLbl -> TamperDatumLbl -> Bool # max :: TamperDatumLbl -> TamperDatumLbl -> TamperDatumLbl # min :: TamperDatumLbl -> TamperDatumLbl -> TamperDatumLbl # |
data MalformDatumLbl Source #
A label added to a TxSkel
on which the malformDatumTweak
has been
successfully applied
Constructors
MalformDatumLbl |
Instances
Show MalformDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods showsPrec :: Int -> MalformDatumLbl -> ShowS # show :: MalformDatumLbl -> String # showList :: [MalformDatumLbl] -> ShowS # | |
PrettyCooked MalformDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods prettyCookedOpt :: PrettyCookedOpts -> MalformDatumLbl -> DocCooked Source # | |
Eq MalformDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods (==) :: MalformDatumLbl -> MalformDatumLbl -> Bool # (/=) :: MalformDatumLbl -> MalformDatumLbl -> Bool # | |
Ord MalformDatumLbl Source # | |
Defined in Cooked.Tweak.Outputs Methods compare :: MalformDatumLbl -> MalformDatumLbl -> Ordering # (<) :: MalformDatumLbl -> MalformDatumLbl -> Bool # (<=) :: MalformDatumLbl -> MalformDatumLbl -> Bool # (>) :: MalformDatumLbl -> MalformDatumLbl -> Bool # (>=) :: MalformDatumLbl -> MalformDatumLbl -> Bool # max :: MalformDatumLbl -> MalformDatumLbl -> MalformDatumLbl # min :: MalformDatumLbl -> MalformDatumLbl -> MalformDatumLbl # |
newtype MockChainT m a Source #
A MockChainT
builds up a stack of monads on top of a given monad m
to
reflect the requirements of the simulation. It writes a MockChainBook
,
updates and reads from a MockChainState
and throws possible
MockChainError
s.
Constructors
MockChainT | |
Fields |
Instances
type FailureProp prop = PrettyCookedOpts -> [MockChainLogEntry] -> MockChainError -> UtxoState -> prop Source #
Type of properties over failures
type SuccessProp a prop = PrettyCookedOpts -> [MockChainLogEntry] -> a -> UtxoState -> prop Source #
Type of properties over successes
type SizeProp prop = Integer -> prop Source #
Type of properties over the number of run outcomes. This does not
necessitate a PrettyCookedOpts
as parameter as an Integer
does not
contain anything significant that can be pretty printed.
type JournalProp prop = PrettyCookedOpts -> [MockChainLogEntry] -> prop Source #
Type of properties over the mockchain journal
type StateProp prop = PrettyCookedOpts -> UtxoState -> prop Source #
Type of properties over the UtxoState
pattern MCLogSubmittedTxSkel :: TxSkel -> MockChainLogEntry Source #
Logging a Skeleton as it is submitted by the user.
pattern MCLogAdjustedTxSkel :: TxSkel -> Integer -> Maybe (Set TxOutRef, Wallet) -> MockChainLogEntry Source #
Logging a Skeleton as it has been adjusted by the balancing mechanism, alongside fee, and possible collateral utxos and return collateral wallet.
pattern MCLogNewTx :: TxId -> Integer -> MockChainLogEntry Source #
Logging the successful validation of a new transaction, with its id and number of produced outputs.
pattern MCLogDiscardedUtxos :: Integer -> String -> MockChainLogEntry Source #
Logging the fact that utxos provided by the user for balancing have to be discarded for a specific reason.
pattern MCLogUnusedCollaterals :: Either Wallet (Set TxOutRef) -> MockChainLogEntry Source #
Logging the fact that utxos provided as collaterals will not be used because the transaction does not involve scripts. There are 2 cases, depending on whether the user has provided an explicit wallet or a set of utxos to be used as collaterals.
pattern MCLogAddedReferenceScript :: TxSkelRedeemer -> TxOutRef -> ScriptHash -> MockChainLogEntry Source #
Logging the automatic addition of a reference script
pattern MCLogAdjustedTxSkelOut :: TxSkelOut -> Lovelace -> MockChainLogEntry Source #
Logging the automatic adjusment of a min ada amount
renderString :: (a -> DocCooked) -> a -> String Source #
Use this to convert a pretty-printer to a regular show function using default layout options. This is used in Testing because Tasty uses strings.
currentSlot :: MonadBlockChainWithoutValidation m => m Slot Source #
Returns the current slot number
awaitSlot :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m Slot Source #
Wait for a certain slot, or throws an error if the slot is already past
(<&&>) :: els ⩀ els' => Payable els -> Payable els' -> Payable (els ∪ els') Source #
An infix-usable alias for PayableAnd
there :: MonadModalBlockChain m => Integer -> Tweak InterpMockChain b -> m a -> m a Source #
Apply a Tweak
to the (0-indexed) nth transaction in a given
trace. Successful when this transaction exists and can be modified.
everywhere :: MonadModalBlockChain m => Tweak InterpMockChain b -> m a -> m a Source #
Apply a Tweak
to every transaction in a given trace. This is also
successful if there are no transactions at all.
somewhere :: MonadModalBlockChain m => Tweak InterpMockChain b -> m a -> m a Source #
Apply a Tweak
to some transaction in the given Trace. The tweak must
apply at least once.
withAnchor :: TxSkelProposal -> String -> TxSkelProposal Source #
Assigns an anchor to a TxSkelProposal
Arguments
:: (MonadTweak m, OwnerConstrs o) | |
=> (Versioned MintingPolicy -> [(TokenName, Integer)]) | For each policy that occurs in some |
-> o | The wallet of the attacker where extra tokens will be paid to |
-> m Value |
This attack adds extra tokens, depending on the minting policy. It is
different from the dupTokenAttack
in that it does
not merely try to increase the amount of tokens minted: It tries to mint
tokens of asset classes that were not necessarily present on the unmodified
transaction.
This attack adds an AddTokenLbl
label.
redirectOutputTweakAny :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => (TxSkelOut -> Maybe owner') -> (Integer -> Bool) -> m TxSkelOut Source #
A version of redirectOutputTweakAll
where, instead of modifying all the
outputs targeted by the input predicates in the same transaction, we modify
one of them at a time, relying on the MonadPlus
instance of m
.
datumHijackingAttackAny Source #
Arguments
:: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') | |
=> (TxSkelOut -> Bool) | Predicate to select outputs to steal, depending on the intended recipient, the datum, and the value. |
-> (Integer -> Bool) | The selection predicate may match more than one output. Use this predicate to restrict to the i-th of the outputs (counting from the left, starting at zero) chosen by the selection predicate with this predicate. |
-> owner' | The thief |
-> m TxSkelOut |
A version of datumHijackingAttackAll relying on the rules of
redirectOutputTweakAny
.
datumHijackingAttack :: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') => owner' -> m TxSkelOut Source #
The default datum hijacking attack. It tries to redirect any output for
which the owner is of type owner
and branches at each attempt.
redirectOutputTweakAll Source #
Arguments
:: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') | |
=> (TxSkelOut -> Maybe owner') | Return |
-> (Integer -> Bool) | The redirection described by the previous argument might apply to more than one of the outputs of the transaction. Use this predicate to select which of the redirectable outputs to actually redirect. We count the redirectable outputs from the left to the right, starting with zero. |
-> m [TxSkelOut] | Returns the list of outputs it redirected (as they were before the modification), in the order in which they occurred on the original transaction. |
Redirects some outputs from one owner to another owner, which can be of different types.
datumHijackingAttackAll Source #
Arguments
:: forall owner owner' m. (MonadTweak m, OwnerConstrs owner, OwnerConstrs owner') | |
=> (TxSkelOut -> Bool) | Predicate to select outputs to steal, depending on the intended recipient, the datum, and the value. |
-> (Integer -> Bool) | The selection predicate may match more than one output. Use this predicate to restrict to the i-th of the outputs (counting from the left, starting at zero) chosen by the selection predicate with this predicate. |
-> owner' | The thief |
-> m [TxSkelOut] |
A datum hijacking attack, simplified: This attack tries to substitute a
different recipient on outputs belonging to scripts, but leaves the datum as
it is. That is, it tests for careless uses of something like
txInfoOutputs
in places where something like getContinuingOutputs
should be used. If this attack goes through, however, a "proper" datum
hijacking attack that modifies the datum in a way that (the relevant part of)
the toBuiltinData
-translation stays the same will also work.
A DatumHijackingLbl
with the hash of the "thief" validator is added to the
labels of the TxSkel
using addLabelTweak
.
This attack returns the list of outputs it redirected, in the order in which they occurred on the original transaction. If no output is redirected, this attack fails.
Arguments
:: (MonadTweak m, Eq is, Is k A_Traversal) | |
=> ([is] -> [[is]]) | how to combine modifications from caused by different foci. See the
comment at |
-> Optic' k (WithIx is) TxSkel a | Each focus of this optic is a potential reason to add some extra constraints. |
-> (is -> a -> m [(a, DoubleSatDelta)]) | How to change each focus, and which inputs, outputs, and mints to add, for each of the foci. There might be different options for each focus, that's why the return value is a list. Continuing the example, for each of the focused script outputs, you might want to try adding some script inputs to the transaction. Since it might be interesting to try different redeemers on these extra script inputs, you can just provide a list of all the options you want to try adding for a given script output that's already on the transaction. ################################### ATTENTION: If you modify the state while computing these lists, the
behaviour of the TODO: Make this interface safer, for example by using (some kind of) an
################################### |
-> Wallet | The wallet of the attacker, where any surplus is paid to. In the example, the extra value in the added input will be paid to the attacker. |
-> m () |
Double satisfaction attack. See the comment above for what such an attack is about conceptually.
This attack consists in adding some extra constraints to a transaction, and hoping that the additional minting policies or validator scripts thereby involved are fooled by what's already present on the transaction. Any extra value contained in new inputs to the transaction is then paid to the attacker.
Arguments
:: (MonadTweak m, OwnerConstrs o) | |
=> (AssetClass -> Integer -> Integer) | A function describing how the amount of tokens specified by a |
-> o | The wallet of the attacker. Any additional tokens that are minted by the modified transaction but were not minted by the original transaction are paid to this wallet. |
-> m Value |
A token duplication attack increases values in Mint
constraints of a
TxSkel
according to some conditions, and pays the extra minted value to a
given recipient wallet. This adds a DupTokenLbl
to the labels of the
transaction using addLabelTweak
. Returns the Value
by which the minted
value was increased.
distributionFromList :: [(Wallet, [Value])] -> InitialDistribution Source #
Creating a initial distribution with simple values assigned to wallets
balanceTxSkel :: MonadBlockChainBalancing m => TxSkel -> m (TxSkel, Integer, Maybe (Set TxOutRef, Wallet)) Source #
This is the main entry point of our balancing mechanism. This function takes a skeleton and returns a (possibly) balanced skeleton alongside the associated fee, collateral inputs and return collateral wallet, which might be empty when no script is involved in the transaction. The options from the skeleton control whether it should be balanced, and how to compute its associated elements.
getMinAndMaxFee :: MonadBlockChainBalancing m => Integer -> m (Integer, Integer) Source #
This computes the minimum and maximum possible fee a transaction can cost based on the current protocol parameters and its number of scripts.
estimateTxSkelFee :: MonadBlockChainBalancing m => TxSkel -> Integer -> Maybe (Set TxOutRef, Wallet) -> m Integer Source #
This function was originally inspired by https://github.com/input-output-hk/plutus-apps/blob/d4255f05477fd8477ee9673e850ebb9ebb8c9657/plutus-ledger/src/Ledger/Fee.hs#L19
currentMSRange :: MonadBlockChainWithoutValidation m => m (POSIXTime, POSIXTime) Source #
Returns the closed ms interval corresponding to the current slot
utxosFromCardanoTx :: MonadBlockChainBalancing m => CardanoTx -> m [(TxOutRef, TxSkelOut)] Source #
getEnclosingSlot :: MonadBlockChainWithoutValidation m => POSIXTime -> m Slot Source #
Return the slot that contains the given time. See slotToMSRange
for
some satisfied equational properties.
awaitEnclosingSlot :: MonadBlockChainWithoutValidation m => POSIXTime -> m Slot Source #
Waits until the current slot becomes greater or equal to the slot containing the given POSIX time. Note that that it might not wait for anything if the current slot is large enough.
waitNMSFromSlotLowerBound :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m Slot Source #
Wait a given number of ms from the lower bound of the current slot and returns the current slot after waiting.
waitNMSFromSlotUpperBound :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m Slot Source #
Wait a given number of ms from the upper bound of the current slot and returns the current slot after waiting.
slotRangeBefore :: MonadBlockChainWithoutValidation m => POSIXTime -> m SlotRange Source #
The infinite range of slots ending before or at the given time
slotRangeAfter :: MonadBlockChainWithoutValidation m => POSIXTime -> m SlotRange Source #
The infinite range of slots starting after or at the given time
slotToMSRange :: (MonadBlockChainWithoutValidation m, Integral i) => i -> m (POSIXTime, POSIXTime) Source #
Returns the closed ms interval corresponding to the slot with the given number. It holds that
slotToMSRange (getEnclosingSlot t) == (a, b) ==> a <= t <= b
and
slotToMSRange n == (a, b) ==> getEnclosingSlot a == n && getEnclosingSlot b == n
and
slotToMSRange n == (a, b) ==> getEnclosingSlot (a-1) == n-1 && getEnclosingSlot (b+1) == n+1
txSkelInputValidators :: MonadBlockChainBalancing m => TxSkel -> m [Versioned Validator] Source #
Returns all validators which guard transaction inputs
txSkelInputValue :: MonadBlockChainBalancing m => TxSkel -> m Value Source #
look up the UTxOs the transaction consumes, and sum their values.
lookupUtxos :: MonadBlockChainBalancing m => [TxOutRef] -> m (Map TxOutRef TxSkelOut) Source #
Go through all of the TxOutRef
s in the list and look them up in the
state of the blockchain, throwing an error if one of them cannot be resolved.
validateTxSkel' :: MonadBlockChain m => TxSkel -> m [TxOutRef] Source #
Validates a skeleton, and retuns the ordered list of produced output references
validateTxSkel_ :: MonadBlockChain m => TxSkel -> m () Source #
Validates a skeleton, and erases the outputs
txSkelProposalsDeposit :: MonadBlockChainBalancing m => TxSkel -> m Lovelace Source #
Retrieves the total amount of lovelace deposited in proposals in this
skeleton (equal to govActionDeposit
times the number of proposals).
govActionDeposit :: MonadBlockChainBalancing m => m Lovelace Source #
Retrieves the required deposit amount for issuing governance actions.
defineM :: (MonadBlockChainWithoutValidation m, ToHash a) => String -> m a -> m a Source #
Like define
, but binds the result of a monadic computation instead
txSkelAllScripts :: MonadBlockChainBalancing m => TxSkel -> m [Versioned Script] Source #
Returns all scripts involved in this TxSkel
previewByRef :: (MonadBlockChainBalancing m, Is af An_AffineFold) => Optic' af is TxSkelOut c -> TxOutRef -> m (Maybe c) Source #
Retrieves an output and previews a specific element out of it
viewByRef :: (MonadBlockChainBalancing m, Is g A_Getter) => Optic' g is TxSkelOut c -> TxOutRef -> m c Source #
Retrieves an output and views a specific element out of it
toTxSkelOutWithMinAda :: MonadBlockChainBalancing m => TxSkelOut -> m TxSkelOut Source #
This transforms an output into another output which contains the minimal required ada. If the previous quantity of ADA was sufficient, it remains unchanged. This can require a few iterations to converge, as the added ADA will increase the size of the UTXO which in turn might need more ADA.
toTxSkelWithMinAda :: MonadBlockChainBalancing m => TxSkel -> m TxSkel Source #
This goes through all the TxSkelOut
s of the given skeleton and updates
their ada value when requested by the user and required by the protocol
parameters.
getTxSkelOutMinAda :: MonadBlockChainBalancing m => TxSkelOut -> m Integer Source #
Compute the required minimal ADA for a given output
interpretAndRunWith :: (forall m. Monad m => MockChainT m a -> m res) -> StagedMockChain a -> [res] Source #
Interprets the staged mockchain then runs the resulting computation with a
custom function. This can be used, for example, to supply a custom
InitialDistribution
by providing runMockChainTFrom
.
interpretAndRun :: StagedMockChain a -> [MockChainReturn a] Source #
Same as interpretAndRunWith
but using runMockChainT
as the default way
to run the computation.
runTweakFrom :: InitialDistribution -> Tweak InterpMockChain a -> TxSkel -> [MockChainReturn (a, TxSkel)] Source #
Runs a Tweak
from a given TxSkel
and InitialDistribution
within a
mockchain
runTweak :: Tweak InterpMockChain a -> TxSkel -> [MockChainReturn (a, TxSkel)] Source #
withTweak :: MonadModalBlockChain m => m x -> Tweak InterpMockChain a -> m x Source #
Apply a Tweak
to the next transaction in the given trace. The order of
arguments is reversed compared to somewhere
and everywhere
, because that
enables an idiom like
do ... endpoint arguments `withTweak` someModification ...
where endpoint
builds and validates a single transaction depending on the
given arguments
. Then withTweak
says "I want to modify the transaction
returned by this endpoint in the following way".
runUtxoSearch :: Monad m => UtxoSearch m a -> m [(TxOutRef, a)] Source #
Given a UTxO search, we can run it to obtain a list of UTxOs.
allUtxosSearch :: MonadBlockChain m => UtxoSearch m TxSkelOut Source #
utxosOwnedBySearch :: (MonadBlockChainBalancing m, ToAddress addr) => addr -> UtxoSearch m TxSkelOut Source #
utxosFromCardanoTxSearch :: MonadBlockChainBalancing m => CardanoTx -> UtxoSearch m TxSkelOut Source #
txSkelOutByRefSearch :: MonadBlockChainBalancing m => [TxOutRef] -> UtxoSearch m TxSkelOut Source #
filterWith :: Monad m => UtxoSearch m a -> (a -> m (Maybe b)) -> UtxoSearch m b Source #
Transform a UtxoSearch
by applying a possibly partial monadic
transformation on each output in the stream
filterWithPure :: Monad m => UtxoSearch m a -> (a -> Maybe b) -> UtxoSearch m b Source #
Same as filterWith
but with a pure transformation
filterWithOptic :: (Is k An_AffineFold, Monad m) => UtxoSearch m a -> Optic' k is a b -> UtxoSearch m b Source #
Some as filterWithPure
, but the transformation is taken from an optic
filterWithPred :: Monad m => UtxoSearch m a -> (a -> Bool) -> UtxoSearch m a Source #
Same as filterWithPure
but the outputs are selected using a boolean
predicate, and not modified
filterWithValuePred :: Monad m => UtxoSearch m TxSkelOut -> (Value -> Bool) -> UtxoSearch m TxSkelOut Source #
A specific version of filterWithPred
where outputs must me of type
TxSkelOut
and the predicate only relies on their value
filterWithOnlyAda :: Monad m => UtxoSearch m TxSkelOut -> UtxoSearch m TxSkelOut Source #
A specific version of filterWithValuePred
when TxSkelOut
s are only kept
when they contain only ADA
filterWithNotOnlyAda :: Monad m => UtxoSearch m TxSkelOut -> UtxoSearch m TxSkelOut Source #
A specific version of filterWithValuePred
when TxSkelOut
s are only kept
when they contain non-ADA assets
onlyValueOutputsAtSearch :: (MonadBlockChainBalancing m, ToAddress addr) => addr -> UtxoSearch m TxSkelOut Source #
Search for UTxOs at a specific address, which only carry address and value information (no datum, staking credential, or reference script).
vanillaOutputsAtSearch :: (MonadBlockChainBalancing m, ToAddress addr) => addr -> UtxoSearch m TxSkelOut Source #
Same as onlyValueOutputsAtSearch
, but also ensures the returned outputs
do not contain non-ADA assets. These "vanilla" outputs are perfect candidates
to be used for balancing transaction and attaching collaterals.
filterWithAlways :: Monad m => UtxoSearch m a -> (a -> b) -> UtxoSearch m b Source #
Some as filterWithPure
but with a total transformation
referenceScriptOutputsSearch :: (MonadBlockChain m, ToScriptHash s) => s -> UtxoSearch m TxSkelOut Source #
Searches for all outputs containing a given script as reference script
filterWithPureRev :: Monad m => UtxoSearch m a -> (a -> Maybe b) -> UtxoSearch m a Source #
Same as filterWithPure
but inverses the predicate
holdsInState :: ToAddress a => a -> UtxoState -> Value Source #
Total value accessible to what's pointed by the address.
printCookedOpt :: PrettyCooked a => PrettyCookedOpts -> a -> IO () Source #
Use this in the REPL as an alternative to the default print
function when
dealing with pretty-printable cooked values.
For example, printCookedOpt def runMockChain i0 foo
printCooked :: PrettyCooked a => a -> IO () Source #
Version of printCookedOpt
that uses default pretty printing options.
prettyHash :: ToHash a => PrettyCookedOpts -> a -> DocCooked Source #
Pretty prints hashable elements based on pcOptHashes
in the
PrettyCookedOpts
. This cannot be made an instance as it would be
undecidable (the hope was (ToHash a) => PrettyCooked a
)
prettyItemize :: PrettyCookedList a => PrettyCookedOpts -> DocCooked -> DocCooked -> a -> DocCooked Source #
Print an item list with a title
>>>
prettyCookedOpts opts "Foo" "-" ["bar1", "bar2", "bar3"]
Foo - bar1 - bar2 - bar3
prettyItemizeNoTitle :: PrettyCookedList a => PrettyCookedOpts -> DocCooked -> a -> DocCooked Source #
Print an item list without a title
prettyItemizeNonEmpty :: PrettyCookedList a => PrettyCookedOpts -> DocCooked -> DocCooked -> a -> Maybe DocCooked Source #
Print an item list with a title, but only when the list is non-empty
hashNamesFromList :: ToHash a => [(a, String)] -> Map BuiltinByteString String Source #
Smart constructor for maps to be used in the "pcOptHashNames" pretty-printing option.
defaultHashNames :: Map BuiltinByteString String Source #
Default hash to names map that assigns Lovelace, Quick, and Permanent to the associated currency symbols. This is used as the default for the pretty-printing option and is recommended to use as a basis to extend with custom names.
addHashNames :: Map BuiltinByteString String -> PrettyCookedOpts -> PrettyCookedOpts Source #
Adds some additional names to these pretty cooked options. This has two practical use cases:
- Users can use it in conjuction to
hashNamesFromList
without having to remember to manually invokedefaultHashNames
- We use it internally to account for names that have been registered during
mockchain runs, such as for names that depend on on-chain data, typically a
TxOutRef
.
txSkelLabelL :: Lens' TxSkel (Set TxSkelLabel) Source #
A lens to set of get labels from a TxSkel
txSkelOptsL :: Lens' TxSkel TxSkelOpts Source #
A lens to set of get options from a TxSkel
txSkelMintsL :: Lens' TxSkel TxSkelMints Source #
A lens to set of get the minted value of a TxSkel
txSkelValidityRangeL :: Lens' TxSkel SlotRange Source #
A lens to set of get the validity range of a TxSkel
txSkelProposalsL :: Lens' TxSkel [TxSkelProposal] Source #
A lens to set of get proposals from a TxSkel
txSkelInsL :: Lens' TxSkel (Map TxOutRef TxSkelRedeemer) Source #
A lens to set of get inputs from a TxSkel
txSkelInsReferenceL :: Lens' TxSkel (Set TxOutRef) Source #
A lens to set of get reference inputs from a TxSkel
txSkelWithdrawalsL :: Lens' TxSkel TxSkelWithdrawals Source #
A lens to set of get withdrawals from a TxSkel
txSkelTemplate :: TxSkel Source #
A convenience template of an empty transaction skeleton.
txSkelKnownTxOutRefs :: TxSkel -> Set TxOutRef Source #
All TxOutRef
s known by a given transaction skeleton. This includes
TxOutRef`s used as inputs of the skeleton and TxOutRef
s used as reference
inputs of the skeleton. This does not include additional possible
TxOutRef
s used for balancing and additional TxOutRef
s used as collateral
inputs, as they are not part of the skeleton.
txSkelWithdrawingScripts :: TxSkel -> [Versioned Script] Source #
Returns all the scripts involved in withdrawals in this TxSkel
txSkelValueInOutputs :: TxSkel -> Value Source #
Returns the full value contained in the skeleton outputs
txSkelInsReferenceInRedeemers :: TxSkel -> Set TxOutRef Source #
All TxOutRef
s in reference inputs from redeemers
txSkelProposingScripts :: TxSkel -> [Versioned Script] Source #
Returns all the scripts involved in proposals in this TxSkel
txSkelMintingScripts :: TxSkel -> [Versioned Script] Source #
Returns all the scripts involved in minting in this TxSkel
datumKindResolvedP :: Prism' DatumKind DatumResolved Source #
Builds a DatumKind
from a DatumResolved
or optionally retrieves it
txSkelOutDatumKindAT :: AffineTraversal' TxSkelOutDatum DatumKind Source #
Extracts or changes the DatumKind
of a TxSkelOutDatum
txSkelOutDatumResolvedAT :: AffineTraversal' TxSkelOutDatum DatumResolved Source #
Extracts or changes the DatumResolved
of a TxSkelOutDatum
txSkelOutDatumTypedAT :: (DatumConstrs a, DatumConstrs b) => AffineTraversal TxSkelOutDatum TxSkelOutDatum a b Source #
Extracts, or sets, the typed datum of a TxSkelOutDatum
. This is attempted
in two ways: first, we try to simply cast the content, and then, if it fails,
we serialise the content and then attempt to deserialise it to the right
type. This second case is specifically useful when the current content is an
BuiltinData
itself directly, but it can also be used in the cornercase
when both types have compatible serialized representation.
txSkelOutDatumDatumAF :: AffineFold TxSkelOutDatum Datum Source #
Converts a TxSkelOutDatum
into a possible Datum
txSkelOutDatumDatumHashAF :: AffineFold TxSkelOutDatum DatumHash Source #
Converts a TxSkelOutDatum
into a possible DatumHash
txSkelOutDatumOutputDatumG :: Getter TxSkelOutDatum OutputDatum Source #
Converts a TxSkelOutDatum
into an OutputDatum
txSkelLabelTypedP :: LabelConstrs a => Prism' TxSkelLabel a Source #
A prism to create a label and retrieve a typed content
mintRedeemerL :: Lens' Mint TxSkelRedeemer Source #
A lens to set or get the redeemer of a Mint
mintTokensL :: Lens' Mint [(TokenName, Integer)] Source #
A lens to set or get the token list of a Mint
mint :: ToVersioned MintingPolicy a => a -> TxSkelRedeemer -> TokenName -> Integer -> Mint Source #
Builds some Mint
when a single type of token is minted for a given MP
burn :: ToVersioned MintingPolicy a => a -> TxSkelRedeemer -> TokenName -> Integer -> Mint Source #
Similar to mint
but deducing the tokens instead
txSkelMintsValueG :: Getter TxSkelMints Value Source #
The value described by a TxSkelMints
txSkelMintsListI :: Iso' TxSkelMints [Mint] Source #
Seeing a TxSkelMints
as a list of Mint
mintVersionedScriptL :: Lens' Mint (Versioned Script) Source #
A lens to set or get the versioned script of a Mint
txSkelMintsAssetClassAmountL :: ToVersioned MintingPolicy mp => mp -> TokenName -> Lens' TxSkelMints (Maybe TxSkelRedeemer, Integer) Source #
Sets or gets the amount of tokens minted for a certain asset class,
represented by a token name and a versioned minting policy. This removes the
appropriate entries (the token entry, and possible the mp entry if it would
leave it empty) when setting the amount to 0. This function is very similar
to valueAssetClassAmountL
but it also involves the
TxSkelRedeemer
associated with the minting policy.
This Lens is quite involved and is the main way to build TxSkelMints
iteratively from a list of Mint
(see txSkelMintsListI
). If you're looking
for simpler optics working in a TxSkelMints
, consider using ix mp % _1
for instance to modify an existing redeemer, or ix mp % _2 % ix tk
to
modify a token amount. Another option is to use the optics working on Mint
and combining them with txSkelMintsListI
.
txSkelMintsFromList :: [Mint] -> TxSkelMints Source #
This builds a TxSkelMints
from a list of Mint
, which should be the main
way of declaring minted values in a TxSkel
.
txSkelMintsValue :: TxSkelMints -> Value Source #
This retrieves the Value
from a TxSkelMints
txSkelOptModTxL :: Lens' TxSkelOpts (Tx ConwayEra -> Tx ConwayEra) Source #
A lens to get or set the Cardano transaction modifications option
txSkelOptAutoSlotIncreaseL :: Lens' TxSkelOpts Bool Source #
A lens to get or set the automatic slot increase option
txSkelOptBalancingPolicyL :: Lens' TxSkelOpts BalancingPolicy Source #
A lens to get or set the balancing policy option
txSkelOptBalanceOutputPolicyL :: Lens' TxSkelOpts BalanceOutputPolicy Source #
A lens to get or set the handling of balancing outputs option
txSkelOptFeePolicyL :: Lens' TxSkelOpts FeePolicy Source #
A lens to get or set the fee policy option
txSkelOptBalancingUtxosL :: Lens' TxSkelOpts BalancingUtxos Source #
A lens to get or set the balancing utxos option
txSkelOptModParamsL :: Lens' TxSkelOpts (Params -> Params) Source #
A lens to get or set the changes to protocol parameters option
txSkelOptCollateralUtxosL :: Lens' TxSkelOpts CollateralUtxos Source #
A lens to get or set the collateral utxos option
txSkelOptAnchorResolutionL :: Lens' TxSkelOpts AnchorResolution Source #
A lens to get or set the anchor resolution option
txSkelOptAddModTx :: (Tx ConwayEra -> Tx ConwayEra) -> TxSkelOpts -> TxSkelOpts Source #
Appends a transaction modification to the given TxSkelOpts
txSkelOptAddModParams :: (Params -> Params) -> TxSkelOpts -> TxSkelOpts Source #
Appends a parameters modification to the given TxSkelOpts
receives :: OwnerConstrs owner => owner -> Payable els -> TxSkelOut Source #
Smart constructor to build a TxSkelOut
from an owner and payment. This
should be the main way of building outputs.
txSkelOutValueAutoAdjustL :: Lens' TxSkelOut Bool Source #
A lens to get or set if the value can be auto-adjusted if needed
txSkelOutDatumL :: Lens' TxSkelOut TxSkelOutDatum Source #
A lens to get or set the TxSkelOutDatum
from a TxSkelOut
txSkelOutReferenceScriptL :: Lens' TxSkelOut TxSkelOutReferenceScript Source #
A lens to get or set the TxSkelOutReferenceScript
from a TxSkelOut
txSkelOutStakingCredentialL :: Lens' TxSkelOut (Maybe StakingCredential) Source #
A lens to get or set the 'Maybe Api.StakingCredential' from a TxSkelOut
txSkelOutValidatorAT :: AffineTraversal' TxSkelOut (Versioned Validator) Source #
Returns the optional validator owning a given TxSkelOut
txSkelOutCredentialG :: Getter TxSkelOut Credential Source #
Returns the credential of this TxSkelOut
txSkelOutPKHashAT :: AffineTraversal' TxSkelOut PubKeyHash Source #
Returns the optional private key owning a given TxSkelOut
txSkelOutTypedOwnerAT :: (OwnerConstrs a, OwnerConstrs b) => AffineTraversal TxSkelOut TxSkelOut a b Source #
Attempts to retrieve or set a typed owner from this TxSkelOut
txSkelOutValidatorHashAF :: AffineFold TxSkelOut ValidatorHash Source #
Returns the optional validator hash owning a given TxSkelOut
valueAssetClassAmountL :: ToMintingPolicyHash mp => mp -> TokenName -> Lens' Value Integer Source #
A lens to get or set the amount of tokens of a certain AssetClass
from a given Value
. This removes the entry if the new amount is 0.
valueAssetClassAmountP :: ToMintingPolicyHash mp => mp -> TokenName -> Prism' Value Integer Source #
A prism to build a value from an asset class and amount, or retrieves the amount from this asset class if it is not zero
valueLovelaceP :: Prism' Value Lovelace Source #
An instance of valueAssetClassAmountP
for Lovelace
ownerCredentialG :: IsTxSkelOutAllowedOwner owner => Getter owner Credential Source #
Retrieves the credential of a TxSkelOut
allowed owner
txSkelProposalAddressL :: Lens' TxSkelProposal Address Source #
A lens to get or set the address of a TxSkelProposal
txSkelProposalActionL :: Lens' TxSkelProposal TxGovAction Source #
A lens to get or set the governance action of a TxSkelProposal
txSkelProposalWitnessL :: Lens' TxSkelProposal (Maybe (Versioned Script, TxSkelRedeemer)) Source #
A lens to get or set the witness of a TxSkelProposal
txSkelProposalAnchorL :: Lens' TxSkelProposal (Maybe String) Source #
A lens to get or set the anchor of a TxSkelProposal
txSkelProposalAutoConstitutionL :: Lens' TxSkelProposal Bool Source #
A lens to get or set the anchor of a TxSkelProposal
simpleTxSkelProposal :: ToAddress a => a -> TxGovAction -> TxSkelProposal Source #
Builds a TxSkelProposal
from an address and a TxGovAction
withWitness :: ToVersioned Script a => TxSkelProposal -> (a, TxSkelRedeemer) -> TxSkelProposal Source #
Assigns a witness to a TxSkelProposal
. Also turns off the auto
constitution flag, so that this witness is not overridden.
withConstitution :: ToVersioned Script a => TxSkelProposal -> Maybe a -> TxSkelProposal Source #
Assigns the constitution script with an empty redeemer
updateConstitution :: ToVersioned Script a => TxSkelProposal -> Maybe a -> TxSkelProposal Source #
Updates the constitution if txSkelProposalAutoConstitution
is True
withReferenceInput :: TxSkelRedeemer -> TxOutRef -> TxSkelRedeemer Source #
Attaches a reference input to a given TxSkelRedeemer
. This should usually
be of no use if option txOptAutoReferenceScripts
is
turned on, which is the case by default.
someTxSkelRedeemer :: RedeemerConstrs redeemer => redeemer -> TxSkelRedeemer Source #
Creates a TxSkelRedeemer
from an inner content with no reference input
emptyTxSkelRedeemer :: TxSkelRedeemer Source #
Creates a TxSkelRedeemer
without an inner content nor a reference input
txSkelRedeemerReferenceInputL :: Lens' TxSkelRedeemer (Maybe TxOutRef) Source #
Sets or gets the reference input from a redeemer
txSkelRedeemerAutoFillL :: Lens' TxSkelRedeemer Bool Source #
Sets or gets the autofill property from a redeemer
txSkelRedeemerTypedAT :: (RedeemerConstrs a, RedeemerConstrs b) => AffineTraversal TxSkelRedeemer TxSkelRedeemer a b Source #
Extracts, or sets, the typed redeemer of a TxSkelRedeemer
. This is
attempted in two ways: first, we try to simply cast the content, and then, if
it fails, we serialise the content and then attempt to deserialise it to the
right type. This second case is specifically useful when the current content
is an BuiltinData
itself directly, but it can also be used in the
cornercase when both types have compatible serialized representation.
someTxSkelRedeemerNoAutoFill :: RedeemerConstrs redeemer => redeemer -> TxSkelRedeemer Source #
Creates a TxSkelRedeemer
from an inner content with no reference input,
while not allowing it to be automatically assigned
emptyTxSkelRedeemerNoAutoFill :: TxSkelRedeemer Source #
Creates a TxSkelRedeemer
with no inner content and no reference input,
while dissallowing it to be automatically assinged
txSkelRedeemerBuiltinDataL :: Lens' TxSkelRedeemer BuiltinData Source #
Extracts, or sets, the redeemer content as an BuiltinData
txSkelOutReferenceScriptHashAF :: AffineFold TxSkelOutReferenceScript ScriptHash Source #
An affine fold producing an optional script hash from a TxSkelOutReferenceScript
txSkelOutReferenceScriptTypedP :: (ReferenceScriptConstrs a, ReferenceScriptConstrs b) => Prism TxSkelOutReferenceScript TxSkelOutReferenceScript a b Source #
A prism targeting a certain typed reference script within a TxSkelOutReferenceScript
txSkelOutReferenceScriptVersionedP :: Prism' TxSkelOutReferenceScript (Versioned Script) Source #
A prism targeting the versioned script within a TxSkelOutReferenceScript
pkWithdrawal :: ToPubKeyHash pkh => pkh -> Integer -> TxSkelWithdrawals Source #
Creates a TxSkelWithdrawals
from a private key hash and amount
scriptWithdrawal :: ToVersioned Script script => script -> TxSkelRedeemer -> Integer -> TxSkelWithdrawals Source #
Creates a TxSkelWithdrawals
from a script, redeemer and amount
failingTweak :: MonadTweak m => m a Source #
The never-applicable Tweak
.
doNothingTweak :: MonadTweak m => m () Source #
The Tweak
that always applies and leaves the transaction unchanged.
viewTweak :: (MonadTweak m, Is k A_Getter) => Optic' k is TxSkel a -> m a Source #
Retrieves some value from the TxSkel
viewAllTweak :: (MonadTweak m, Is k A_Fold) => Optic' k is TxSkel a -> m [a] Source #
Like the viewTweak
, but returns a list of all foci
setTweak :: (MonadTweak m, Is k A_Setter) => Optic' k is TxSkel a -> a -> m () Source #
The tweak that sets a certain value in the TxSkel
.
overTweak :: (MonadTweak m, Is k A_Setter) => Optic' k is TxSkel a -> (a -> a) -> m () Source #
The tweak that modifies a certain value in the TxSkel
.
overMaybeTweak :: (MonadTweak m, Is k A_Traversal) => Optic' k is TxSkel a -> (a -> Maybe a) -> m [a] Source #
Like overTweak
, but only modifies foci on which the argument function
returns Just
the new focus. Returns a list of the foci that were modified,
as they were before the tweak, and in the order in which they occurred on
the original transaction.
overMaybeSelectingTweak :: forall a m k is. (MonadTweak m, Is k A_Traversal) => Optic' k is TxSkel a -> (a -> Maybe a) -> (Integer -> Bool) -> m [a] Source #
Sometimes overMaybeTweak
modifies too many foci. This might be the case
if there are several identical foci, but you only want to modify some of
them. This is where this Tweak
becomes useful: The (Integer -> Bool)
argument can be used to select which of the modifiable foci should be
actually modified.
selectP :: (a -> Bool) -> Prism' a a Source #
overMaybeTweak
requires a modification that can fail (targeting Maybe
).
Sometimes, it can prove more convenient to explicitly state which property
the foci shoud satisfy to be eligible for a modification that cannot fail
instead. selectP
provides a prism to make such a selection. The intended
use case is overTweak (optic % selectP prop) mod
where optic
gives the
candidate foci, prop
is the predicate to be satisfied by the foci, and
mod
is the modification to be applied to the selected foci.
combineModsTweak :: (Eq is, Is k A_Traversal, MonadTweak m) => ([is] -> [[is]]) -> Optic' k (WithIx is) TxSkel x -> (is -> x -> m [(x, l)]) -> m [l] Source #
When constructing a tweak from an optic and a modification of foci, there are in principle two options for optics with many foci: (a) apply the modification to all foci and return one modified transaction (b) generate a number of transactions that contain different combinations of modified and un-modified foci.
While most of the other "optic -> tweak" functions in this module take take the route (a), this function enables strategy (b).
Explanation of the arguments and return value
- Each of the foci of the
Optic k (WithIx is) TxSkel x
argument is something in the transaction that we might want to modify. - The
is -> x -> m [(x, l)]
argument computes a list of possible modifications for each focus, depending on its index. For each modified focus, it also returns a "label" of typel
, which somehow describes the modification that was made. - The
[is] -> [[is]]
argument determines which combinations of (un-) modified foci will be present on the modified transactions: The input is a list of all of the indices of foci, and for each element[i_1,...,i_n]
of the output list, all possible modified transactions that have a modification applied to the foci with indicesi_1,...,i_n
are generated. - The return value of type
[l]
is the list of labels of all modified foci, in the order in which their indices occurred. Later tweaks may use this list to decide what to do.
Example 1
Assume the optic has three foci, let's denote them by a, b, c :: x
, with
indices 1, 2, 3 :: Integer
respectively. Also assume that the is -> x -> m
[(x, l)]
argument returns lists of 2, 3, and 5 elements on a
, b
, and
c
, respectively. Let's call those elements a1, a2
and b1, b2, b3
and
c1, c2, c3, c4, c5
.
If the [ix] -> [[ix]]
argument is map (:[])
, you will try every
modification on a separate transaction, since
map (:[]) [1, 2, 3] = [[1], [2], [3]] .
Thus, there'll be 2+3+5=10 modified transactions in our examples. Namely, for each element of the list
[a1, a2, b1, b2, b3, c1, c2, c3, c4, c5]
you'll get one modified transaction that includes that value in place of the original focus.
Example 2
In the setting of the first example, if you want to try combining all
possible modifications of one focus with all possible modifications of all
other foci, choose tail . subsequences
for the @[ix] -> [[ix]] argument. We
have
tail (subsequences [1, 2, 3]) == [ [1], [2], [3], [1, 2], [1, 3], [2, 3], [1, 2, 3] ]
This will correspond to the following 71 modified transactions, represented by the list of modified foci they contain:
[ -- one modified focus (the 10 cases from Example 1) [a1], [a2], ... [c4], [c5], -- two modifications of different foci (2*3 + 2*5 + 3*5 = 31 cases) [a1, b1], [a1, b2], ... [b3, c4], [b3, c5], -- three modified foci, one from each focus (2*3*5 = 30 cases) [a1, b1, c1], [a1, b1, c2], ... [a1, b3, c4], [a1, b3, c5] ]
So you see that tweaks constructed like this can branch quite wildly. Use with caution!
iviewTweak :: (MonadTweak m, Is k A_Getter) => Optic' k (WithIx is) TxSkel a -> m (is, a) Source #
Like viewTweak
, only for indexed optics.
ensureInputTweak :: MonadTweak m => TxOutRef -> TxSkelRedeemer -> m (Maybe (TxOutRef, TxSkelRedeemer)) Source #
Ensure that a given TxOutRef
is being spent with a given
TxSkelRedeemer
. The return value will be Just
the added data, if anything
changed.
addInputTweak :: MonadTweak m => TxOutRef -> TxSkelRedeemer -> m () Source #
Add an input to a transaction. If the given TxOutRef
is already being
consumed by the transaction, fail.
removeInputTweak :: MonadTweak m => (TxOutRef -> TxSkelRedeemer -> Bool) -> m [(TxOutRef, TxSkelRedeemer)] Source #
Remove transaction inputs according to a given predicate. The returned list contains all removed inputs.
modifySpendRedeemersOfTypeTweak :: forall a b m. (RedeemerConstrs a, RedeemerConstrs b, MonadTweak m) => (a -> Maybe b) -> m [TxSkelRedeemer] Source #
Applies an optional modification to all spend redeemers of type a. Returns the list of modified spending redemeers, as they were before being modified.
addLabelTweak :: (MonadTweak m, LabelConstrs x) => x -> m () Source #
Adds a label to a TxSkel
.
removeLabelTweak :: (MonadTweak m, LabelConstrs x) => x -> m () Source #
Removes a label from a TxSkel
when possible, fails otherwise
hasLabelTweak :: (MonadTweak m, LabelConstrs x) => x -> m Bool Source #
Checks if a given label is present in the TxSkel
addMintsTweak :: MonadTweak m => [Mint] -> m () Source #
Adds new entries to the TxSkelMints
of the transaction skeleton under
modification.
removeMintTweak :: MonadTweak m => (Mint -> Bool) -> m [Mint] Source #
Remove some entries from the TxSkelMints
of a transaction, according to
some predicate. The returned list holds the removed entries.
allOutPermutsTweak :: MonadTweak m => PermutOutTweakMode -> m () Source #
Modify transactions by changing the ordering of output constraints. If the
PermutOutTweakMode
is
KeepIdentity (Just n)
, the unmodified transaction is included in the list of modified transactions and only the first n outputs are permuted,KeepIdentity Nothing
, the unmodified transaction is included and all outputs are permuted. Use this with care; there might be a lot of permutations!OmitIdentity (Just n)
, the unmodified transaction is not included in the list of modified transactions and only the first n outputs are permuted,OmitIdentity Nothing
, the unmodified transaction is not included and all outputs are permuted. Use this with care; there might be a lot of permutations!
(In particular, this is clever enough to generate only the distinct permutations, even if some outputs are identical.)
singleOutPermutTweak :: MonadTweak m => Int -> m () Source #
This randomly permutes the outputs of a transaction with a given seed. Can be used to assess if a certain validator is order-dependant
ensureOutputTweak :: MonadTweak m => TxSkelOut -> m (Maybe TxSkelOut) Source #
Ensures that a certain output is produced by a transaction. The return
value will be Just
the added output, when applicable.
addOutputTweak :: MonadTweak m => TxSkelOut -> m () Source #
Adds a transaction output, at the end of the current list of outputs, thus retaining the initial outputs order.
removeOutputTweak :: MonadTweak m => (TxSkelOut -> Bool) -> m [TxSkelOut] Source #
Removes transaction outputs according to some predicate. The returned list contains all the removed outputs.
tamperDatumTweak :: forall a m. (MonadTweak m, DatumConstrs a) => (a -> Maybe a) -> m [a] Source #
A tweak that tries to change the datum on outputs carrying datums of a
certain type with a prescribed tampering function. The tampering function
ignores datums of other types and those for which it returns Nothing
.
The tweak returns a list of the modified datums, as they were *before* the modification was applied to them.
malformDatumTweak :: forall a m. (MonadTweak m, DatumConstrs a) => (a -> [BuiltinData]) -> m () Source #
A tweak that tries to change the datum on outputs carrying datums of a
certain type with a prescribed tampering function. There are two main
differences with tamperDatumTweak
. First, the tampering function returns
BuiltinData
, allowing it to do pretty much anything with the
datums. Second, for every output datum there are zero or more options for how
to modify it, and all combinations of these modifications are tried.
That is, if there are n
output datums, for which there are k_1,...,k_n
possible modifications, this tweak will try
k_1 + ... + k_n + k_1 * k_2 + ... + k_{n-1} * k_n + k_1 * k_2 * k_3 + ... + k_{n-2} * k_{n-1} * k_n + ... + k_1 * k_2 * ... * k_{n-1} * k_n == (k_1 + 1) * ... * (k_n + 1) - 1
modified transactions.
getSignersTweak :: MonadTweak m => m [Wallet] Source #
Returns the current list of signers
modifySignersTweak :: MonadTweak m => ([Wallet] -> [Wallet]) -> m [Wallet] Source #
Apply a function to the list of signers and return the old ones
setSignersTweak :: MonadTweak m => [Wallet] -> m [Wallet] Source #
Change the current signers and return the old ones
signersSatisfyTweak :: MonadTweak m => ([Wallet] -> Bool) -> m Bool Source #
Check if the signers satisfy a certain predicate
isSignerTweak :: MonadTweak m => Wallet -> m Bool Source #
Check if a wallet signs a transaction
hasSignersTweak :: MonadTweak m => m Bool Source #
Check if the transaction has at least a signer
addFirstSignerTweak :: MonadTweak m => Wallet -> m [Wallet] Source #
Add a signer to the transaction, at the head of the list of signers, and return the old list of signers
addSignersTweak :: MonadTweak m => [Wallet] -> m [Wallet] Source #
Add signers at the end of the list of signers, and return the old list of signers
addLastSignerTweak :: MonadTweak m => Wallet -> m [Wallet] Source #
Add a signer to the transaction, at the end of the list of signers, and return the old list of signers
removeSignersTweak :: MonadTweak m => [Wallet] -> m [Wallet] Source #
Remove signers from the transaction and return the old list of signers
removeSignerTweak :: MonadTweak m => Wallet -> m [Wallet] Source #
Remove a signer from the transaction and return the old list of signers
replaceFirstSignerTweak :: MonadTweak m => Wallet -> m [Wallet] Source #
Changes the first signer (adds it if there are no signers) and return the old list of signers.
getValidityRangeTweak :: MonadTweak m => m SlotRange Source #
Looks up the current validity range of the transaction
knownWallets :: [Wallet] Source #
All the wallets corresponding to known Plutus mock wallets. This is a list of 10 wallets which will
- receive funds in the standard initial distribution of cooked-validators,
- be pretty-printed as part the final state after running a few transactions.
wallet :: Integer -> Wallet Source #
Wallet corresponding to a given wallet number (or wallet ID) with an offset of 1 to start at 1 instead of 0
walletPKHashToId :: PubKeyHash -> Maybe Int Source #
Retrieves the id of the known wallet that corresponds to a public key hash
walletPKHashToId (walletPKHash (wallet 3)) == Just 3
walletPKHashToWallet :: PubKeyHash -> Maybe Wallet Source #
Retrieves the known wallet that corresponds to a public key hash
walletStakingPK :: Wallet -> Maybe PubKey Source #
Retrieves a wallet's public staking key (PK), if any
walletStakingPKHash :: Wallet -> Maybe PubKeyHash Source #
Retrieves a wallet's public staking key hash, if any
walletStakingSK :: Wallet -> Maybe XPrv Source #
Retrieves a wallet's private staking key (secret key SK), if any
utxoPayloadSet :: UtxoPayloadSet -> [UtxoPayload] Source #
List of UTxOs contained in this UtxoPayloadSet
utxoPayloadTxOutRef :: UtxoPayload -> TxOutRef Source #
The reference of this UTxO
utxoPayloadValue :: UtxoPayload -> Value Source #
The value stored in this UTxO
utxoPayloadDatum :: UtxoPayload -> UtxoPayloadDatum Source #
The optional datum stored in this UTxO
utxoPayloadReferenceScript :: UtxoPayload -> Maybe ScriptHash Source #
The optional reference script stored in this UTxO
combineMockChainT :: (forall a. m a -> m a -> m a) -> MockChainT m x -> MockChainT m x -> MockChainT m x Source #
Combines two MockChainT
together
mcrValue :: MockChainReturn a -> Either MockChainError a Source #
The returned value of the run
mcrOutputs :: MockChainReturn a -> Map TxOutRef (TxSkelOut, Bool) Source #
All the outputs used throughout the run
mcrUtxoState :: MockChainReturn a -> UtxoState Source #
The resulting UtxoState
of the run
mcrJournal :: MockChainReturn a -> [MockChainLogEntry] Source #
The log entries emitted during the run
mcrAliases :: MockChainReturn a -> Map BuiltinByteString String Source #
The aliases defined during the run
runMockChainTRaw :: Monad m => MockChainT m a -> m (MockChainReturn a) Source #
Runs a MockChainT
from a default MockChainState
runMockChainTFrom :: Monad m => InitialDistribution -> MockChainT m a -> m (MockChainReturn a) Source #
Runs a MockChainT
from an initial MockChainState
built from a given
InitialDistribution
.
runMockChainT :: Monad m => MockChainT m a -> m (MockChainReturn a) Source #
Executes a MockChainT
from the canonical initial state and environment.
runMockChainFrom :: InitialDistribution -> MockChain a -> MockChainReturn a Source #
runMockChain :: MockChain a -> MockChainReturn a Source #
See runMockChainT
testAll :: IsProp prop => (a -> prop) -> [a] -> prop Source #
Ensures all elements of a list satisfy a given prop
testAny :: IsProp prop => (a -> prop) -> [a] -> prop Source #
Ensures at least one element of a list satisfy a given prop
assertionToMaybe :: Assertion -> IO (Maybe HUnitFailure) Source #
Catches a HUnit test failure, if the test fails.
assertSubset :: (Show a, Eq a) => [a] -> [a] -> Assertion Source #
Asserts whether a set is a subset of another one, both given as lists.
assertSameSets :: (Show a, Eq a) => [a] -> [a] -> Assertion Source #
Asserts whether 2 sets are equal, both given as lists.
testToProp :: (IsProp prop, Show a) => Test a prop -> prop Source #
This takes a Test
and transforms it into an actual test case in
prop. This is the main function justifying the existence of Test
. This runs
the traces, ensures there is the right number of outcomes and, depending on
the nature of these outcomes, either calls testFailureProp
or
testSuccessProp
. It also uses the aliases emitted during the mockchain run
to pretty print messages when applicable.
testCooked :: Show a => String -> Test a Assertion -> TestTree Source #
A convenience helper when using Assertion
which allows to replace
testCase
with testCooked
and thus avoid the use of testToProp
.
Sadly we cannot generalise it with type classes on prop
to work for
QuichCheck at GHC will never be able to instantiate prop
.
testCookedQC :: Show a => String -> Test a Property -> TestTree Source #
Same as testCooked
, but for Property
mustSucceedTest :: IsProp prop => StagedMockChain a -> Test a prop Source #
A test template which expects a success from a trace
mustFailTest :: IsProp prop => StagedMockChain a -> Test a prop Source #
A test template which expects a failure from a trace
withInitDist :: Test a prop -> InitialDistribution -> Test a prop Source #
Gives an initial distribution from which the trace will be run
withPrettyOpts :: Test a prop -> PrettyCookedOpts -> Test a prop Source #
Gives some pretty options to render test messages
withJournalProp :: IsProp prop => Test a prop -> JournalProp prop -> Test a prop Source #
Appends a requirements over the emitted log, which will need to be satisfied both in case of success or failure of the run.
withStateProp :: IsProp prop => Test a prop -> StateProp prop -> Test a prop Source #
Appends a requirements over the resulting UtxoState
, which will need to
be satisfied both in case of success or failure of the run.
withSuccessProp :: IsProp prop => Test a prop -> SuccessProp a prop -> Test a prop Source #
Appends a requirement over the resulting value and state of the mockchain run which will need to be satisfied if the run is successful
withResultProp :: IsProp prop => Test a prop -> (a -> prop) -> Test a prop Source #
Same as withSuccessProp
but only considers the returning value of the run
withSizeProp :: IsProp prop => Test a prop -> SizeProp prop -> Test a prop Source #
Appends a requirement over the resulting number of outcomes of the run
withFailureProp :: IsProp prop => Test a prop -> FailureProp prop -> Test a prop Source #
Appends a requirement over the resulting value and state of the mockchain run which will need to be satisfied if the run is successful
withErrorProp :: IsProp prop => Test a prop -> (MockChainError -> prop) -> Test a prop Source #
Same as withFailureProp
but only considers the returning error of the run
isPhase1Failure :: IsProp prop => FailureProp prop Source #
A property to ensure a phase 1 failure
isPhase2Failure :: IsProp prop => FailureProp prop Source #
A property to ensure a phase 2 failure
isPhase1FailureWithMsg :: IsProp prop => String -> FailureProp prop Source #
Same as isPhase1Failure
with an added predicate on the text error
isPhase2FailureWithMsg :: IsProp prop => String -> FailureProp prop Source #
Same as isPhase2Failure
with an added predicate over the text error
isOfSize :: IsProp prop => Integer -> SizeProp prop Source #
Ensures the run has an exact given number of outcomes
isAtLeastOfSize :: IsProp prop => Integer -> SizeProp prop Source #
Ensures the run has a minimal number of outcomes
isAtMostOfSize :: IsProp prop => Integer -> SizeProp prop Source #
Ensures the run has a minimal number of outcomes
happened :: IsProp prop => String -> JournalProp prop Source #
Ensures a certain event has been emitted. This uses the constructor's name
of the MockChainLogEntry
by relying on show
being lazy.
didNotHappen :: IsProp prop => String -> JournalProp prop Source #
Ensures a certain event has not been emitted. This uses the constructor's
name of the MockChainLogEntry
by relying on show
being lazy.
isInWallets :: IsProp prop => [(Wallet, [(AssetClass, Integer -> Bool)])] -> SuccessProp a prop Source #
Ensures that the given wallets satisfy certain amount requirements over a list of given asset classes in the end of the run
isInWallet :: IsProp prop => (Wallet, AssetClass, Integer) -> SuccessProp a prop Source #
Ensures that a given wallet possesses exactly a certain amount of a given asset class in the end of the run
mustFailInPhase2Test :: IsProp prop => StagedMockChain a -> Test a prop Source #
A test template which expects a Phase 2 failure
mustFailInPhase2WithMsgTest :: IsProp prop => String -> StagedMockChain a -> Test a prop Source #
A test template which expects a specific phase 2 error message
mustFailInPhase1Test :: IsProp prop => StagedMockChain a -> Test a prop Source #
A test template which expects a Phase 1 failure
mustFailInPhase1WithMsgTest :: IsProp prop => String -> StagedMockChain a -> Test a prop Source #
A test template which expects a specific phase 1 error message
mustSucceedWithSizeTest :: IsProp prop => Integer -> StagedMockChain a -> Test a prop Source #
A test template which expects a certain number of successful outcomes
mustFailWithSizeTest :: IsProp prop => Integer -> StagedMockChain a -> Test a prop Source #
A test template which expects a certain number of unsuccessful outcomes
setValidityRangeTweak :: MonadTweak m => SlotRange -> m SlotRange Source #
Changes the current validity range, returning the old one
setAlwaysValidRangeTweak :: MonadTweak m => m SlotRange Source #
Ensures the skeleton makes for an unconstrained validity range
setValidityStartTweak :: MonadTweak m => Slot -> m SlotRange Source #
Sets the left bound of the validity range. Leaves the right bound unchanged
setValidityEndTweak :: MonadTweak m => Slot -> m SlotRange Source #
Sets the right bound of the validity range. Leaves the left bound unchanged
validityRangeSatisfiesTweak :: MonadTweak m => (SlotRange -> Bool) -> m Bool Source #
Checks if the validity range satisfies a certain predicate
isValidAtTweak :: MonadTweak m => Slot -> m Bool Source #
Checks if a given time belongs to the validity range of a transaction
isValidNowTweak :: MonadTweak m => m Bool Source #
Checks if the current validity range includes the current time
isValidDuringTweak :: MonadTweak m => SlotRange -> m Bool Source #
Checks if a given range is included in the validity range of a transaction
hasEmptyTimeRangeTweak :: MonadTweak m => m Bool Source #
Checks if the validity range is empty
hasFullTimeRangeTweak :: MonadTweak m => m Bool Source #
Checks if the validity range is unconstrained
intersectValidityRangeTweak :: MonadTweak m => SlotRange -> m SlotRange Source #
Adds a constraint to the current validity range. Returns the old range, and fails is the resulting interval is empty
centerAroundValidityRangeTweak :: MonadTweak m => Slot -> Integer -> m SlotRange Source #
Centers the validity range around a value with a certain radius
makeValidityRangeSingletonTweak :: MonadTweak m => Slot -> m SlotRange Source #
Makes a transaction range equal to a singleton
makeValidityRangeNowTweak :: MonadTweak m => m SlotRange Source #
Makes the transaction validity range comply with the current time
waitUntilValidTweak :: MonadTweak m => m Slot Source #
Makes current time comply with the validity range of the transaction under modification. Returns the new current time after the modification; fails if current time is already after the validity range.