cleveland-0.3.1: Testing framework for Morley.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cleveland.Internal.Actions.Misc

Description

The bulk of Cleveland actions.

Synopsis

Documentation

type EqBaseMonad a b = ClevelandBaseMonad a ~ ClevelandBaseMonad b Source #

A helper constraint synonym to make signatures below a bit shorter

withSender :: MonadCleveland caps m => ImplicitAddressWithAlias -> m a -> m a Source #

Update the current sender on whose behalf transfers and originations are invoked.

withMoneybag :: MonadCleveland caps m => ImplicitAddressWithAlias -> m a -> m a Source #

Update the current moneybag that transfers money on the newly created addresses. For the rare occasions when this is necessary.

runIO :: (HasCallStack, MonadCleveland caps m) => IO res -> m res Source #

Runs an IO action.

resolveAddress :: (HasCallStack, MonadCleveland caps m) => Alias kind -> m (KindedAddress kind) Source #

Get the address of the implicit account / contract associated with the given alias.

refillable :: (ToImplicitAddress addr, MonadCleveland caps m) => m addr -> m addr Source #

Simple combinator that marks address as "refillable".

If a refillable address lacks funds for the next operation, some funds will automatically be transferred to it.

refillables :: (ToImplicitAddress addr, Traversable f, MonadCleveland caps m) => m (f addr) -> m (f addr) Source #

Mark multiple addresses as refillable, useful with newAddresses &c.

newAddress :: (HasCallStack, MonadCleveland caps m) => SpecificOrDefaultAlias -> m ImplicitAddressWithAlias Source #

If the given alias is already associated with an existing address, that address will be reused and returned. Otherwise, generate a new secret key and record it with given alias.

If the account has too low of a balance, a small amount of XTZ will be transferred to it.

Notes:

  • By default, the XTZ is transferred from the account associated with the moneybag alias. This can be overridden with the --cleveland-moneybag-alias command line option, the TASTY_CLEVELAND_MONEYBAG_ALIAS env var, or withMoneybag.

newAddresses :: forall n n' caps m. (HasCallStack, MonadCleveland caps m, IsoNatPeano n n') => SizedList n SpecificOrDefaultAlias -> m (SizedList n ImplicitAddressWithAlias) Source #

Batched version of newAddress

newFreshAddress :: (HasCallStack, MonadCleveland caps m) => SpecificOrDefaultAlias -> m ImplicitAddressWithAlias Source #

Generate a new secret key and record it with given alias. If the alias is already known, the key will be overwritten. The address is guaranteed to be fresh, i. e. no operations on it have been made.

signBytes :: (HasCallStack, MonadCleveland caps m) => ByteString -> ImplicitAddressWithAlias -> m Signature Source #

Get the signature of the preapplied operation.

enumAliases :: forall n n'. (SingIPeano n, IsoNatPeano n n') => ImplicitAlias -> SizedList n SpecificOrDefaultAlias Source #

Create a list of similarly named SpecificAliases.

For example,

>>> enumAliases @2 "operator" `isEquivalentTo` "operator-0" :< "operator-1" :< Nil
True

signBinary :: (HasCallStack, BytesLike bs, MonadCleveland caps m) => bs -> ImplicitAddressWithAlias -> m (TSignature bs) Source #

Type-safer version of signBytes.

importUntypedContract :: (HasCallStack, MonadCleveland caps m) => FilePath -> m Contract Source #

Import an untyped contract from file.

importContract :: (HasCallStack, NiceParameter param, NiceStorage st, NiceViewsDescriptor vd, DemoteViewsDescriptor vd, MonadCleveland caps m) => FilePath -> m (Contract param st vd) Source #

Import a contract from file.

The compiler must be able to infer the types of parameter, storage and views. In case there are no views or you don't care, you can use noViews.

inBatch :: (HasCallStack, MonadCleveland caps m) => ClevelandOpsBatch a -> m a Source #

Run operations in a batch. Best used with the ApplicativeDo GHC extension.

Example:


contract <- inBatch $ do
  contract <- originate ...
  for_ [1..3] i ->
    transfer ...
  return contract

Batched operations should be applied to chain faster, but note that batches have their own limits. For instance, at the moment of writing, the gas limit on a batch is 10x of gas limit applied to a single operation.

A context of a batch is only Applicative, not Monad. This means that:

  • Return values of one function cannot be passed to another function in the same batch, it can only be returned;
  • Sometimes the compiler does not recognize that only Applicative context is required, in case of any issues with that - follow the error messages.

comment :: (HasCallStack, MonadCleveland caps m) => Text -> m () Source #

Print the given string verbatim as a comment. At the moment, this is a no-op in emulator tests.

getBalance :: (HasCallStack, MonadCleveland caps m, ToL1Address addr) => addr -> m Mutez Source #

Get the balance of the given address.

getDelegate :: (HasCallStack, MonadCleveland caps m, ToL1Address addr) => addr -> m (Maybe KeyHash) Source #

Get the delegate for the given contract/implicit address.

registerDelegate :: (HasCallStack, MonadCleveland caps m) => ImplicitAddressWithAlias -> m () Source #

