morley-client-0.1.1: Client to interact with the Tezos blockchain
Safe HaskellNone
LanguageHaskell2010

Morley.Client

Description

Morley client that connects with real Tezos network through RPC and tezos-client binary. For more information please refer to README.

Synopsis

Command line parser

parserInfo :: ("usage" :! Doc) -> ("description" :! String) -> ("header" :! String) -> ("parser" :! Parser s) -> ParserInfo s #

Full client monad and environment

data MorleyClientM a Source #

Instances

Instances details
Monad MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Functor MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

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

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

Applicative MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

MonadIO MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

liftIO :: IO a -> MorleyClientM a #

MonadThrow MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

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

MonadCatch MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

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

MonadMask MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

RunClient MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

MonadUnliftIO MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

withRunInIO :: ((forall a. MorleyClientM a -> IO a) -> IO b) -> MorleyClientM b #

HasTezosRpc MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

getBlockHash :: BlockId -> MorleyClientM Text Source #

getCounterAtBlock :: BlockId -> Address -> MorleyClientM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyClientM BlockHeader Source #

getBlockConstants :: BlockId -> MorleyClientM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyClientM [[BlockOperation]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyClientM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyClientM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyClientM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyClientM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyClientM OperationHash Source #

getContractScriptAtBlock :: BlockId -> Address -> MorleyClientM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> Address -> MorleyClientM Expression Source #

getContractBigMapAtBlock :: BlockId -> Address -> GetBigMap -> MorleyClientM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyClientM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyClientM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyClientM Mutez Source #

getDelegateAtBlock :: BlockId -> Address -> MorleyClientM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyClientM RunCodeResult Source #

getChainId :: MorleyClientM ChainId Source #

getManagerKeyAtBlock :: BlockId -> Address -> MorleyClientM (Maybe PublicKey) Source #

HasTezosClient MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

MonadReader MorleyClientEnv MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

HasLog MorleyClientEnv Message MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

data MorleyClientConfig Source #

Data necessary for morley client initialization.

Constructors

MorleyClientConfig 

Fields

Instances

Instances details
Show MorleyClientConfig Source # 
Instance details

Defined in Morley.Client.Init

data MorleyClientEnv' m Source #

Runtime environment for morley client.

Constructors

MorleyClientEnv 

Fields

runMorleyClientM :: MorleyClientEnv -> MorleyClientM a -> IO a Source #

Run MorleyClientM action within given MorleyClientEnv. Retry action in case of invalid counter error.

mkMorleyClientEnv :: MonadIO m => MorleyClientConfig -> IO (MorleyClientEnv' m) Source #

Construct MorleyClientEnv.

Lens

mceSecretKeyL :: forall m. Lens' (MorleyClientEnv' m) (Maybe SecretKey) Source #

Only-RPC client monad and environment

newtype MorleyOnlyRpcM a Source #

Monad that implements HasTezosClient and HasTezosRpc classes and can be used for high-level actions as an alternative to MorleyClientM.

Instances

Instances details
Monad MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Functor MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

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

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

Applicative MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

MonadIO MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

liftIO :: IO a -> MorleyOnlyRpcM a #

MonadThrow MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

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

MonadCatch MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

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

MonadMask MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

RunClient MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

MonadUnliftIO MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

withRunInIO :: ((forall a. MorleyOnlyRpcM a -> IO a) -> IO b) -> MorleyOnlyRpcM b #

HasTezosRpc MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

getBlockHash :: BlockId -> MorleyOnlyRpcM Text Source #

getCounterAtBlock :: BlockId -> Address -> MorleyOnlyRpcM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyOnlyRpcM BlockHeader Source #

getBlockConstants :: BlockId -> MorleyOnlyRpcM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyOnlyRpcM [[BlockOperation]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyOnlyRpcM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyOnlyRpcM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyOnlyRpcM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyOnlyRpcM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyOnlyRpcM OperationHash Source #

getContractScriptAtBlock :: BlockId -> Address -> MorleyOnlyRpcM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> Address -> MorleyOnlyRpcM Expression Source #

getContractBigMapAtBlock :: BlockId -> Address -> GetBigMap -> MorleyOnlyRpcM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyOnlyRpcM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyOnlyRpcM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyOnlyRpcM Mutez Source #

getDelegateAtBlock :: BlockId -> Address -> MorleyOnlyRpcM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyOnlyRpcM RunCodeResult Source #

getChainId :: MorleyOnlyRpcM ChainId Source #

getManagerKeyAtBlock :: BlockId -> Address -> MorleyOnlyRpcM (Maybe PublicKey) Source #

HasTezosClient MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

MonadReader MorleyOnlyRpcEnv MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

HasLog MorleyOnlyRpcEnv Message MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

mkMorleyOnlyRpcEnv :: [SecretKey] -> BaseUrl -> Word -> IO MorleyOnlyRpcEnv Source #

Construct MorleyOnlyRpcEnv.

  • Full MorleyClientConfig is not passed because we need just 2 things from it.
  • Log action is built the same way as for MorleyClientEnv.
  • All secret keys are passed as an argument.

runMorleyOnlyRpcM :: MorleyOnlyRpcEnv -> MorleyOnlyRpcM a -> IO a Source #

Run MorleyOnlyRpcM action within given MorleyOnlyRpcEnv. Retry action in case of invalid counter error.

High-level actions

RPC

data BlockId Source #

A block identifier as submitted to RPC.

A block can be referenced by head, genesis, level or block hash

Constructors

HeadId

Identifier referring to the head block.

FinalHeadId

Identifier of the most recent block guaranteed to have been finalized. See: https://web.archive.org/web/20220305165609/https://tezos.gitlab.io/protocols/tenderbake.html#operations

GenesisId

Identifier referring to the genesis block.

LevelId Natural

Identifier referring to a block by its level.

BlockHashId Text

Idenfitier referring to a block by its hash in Base58Check notation.

AtDepthId Natural

Identifier of a block at specific depth relative to head.

Instances

Instances details
Eq BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

(==) :: BlockId -> BlockId -> Bool #

(/=) :: BlockId -> BlockId -> Bool #

Show BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: BlockId -> Builder #

ToHttpApiData BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

HasCLReader BlockId Source # 
Instance details

Defined in Morley.Client.RPC.Types

class (Monad m, MonadCatch m) => HasTezosRpc m where Source #

Type class that provides interaction with tezos node via RPC

Methods

getBlockHash :: BlockId -> m Text Source #

Get hash of the given BlockId, mostly used to get hash of HeadId

getCounterAtBlock :: BlockId -> Address -> m TezosInt64 Source #

Get address counter, which is required for both transaction sending and contract origination.

getBlockHeader :: BlockId -> m BlockHeader Source #

Get the whole header of a block.

getBlockConstants :: BlockId -> m BlockConstants Source #

Get block constants that are required by other RPC calls.

getBlockOperations :: BlockId -> m [[BlockOperation]] Source #

Get all operations from the block with specified ID.

getProtocolParametersAtBlock :: BlockId -> m ProtocolParameters Source #

Get protocol parameters that are for limits calculations.

runOperationAtBlock :: BlockId -> RunOperation -> m RunOperationResult Source #

Perform operation run, this operation doesn't require proper signing. As a result it returns burned gas and storage diff (also list of originated contracts but their addresses are incorrect due to the fact that operation could be not signed properly) or indicates about operation failure.

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> m [RunOperationResult] Source #

Preapply list of operations, each operation has to be signed with sender secret key. As a result it returns list of results each of which has information about burned gas, storage diff size and originated contracts.

forgeOperationAtBlock :: BlockId -> ForgeOperation -> m HexJSONByteString Source #

Forge operation in order to receive its hexadecimal representation.

injectOperation :: HexJSONByteString -> m OperationHash Source #

Inject operation, note that this operation has to be signed before injection. As a result it returns operation hash.

getContractScriptAtBlock :: BlockId -> Address -> m OriginationScript Source #

Get code and storage of the desired contract. Note that both code and storage are presented in low-level Micheline representation. If the storage contains a big_map, then the expression will contain the big_map's ID, not its contents.

getContractStorageAtBlock :: BlockId -> Address -> m Expression Source #

Get storage of the desired contract at some block. Note that storage is presented in low-level Micheline representation. If the storage contains a big_map, then the expression will contain the big_map's ID, not its contents.

getContractBigMapAtBlock :: BlockId -> Address -> GetBigMap -> m GetBigMapResult Source #

Get big map value by contract address.

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> m Expression Source #

Get big map value at some block by the big map's ID and the hashed entry key.

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> m Expression Source #

Get all big map values at some block by the big map's ID and the optional offset and length.

getBalanceAtBlock :: BlockId -> Address -> m Mutez Source #

Get balance for given address.

getDelegateAtBlock :: BlockId -> Address -> m (Maybe KeyHash) Source #

Get delegate for given address.

runCodeAtBlock :: BlockId -> RunCode -> m RunCodeResult Source #

Emulate contract call. This RPC endpoint does the same as tezos-client run script command does.

getChainId :: m ChainId Source #

Get current ChainId

getManagerKeyAtBlock :: BlockId -> Address -> m (Maybe PublicKey) Source #

Get manager key for given address. Returns Nothing if this key wasn't revealed.

Instances

Instances details
HasTezosRpc MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

getBlockHash :: BlockId -> MorleyOnlyRpcM Text Source #

getCounterAtBlock :: BlockId -> Address -> MorleyOnlyRpcM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyOnlyRpcM BlockHeader Source #

getBlockConstants :: BlockId -> MorleyOnlyRpcM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyOnlyRpcM [[BlockOperation]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyOnlyRpcM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyOnlyRpcM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyOnlyRpcM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyOnlyRpcM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyOnlyRpcM OperationHash Source #

getContractScriptAtBlock :: BlockId -> Address -> MorleyOnlyRpcM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> Address -> MorleyOnlyRpcM Expression Source #

getContractBigMapAtBlock :: BlockId -> Address -> GetBigMap -> MorleyOnlyRpcM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyOnlyRpcM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyOnlyRpcM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyOnlyRpcM Mutez Source #

getDelegateAtBlock :: BlockId -> Address -> MorleyOnlyRpcM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyOnlyRpcM RunCodeResult Source #

getChainId :: MorleyOnlyRpcM ChainId Source #

getManagerKeyAtBlock :: BlockId -> Address -> MorleyOnlyRpcM (Maybe PublicKey) Source #

HasTezosRpc MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

getBlockHash :: BlockId -> MorleyClientM Text Source #

getCounterAtBlock :: BlockId -> Address -> MorleyClientM TezosInt64 Source #

getBlockHeader :: BlockId -> MorleyClientM BlockHeader Source #

getBlockConstants :: BlockId -> MorleyClientM BlockConstants Source #

getBlockOperations :: BlockId -> MorleyClientM [[BlockOperation]] Source #

getProtocolParametersAtBlock :: BlockId -> MorleyClientM ProtocolParameters Source #

runOperationAtBlock :: BlockId -> RunOperation -> MorleyClientM RunOperationResult Source #

preApplyOperationsAtBlock :: BlockId -> [PreApplyOperation] -> MorleyClientM [RunOperationResult] Source #

forgeOperationAtBlock :: BlockId -> ForgeOperation -> MorleyClientM HexJSONByteString Source #

injectOperation :: HexJSONByteString -> MorleyClientM OperationHash Source #

getContractScriptAtBlock :: BlockId -> Address -> MorleyClientM OriginationScript Source #

getContractStorageAtBlock :: BlockId -> Address -> MorleyClientM Expression Source #

getContractBigMapAtBlock :: BlockId -> Address -> GetBigMap -> MorleyClientM GetBigMapResult Source #

getBigMapValueAtBlock :: BlockId -> Natural -> Text -> MorleyClientM Expression Source #

getBigMapValuesAtBlock :: BlockId -> Natural -> Maybe Natural -> Maybe Natural -> MorleyClientM Expression Source #

getBalanceAtBlock :: BlockId -> Address -> MorleyClientM Mutez Source #

getDelegateAtBlock :: BlockId -> Address -> MorleyClientM (Maybe KeyHash) Source #

runCodeAtBlock :: BlockId -> RunCode -> MorleyClientM RunCodeResult Source #

getChainId :: MorleyClientM ChainId Source #

getManagerKeyAtBlock :: BlockId -> Address -> MorleyClientM (Maybe PublicKey) Source #

getContract :: HasTezosRpc m => Address -> m Contract Source #

Get originated Contract for some address.

getImplicitContractCounter :: HasTezosRpc m => Address -> m TezosInt64 Source #

Get counter value for given address.

Throws an error if given address is a contract address.

getContractStorage :: HasTezosRpc m => Address -> m Expression Source #

getContractStorageAtBlock applied to the head block.

getBigMapValue :: HasTezosRpc m => Natural -> Text -> m Expression Source #

getBigMapValueAtBlock applied to the head block.

getHeadBlock :: HasTezosRpc m => m Text Source #

Get hash of the current head block, this head hash is used in other RPC calls.

getCounter :: HasTezosRpc m => Address -> m TezosInt64 Source #

getCounterAtBlock applied to the head block.

forgeOperation :: HasTezosRpc m => ForgeOperation -> m HexJSONByteString Source #

forgeOperationAtBlock applied to the head block.

getContractScript :: HasTezosRpc m => Address -> m OriginationScript Source #

getContractScriptAtBlock applied to the head block.

getContractBigMap :: HasTezosRpc m => Address -> GetBigMap -> m GetBigMapResult Source #

getContractBigMapAtBlock applied to the head block.

getBalance :: HasTezosRpc m => Address -> m Mutez Source #

getBalanceAtBlock applied to the head block.

getDelegate :: HasTezosRpc m => Address -> m (Maybe KeyHash) Source #

getDelegateAtBlock applied to the head block.

runCode :: HasTezosRpc m => RunCode -> m RunCodeResult Source #

runCodeAtBlock applied to the head block.

getManagerKey :: HasTezosRpc m => Address -> m (Maybe PublicKey) Source #

Errors

data ClientRpcError Source #

Errors that can happen in the RPC part when a user tries to make failing actions.

Constructors

ContractFailed

Smart contract execution has failed.

Fields

  • Address

    Smart contract address.

  • Expression

    Value the contract has failed with.

BadParameter

Parameter passed to a contract does not match its type.

Fields

  • Address

    Smart contract address.

  • Expression

    Value passed as parameter.

EmptyTransaction

Transfer of 0 to an implicit account.

Fields

  • Address

    Receiver address.

ShiftOverflow

A smart contract execution failed due to a shift overflow.

Fields

  • Address

    Smart contract address.

GasExhaustion

A smart contract execution failed due gas exhaustion.

Fields

  • Address

    Smart contract address.

KeyAlreadyRevealed

A key has already been revealed.

Fields

  • Address

    The address corresponding to the key.

ClientInternalError InternalError

An error that RPC considers internal occurred. These errors are considered internal by mistake, they are actually quite realistic and normally indicate bad user action. Currently we put InternalError here as is, because it's easy for a user of morley-client to work with this type. In #284 we will consider more errors and maybe some of them will need to be mapped into something more user-friendly, then we will reconsider this approach.

data IncorrectRpcResponse Source #

Errors that we can throw when we get a response from a node that doesn't match our expectations. It means that either the node we are talking to misbehaves or our code is incorrect.

data RunError Source #

Errors that are sent as part of operation result in an OK response (status 200). They are semi-formally defined as errors that can happen when a contract is executed and something goes wrong.

Constructors

RuntimeError Address 
ScriptRejected Expression 
BadContractParameter Address 
InvalidConstant Expression Expression 
InvalidContract Address 
InconsistentTypes Expression Expression 
InvalidPrimitive [Text] Text 
InvalidSyntacticConstantError Expression Expression 
InvalidExpressionKind [Text] Text 
InvalidContractNotation Text 
UnexpectedContract 
IllFormedType Expression 
UnexpectedOperation 
REEmptyTransaction

Transfer of 0 to an implicit account.

Fields

  • Address

    Receiver address.

ScriptOverflow

A contract failed due to the detection of an overflow. It seems to happen if a too big value is passed to shift instructions (as second argument).

GasExhaustedOperation 
MutezAdditionOverflow [TezosInt64] 
MutezSubtractionUnderflow [TezosInt64] 
MutezMultiplicationOverflow TezosInt64 TezosInt64 
CantPayStorageFee 
BalanceTooLow ("balance" :! Mutez) ("required" :! Mutez) 
PreviouslyRevealedKey Address 
NonExistingContract Address 

Instances

Instances details
Show RunError Source # 
Instance details

Defined in Morley.Client.RPC.Types

FromJSON RunError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Buildable RunError Source # 
Instance details

Defined in Morley.Client.RPC.Types

Methods

build :: RunError -> Builder #

Getters

readAllBigMapValues :: forall v k m. (NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> m [v] Source #

Read all big_map values, given it's ID. If the values are not of the expected type, a ValueDecodeFailure will be thrown.

readAllBigMapValuesMaybe :: forall v k m. (NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> m (Maybe [v]) Source #

Read all big_map values, given it's ID. If the values are not of the expected type, a ValueDecodeFailure will be thrown.

Returns Nothing if a big_map with the given ID does not exist.

readContractBigMapValue :: forall k v m. (PackedValScope k, HasTezosRpc m, SingI v) => Address -> Value k -> m (Value v) Source #

Read big_map value of given contract by key.

If the contract contains several big_maps with given key type, only one of them will be considered.

readBigMapValueMaybe :: forall v k m. (NicePackedValue k, NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> k -> m (Maybe v) Source #

Read big_map value, given it's ID and a key. If the value is not of the expected type, a ValueDecodeFailure will be thrown.

Returns Nothing if a big_map with the given ID does not exist, or it does exist but does not contain the given key.

readBigMapValue :: forall v k m. (NicePackedValue k, NiceUnpackedValue v, HasTezosRpc m) => BigMapId k v -> k -> m v Source #

Read big_map value, given it's ID and a key. If the value is not of the expected type, a ValueDecodeFailure will be thrown.

tezos-client

data Alias Source #

tezos-client can associate addresses with textual aliases. This type denotes such an alias.

Instances

Instances details
Eq Alias Source # 
Instance details

Defined in Morley.Client.TezosClient.Types

Methods

(==) :: Alias -> Alias -> Bool #

(/=) :: Alias -> Alias -> Bool #

Ord Alias Source # 
Instance details

Defined in Morley.Client.TezosClient.Types

Methods

compare :: Alias -> Alias -> Ordering #

(<) :: Alias -> Alias -> Bool #

(<=) :: Alias -> Alias -> Bool #

(>) :: Alias -> Alias -> Bool #

(>=) :: Alias -> Alias -> Bool #

max :: Alias -> Alias -> Alias #

min :: Alias -> Alias -> Alias #

Show Alias Source # 
Instance details

Defined in Morley.Client.TezosClient.Types

Methods

showsPrec :: Int -> Alias -> ShowS #

show :: Alias -> String #

showList :: [Alias] -> ShowS #

Buildable Alias Source # 
Instance details

Defined in Morley.Client.TezosClient.Types

Methods

build :: Alias -> Builder #

CmdArg Alias Source # 
Instance details

Defined in Morley.Client.TezosClient.Types

data AliasHint Source #

A hint for constructing an alias when generating an address or remembering a contract.

Resulting Alias most likely will differ from this as we tend to prefix aliases, but a user should be able to recognize your alias visually. For instance, passing "alice" as a hint may result into "myTest.alice" alias being created.

data AliasOrAliasHint Source #

Either an Alias, or an AliasHint. The difference is that AliasHint needs to be prefixed (if alias prefix is non-empty), while Alias doesn't.

Instances

Instances details
Show AliasOrAliasHint Source # 
Instance details

Defined in Morley.Client.TezosClient.Types

data AddressOrAlias Source #

Representation of an address that tezos-client uses. It can be an address itself or a textual alias.

Constructors

AddressResolved Address

Address itself, can be used as is.

AddressAlias Alias

Address alias, should be resolved by tezos-client.

addressResolved :: ToAddress addr => addr -> AddressOrAlias Source #

Creates an AddressOrAlias with the given address.

class Monad m => HasTezosClient m where Source #

Type class that provides interaction with tezos-client binary

Methods

signBytes :: AddressOrAlias -> Maybe ScrubbedBytes -> ByteString -> m Signature Source #

Sign an operation with tezos-client.

genKey :: AliasOrAliasHint -> m Address Source #

Generate a secret key and store it with given alias. If a key with this alias already exists, the corresponding address will be returned and no state will be changed.

genFreshKey :: AliasOrAliasHint -> m Address Source #

Generate a secret key and store it with given alias. Unlike genKey this function overwrites the existing key when given alias is already stored.

revealKey :: Alias -> Maybe ScrubbedBytes -> m () Source #

Reveal public key associated with given implicit account.

waitForOperation :: OperationHash -> m () Source #

Wait until operation known by some hash is included into the chain.

rememberContract :: Bool -> Address -> AliasOrAliasHint -> m () Source #

Associate the given contract with alias. The Bool variable indicates whether or not we should replace already existing contract alias or not.

importKey :: Bool -> AliasOrAliasHint -> SecretKey -> m Alias Source #

Saves SecretKey via tezos-client with given alias or hint associated. The Bool variable indicates whether or not we should replace already existing alias key or not. The returned Alias is the alias under which the key will be accessible.

resolveAddressMaybe :: AddressOrAlias -> m (Maybe Address) Source #

Retrieve an address from given address or alias. If address or alias does not exist returns Nothing

getAlias :: AddressOrAlias -> m Alias Source #

Retrieve an alias from given address using tezos-client. The primary (and probably only) reason this function exists is that tezos-client sign command only works with aliases. It was reported upstream: https://gitlab.com/tezos/tezos/-/issues/836.

getPublicKey :: AddressOrAlias -> m PublicKey Source #

Get public key for given address. Public keys are often used when interacting with the multising contracts

registerDelegate :: AliasOrAliasHint -> Maybe ScrubbedBytes -> m () Source #

Register a given address as delegate

getTezosClientConfig :: m TezosClientConfig Source #

Retrieve the current tezos-client config.

calcTransferFee :: AddressOrAlias -> Maybe ScrubbedBytes -> TezosInt64 -> [CalcTransferFeeData] -> m [TezosMutez] Source #

Calculate fee for transfer using `--dry-run` flag.

calcOriginationFee :: UntypedValScope st => CalcOriginationFeeData cp st -> m TezosMutez Source #

Calculate fee for origination using `--dry-run` flag.

getKeyPassword :: Address -> m (Maybe ScrubbedBytes) Source #

Get password for secret key associated with given address in case this key is password-protected. Obtained password is used in two places: * 1) In signBytes call. * 2) in revealKey call.

Instances

Instances details
HasTezosClient MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

HasTezosClient MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

resolveAddress :: (MonadThrow m, HasTezosClient m) => AddressOrAlias -> m Address Source #

Return Address corresponding to given AddressOrAlias.

data TezosClientError Source #

A data type for all predicatable errors that can happen during tezos-client usage.

Constructors

UnexpectedClientFailure

tezos-client call unexpectedly failed (returned non-zero exit code). The error contains the error code, stdout and stderr contents.

Fields

UnknownAddressAlias

Could not find an address with given name.

Fields

  • Alias

    Name of address which is eventually used

UnknownAddress

Could not find an address.

Fields

  • Address

    Address that is not present in local tezos cache

AlreadyRevealed

Public key of the given address is already revealed.

Fields

  • Alias

    Address alias that has already revealed its key

InvalidOperationHash OperationHash

Can't wait for inclusion of operation with given hash because the hash is invalid.

CounterIsAlreadyUsed

Error that indicates when given counter is already used for given contract.

Fields

EConnreset

Network error with which tezos-client fails from time to time.

ConfigParseError String

A parse error occurred during config parsing.

TezosClientCryptoParseError Text CryptoParseError

tezos-client produced a cryptographic primitive that we can't parse.

TezosClientParseAddressError Text ParseAddressError

tezos-client produced an address that we can't parse.

TezosClientParseFeeError Text Text

tezos-client produced invalid output for parsing baker fee

TezosClientUnexpectedOutputFormat Text

tezos-client printed a string that doesn't match the format we expect.

CantRevealContract

Given alias is a contract and cannot be revealed.

Fields

  • Alias

    Address alias of implicit account

ContractSender Address Text

Given contract is a source of a transfer or origination operation.

EmptyImplicitContract

Given alias is an empty implicit contract.

Fields

  • Alias

    Address alias of implicit contract

TezosClientUnexpectedSignatureOutput Text

tezos-client sign bytes produced unexpected output format

TezosClientParseEncryptionTypeError Text Text

tezos-client produced invalid output for parsing secret key encryption type.

Util

disableAlphanetWarning :: IO () Source #

Sets the environment variable for disabling tezos-client "not a mainnet" warning

Reexports

data ParserInfo a #

A full description for a runnable Parser for a program.

Instances

Instances details
Functor ParserInfo 
Instance details

Defined in Options.Applicative.Types

Methods

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

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