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

Test.Cleveland.Internal.Client

Description

Implementation that works with real Tezos network, it talks to a Tezos node and uses octez-client.

Synopsis

Documentation

newtype TestError Source #

Signals an assertion failure during the execution of an action.

Constructors

CustomTestError Text 

newtype ClientM a Source #

Constructors

ClientM 

Instances

Instances details
MonadFail ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

fail :: String -> ClientM a #

MonadIO ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

liftIO :: IO a -> ClientM a #

Applicative ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

pure :: a -> ClientM a #

(<*>) :: ClientM (a -> b) -> ClientM a -> ClientM b #

liftA2 :: (a -> b -> c) -> ClientM a -> ClientM b -> ClientM c #

(*>) :: ClientM a -> ClientM b -> ClientM b #

(<*) :: ClientM a -> ClientM b -> ClientM a #

Functor ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

fmap :: (a -> b) -> ClientM a -> ClientM b #

(<$) :: a -> ClientM b -> ClientM a #

Monad ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

(>>=) :: ClientM a -> (a -> ClientM b) -> ClientM b #

(>>) :: ClientM a -> ClientM b -> ClientM b #

return :: a -> ClientM a #

MonadScenario ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Scenario

MonadCatch ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

catch :: Exception e => ClientM a -> (e -> ClientM a) -> ClientM a #

MonadThrow ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Methods

throwM :: Exception e => e -> ClientM a #

MonadReader (IORef ClientState) ClientM Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

data MoneybagConfigurationException Source #

This error designates that necessary preparations for running tests are not made.

Instances

Instances details
Exception MoneybagConfigurationException Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Generic MoneybagConfigurationException Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Associated Types

type Rep MoneybagConfigurationException :: Type -> Type #

Show MoneybagConfigurationException Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Buildable MoneybagConfigurationException Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

Eq MoneybagConfigurationException Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

type Rep MoneybagConfigurationException Source # 
Instance details

Defined in Test.Cleveland.Internal.Client

mkMorleyOnlyRpcEnvNetwork Source #

Arguments

:: NetworkEnv 
-> [SecretKey]

Extra secrets that should be known

-> MorleyOnlyRpcEnv 

Construct MorleyOnlyRpcEnv from NetworkEnv.

setupMoneybagAddress :: NetworkEnv -> IO Moneybag Source #

Initialize moneybag address by given NetworkEnv

networkOpsImpl :: MorleyClientEnv -> Sender -> ClevelandOpsImpl ClientM Source #

Implementation that works with real network and uses octez-node RPC and octez-client.

getAlias :: L1AddressKind kind => MorleyClientEnv -> KindedAddress kind -> ClientM (Alias kind) Source #

getAliasMaybe :: L1AddressKind kind => MorleyClientEnv -> KindedAddress kind -> ClientM (Maybe (Alias kind)) Source #

toClevelandResult :: OperationInfo Result -> ClientM (OperationInfo ClevelandResult) Source #

dryRunOperations :: ImplicitAddressWithAlias -> [OperationInfo ClientInput] -> MorleyClientM [(AppliedResult, Mutez)] Source #

findBalanceTooLow :: [RunError] -> Maybe ("balance" :! Mutez, "required" :! Mutez) Source #

revealKeyUnlessRevealed :: MorleyClientEnv -> ImplicitAddressWithAlias -> IO () Source #

Runs revealKeyUnlessRevealed with given client environment.