Register the given implicit address as a delegate.

setDelegate :: (HasCallStack, MonadCleveland caps m) => ImplicitAddressWithAlias -> Maybe KeyHash -> m () Source #

Set/unset delegate

getStorage :: forall st addr caps m. (HasCallStack, MonadCleveland caps m, ToStorageType st addr, IsoValue (AsRPC st)) => addr -> m (AsRPC st) Source #

Retrieve a contract's storage in its "RPC representation" (i.e., all its big_maps will be replaced by big_map IDs).

If the storage is of a user-defined type, then deriveRPC / deriveManyRPC should be used to create an RPC representation of the storage type.

data MyStorage = MyStorage { field1 :: Natural, field2 :: BigMap Integer MText }
deriveRPC "MyStorage"

getFullStorage :: forall st addr caps m. (HasCallStack, MonadEmulated caps m, ToStorageType st addr) => addr -> m st Source #

Retrieve a contract's full storage, including the contents of its big_maps.

This function can only be used in emulator-only tests.

getSomeStorage :: forall addr caps m. (HasCallStack, MonadCleveland caps m, ToContractAddress addr) => addr -> m SomeAnnotatedValue Source #

Similar to getStorage, but doesn't require knowing the storage type in advance.

Use the optics in AnnotatedValue to read data from the storage.

getBigMapValueMaybe :: forall k v caps m. (HasCallStack, MonadCleveland caps m, NiceComparable k, NicePackedValue k, NiceUnpackedValue v) => BigMapId k v -> k -> m (Maybe v) Source #

Retrieve a big_map value, given a big_map ID and a key. Returns Nothing when the big_map ID does not exist, or it exists but does not contain the given key.

getBigMapValue :: forall k v caps m. (HasCallStack, MonadCleveland caps m, NiceComparable k, NicePackedValue k, NiceUnpackedValue v, Buildable k) => BigMapId k v -> k -> m v Source #

Like getBigMapValueMaybe, but fails the tests instead of returning Nothing.

getAllBigMapValuesMaybe :: forall k v caps m. (HasCallStack, MonadCleveland caps m, NiceComparable k, NiceUnpackedValue v) => BigMapId k v -> m (Maybe [v]) Source #

Retrieve all big_map values, given a big_map ID. Returns Nothing when the big_map ID does not exist.

getAllBigMapValues :: forall k v caps m. (HasCallStack, MonadCleveland caps m, NiceComparable k, NiceUnpackedValue v) => BigMapId k v -> m [v] Source #

Like getAllBigMapValuesMaybe, but fails the tests instead of returning Nothing.

getBigMapSizeMaybe :: forall k v caps m. (HasCallStack, MonadCleveland caps m, NiceComparable k, NiceUnpackedValue v) => BigMapId k v -> m (Maybe Natural) Source #

Retrieve a big_map size, given a big_map ID. Returns Nothing when the big_map ID does not exist.

O(n), because it's implemented with getBigMapValues.

getBigMapSize :: forall k v caps m. (HasCallStack, MonadCleveland caps m, NiceComparable k, NiceUnpackedValue v) => BigMapId k v -> m Natural Source #

Like getBigMapSizeMaybe, but fails the tests instead of returning Nothing.

getPublicKey :: (HasCallStack, MonadCleveland caps m) => ImplicitAddressWithAlias -> m PublicKey Source #

Get the public key associated with given address. Fail if given address is not an implicit account.

getChainId :: (HasCallStack, MonadCleveland caps m) => m ChainId Source #

Get the chain's ChainId.

advanceTime :: forall unit caps m. (HasCallStack, MonadCleveland caps m, KnownDivRat unit Second) => Time unit -> m () Source #

Advance at least the given amount of time, or until a new block is baked, whichever happens last.

On a real network, this is implemented using threadDelay, so it's advisable to use small amounts of time only.

advanceLevel :: forall caps m. (HasCallStack, MonadCleveland caps m) => Natural -> m () Source #

Wait till the provided number of levels is past.

advanceToLevel :: forall caps m. (HasCallStack, MonadCleveland caps m) => Natural -> m () Source #

Wait till the provided level is reached.

getNow :: (HasCallStack, MonadCleveland caps m) => m Timestamp Source #

Get the timestamp observed by the last block to be baked.

getLevel :: (HasCallStack, MonadCleveland caps m) => m Natural Source #

Get the current level observed by the last block to be baked.

getApproximateBlockInterval :: (HasCallStack, MonadCleveland caps m) => m (Time Second) Source #

Get approximate block interval in seconds. Note, that this value is minimal bound and real intervals can be larger, see http://tezos.gitlab.io/active/consensus.html#minimal-block-delay-function for more information about block delays.

getMinBlockTime :: (HasCallStack, MonadCleveland caps m) => m Natural Source #

Get minimal block delay in seconds. This is essentially the same as getApproximateBlockInterval, but returns a Natural instead of Time Second.

Can be useful when testing code using MIN_BLOCK_TIME instruction.

runCode :: (HasCallStack, MonadCleveland caps m, HasRPCRepr st, IsoValue (AsRPC st)) => RunCode cp st vd -> m (AsRPC st) Source #

