| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Morley.Client.TezosClient.Types
Contents
Description
Types used for interaction with tezos-client.
Synopsis
- class CmdArg a where
- data Alias
- data AliasHint
- data AliasOrAliasHint
- data AddressOrAlias
- = AddressResolved Address
- | AddressAlias Alias
- addressResolved :: ToAddress addr => addr -> AddressOrAlias
- data CalcOriginationFeeData cp st = CalcOriginationFeeData {
- cofdFrom :: AddressOrAlias
- cofdBalance :: TezosMutez
- cofdMbFromPassword :: Maybe ScrubbedBytes
- cofdContract :: Contract cp st
- cofdStorage :: Value st
- cofdBurnCap :: TezosInt64
- data CalcTransferFeeData = forall t.UntypedValScope t => CalcTransferFeeData {
- ctfdTo :: AddressOrAlias
- ctfdParam :: Value t
- ctfdEp :: EpName
- ctfdAmount :: TezosMutez
- newtype TezosClientConfig = TezosClientConfig {}
- data TezosClientEnv = TezosClientEnv {}
- class HasTezosClientEnv env where
- tezosClientEnvL :: Lens' env TezosClientEnv
- data SecretKeyEncryption
- unsafeCoerceAliasHintToAlias :: AliasHint -> Alias
- unsafeCoerceAliasToAliasHint :: Alias -> AliasHint
- unsafeGetAliasText :: Alias -> Text
- unsafeGetAliasHintText :: AliasHint -> Text
- mkAlias :: Text -> Alias
- mkAliasHint :: Text -> AliasHint
- tceAliasPrefixL :: Lens' TezosClientEnv (Maybe Text)
- tceEndpointUrlL :: Lens' TezosClientEnv BaseUrl
- tceTezosClientPathL :: Lens' TezosClientEnv FilePath
- tceMbTezosClientDataDirL :: Lens' TezosClientEnv (Maybe FilePath)
Documentation
An object that can be put as argument to a tezos-client command-line call.
Minimal complete definition
Nothing
Instances
| CmdArg Word16 Source # | |
| CmdArg ByteString Source # | |
Defined in Morley.Client.TezosClient.Types Methods toCmdArg :: ByteString -> String Source # | |
| CmdArg Text Source # | |
| CmdArg BaseUrl Source # | |
| CmdArg LText Source # | |
| CmdArg Address Source # | |
Defined in Morley.Client.TezosClient.Types | |
| CmdArg Mutez Source # | |
Defined in Morley.Client.TezosClient.Types | |
| CmdArg SecretKey Source # | |
Defined in Morley.Client.TezosClient.Types | |
| CmdArg EpName Source # | |
Defined in Morley.Client.TezosClient.Types | |
| CmdArg OperationHash Source # | |
Defined in Morley.Client.TezosClient.Types Methods toCmdArg :: OperationHash -> String Source # | |
| CmdArg AddressOrAlias Source # | |
Defined in Morley.Client.TezosClient.Types Methods toCmdArg :: AddressOrAlias -> String Source # | |
| CmdArg Alias Source # | |
| ProperUntypedValBetterErrors t => CmdArg (Value t) Source # | |
Defined in Morley.Client.TezosClient.Types | |
| CmdArg (Contract cp st) Source # | |
Defined in Morley.Client.TezosClient.Types | |
tezos-client can associate addresses with textual aliases.
This type denotes such an alias.
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.
Constructors
| AnAlias Alias | |
| AnAliasHint AliasHint |
Instances
| Show AliasOrAliasHint Source # | |
Defined in Morley.Client.TezosClient.Types Methods showsPrec :: Int -> AliasOrAliasHint -> ShowS # show :: AliasOrAliasHint -> String # showList :: [AliasOrAliasHint] -> ShowS # | |
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 |
Instances
addressResolved :: ToAddress addr => addr -> AddressOrAlias Source #
Creates an AddressOrAlias with the given address.
data CalcOriginationFeeData cp st Source #
Data required for calculating fee for origination operation.
Constructors
| CalcOriginationFeeData | |
Fields
| |
data CalcTransferFeeData Source #
Data required for calculating fee for transfer operation.
Constructors
| forall t.UntypedValScope t => CalcTransferFeeData | |
Fields
| |
Instances
| ToJSON CalcTransferFeeData Source # | |
Defined in Morley.Client.TezosClient.Types Methods toJSON :: CalcTransferFeeData -> Value # toEncoding :: CalcTransferFeeData -> Encoding # toJSONList :: [CalcTransferFeeData] -> Value # toEncodingList :: [CalcTransferFeeData] -> Encoding # | |
newtype TezosClientConfig Source #
Configuration maintained by tezos-client, see its config subcommands
(e. g. tezos-client config show).
Only the field we are interested in is present here.
Constructors
| TezosClientConfig | |
Fields | |
Instances
| Show TezosClientConfig Source # | |
Defined in Morley.Client.TezosClient.Types Methods showsPrec :: Int -> TezosClientConfig -> ShowS # show :: TezosClientConfig -> String # showList :: [TezosClientConfig] -> ShowS # | |
| FromJSON TezosClientConfig Source # | For reading tezos-client config. |
Defined in Morley.Client.TezosClient.Types Methods parseJSON :: Value -> Parser TezosClientConfig # parseJSONList :: Value -> Parser [TezosClientConfig] # | |
data TezosClientEnv Source #
Runtime environment for tezos-client bindings.
Constructors
| TezosClientEnv | |
Fields
| |
class HasTezosClientEnv env where Source #
Using this type class one can require MonadReader constraint
that holds any type with TezosClientEnv inside.
Methods
tezosClientEnvL :: Lens' env TezosClientEnv Source #
Instances
| HasTezosClientEnv (MorleyClientEnv' m) Source # | |
Defined in Morley.Client.Env Methods tezosClientEnvL :: Lens' (MorleyClientEnv' m) TezosClientEnv Source # | |
data SecretKeyEncryption Source #
Representation of address secret key encryption type
Constructors
| UnencryptedKey | |
| EncryptedKey | |
| LedgerKey |
Instances
| Eq SecretKeyEncryption Source # | |
Defined in Morley.Client.TezosClient.Types Methods (==) :: SecretKeyEncryption -> SecretKeyEncryption -> Bool # (/=) :: SecretKeyEncryption -> SecretKeyEncryption -> Bool # | |
| Show SecretKeyEncryption Source # | |
Defined in Morley.Client.TezosClient.Types Methods showsPrec :: Int -> SecretKeyEncryption -> ShowS # show :: SecretKeyEncryption -> String # showList :: [SecretKeyEncryption] -> ShowS # | |
Unsafe coercions
unsafeGetAliasText :: Alias -> Text Source #
Unsafely extract Text from Alias. Do NOT use the result with
mkAliasHint.