Execute a contract's code without originating it. The chain's state will not be modified.

Notes:

  • If the contract's code emits operations, they will not be executed.
  • The sender's account won't be debited.
  • When running an _originated_ contract, the BALANCE instruction returns the sum of the contract's balance before the transfer operation + the amount of tz being transferred. In other words, this invariant holds: BALANCE >= AMOUNT. However, since runCode allows overriding the BALANCE instruction, then this invariant no longer holds. It's possible that BALANCE < AMOUNT.

branchout :: forall caps m. MonadEmulated caps m => [(Text, m ())] -> m () Source #

Execute multiple testing scenarios independently.

  • Actions performed before branchout will be observed by all branches.
  • Actions performed in branches will _not_ be observed by any actions performed after branchout.
  • Actions performed in one branch will _not_ be observed by another branch.
  • The test succeeds IFF all branches succeed.
  • If any branch fails, the test ends immediately and the remaining branches won't be executed.

The following property holds:

pre >> branchout [a, b, c] = branchout [pre >> a, pre >> b, pre >> c]

The list of branches must be non-empty.

offshoot :: forall caps m. MonadEmulated caps m => Text -> m () -> m () Source #

Execute one or more actions and roll them back afterwards. Actions performed in offshoot will _not_ be observed by any actions performed after offshoot.

Similar to branchout, but accepts one single branch.

getMorleyLogs :: forall a caps m. MonadEmulated caps m => m a -> m (LogsInfo, a) Source #

Returns the result of the action with the logs it produced. Logs are messages printed by the Lorentz instruction printComment.

This function can be combined either with lens-based accessors or helper functions to get more specific information about logs.

Examples:

(logsInfo, _) <- getMorleyLogs scenario
logsInfo ^.. each . logsL == [MorleyLogs ["log"], MorleyLogs ["log2"]]
logsInfo ^.. each . filterLogsByAddrL addr == [MorleyLogs ["log"]]
(logsInfo, _) <- getMorleyLogs scenario
collectLogs logsInfo == MorleyLogs ["log", "log2"]
logsForAddress logsInfo == [MorleyLogs ["log"]]

getMorleyLogs_ :: MonadEmulated caps m => m () -> m LogsInfo Source #

Version of getMorleyLogs for actions that don't return a result.

setVotingPowers :: MonadEmulated caps m => VotingPowers -> m () Source #

Updates voting power accessible via VOTING_POWER and similar instructions.

whenEmulation :: MonadCleveland caps m => (forall caps1 m1. (EqBaseMonad caps caps1, MonadEmulated caps1 m1) => m1 ()) -> m () Source #

Perform an action if we are currently in emulation mode. See also ifEmulation note on constraints.

whenNetwork :: MonadCleveland caps m => (forall caps1 m1. (EqBaseMonad caps caps1, MonadNetwork caps1 m1) => m1 ()) -> m () Source #

Perform an action if we are currently in network mode. See also ifEmulation note on constraints.

ifEmulation :: forall a caps m. MonadCleveland caps m => (forall caps1 m1. (EqBaseMonad caps caps1, MonadEmulated caps1 m1) => m1 a) -> (forall caps1 m1. (EqBaseMonad caps caps1, MonadNetwork caps1 m1) => m1 a) -> m a Source #

Perform one action if we are currently in emulation mode, another otherwise

Functions passed as the first two arguments are universally quantified over the outer monad, so if additional constraints are required beyond MonadEmulated or MonadCleveland, those constraints have to go on the base monad, e.g.

someFunction :: (MonadCleveland caps m, MonadFail (ClevelandBaseMonad caps)) => m ()
someFunction = whenEmulation do
  Just x <- pure (Just 1 :: Maybe Int) -- this would error without MonadFail
  runIO $ print x

getMorleyClientEnv :: MonadNetwork caps m => m MorleyClientEnv Source #

Get a MorleyClientEnv when running a test on network. Useful to run f.ex. octez-client inside a network test.

This is considered a pretty low-level function, so it's better to avoid it in most cases.

getOnlyRpcEnv :: MonadNetwork caps m => [SecretKey] -> m MorleyOnlyRpcEnv Source #

Get a MorleyOnlyRpcEnv when running a test on network. Useful to run raw network actions inside a network test.

This is considered a pretty low-level function, so it's better to avoid it in most cases.

importSecretKey :: MonadCleveland caps m => SecretKey -> SpecificOrDefaultAlias -> m ImplicitAddressWithAlias Source #

Import an (unencrypted) secret key as an alias. Can be used to get an implicit address/alias with a specific key or key type. If you don't care about the key or key type, consider using newAddress or newAddresses instead.

getTicketBalance :: (MonadCleveland caps m, HasNoOpToT a, NiceComparable a, ToL1Address addr, ToContractAddress contractAddr) => addr -> contractAddr -> a -> m Natural Source #

Get balance for a particular ticket.

getAllTicketBalances :: (MonadCleveland caps m, ToContractAddress addr) => addr -> m [SomeTicket] Source #

Get balance for all contract's tickets.