morley-client-0.3.0: Client to interact with the Tezos blockchain
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Client.OnlyRPC

Description

An alternative implementation of morley-client that does not require octez-client and has some limitations because of that (not all methods are implemented).

Synopsis

Documentation

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.

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
MonadIO MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

liftIO :: IO a -> MorleyOnlyRpcM a #

Applicative 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 #

Monad MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

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

MonadThrow MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

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

HasTezosRpc MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

getBlockHash :: BlockId -> MorleyOnlyRpcM BlockHash Source #

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

getBlockHeader :: BlockId -> MorleyOnlyRpcM BlockHeader Source #

getScriptSizeAtBlock :: BlockId -> CalcSize -> MorleyOnlyRpcM ScriptSize Source #

getBlockConstants :: BlockId -> MorleyOnlyRpcM BlockConstants Source #

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

getBlockOperationHashes :: BlockId -> MorleyOnlyRpcM [[OperationHash]] 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 -> ContractAddress -> MorleyOnlyRpcM OriginationScript Source #

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

getContractBigMapAtBlock :: BlockId -> ContractAddress -> 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 -> L1Address -> MorleyOnlyRpcM (Maybe KeyHash) Source #

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

getChainId :: MorleyOnlyRpcM ChainId Source #

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

waitForOperation :: MorleyOnlyRpcM OperationHash -> MorleyOnlyRpcM OperationHash Source #

HasTezosClient MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

Methods

signBytes :: ImplicitAddressOrAlias -> Maybe ScrubbedBytes -> ByteString -> MorleyOnlyRpcM Signature Source #

genKey :: ImplicitAlias -> MorleyOnlyRpcM ImplicitAddress Source #

genFreshKey :: ImplicitAlias -> MorleyOnlyRpcM ImplicitAddress Source #

revealKey :: ImplicitAlias -> Maybe ScrubbedBytes -> MorleyOnlyRpcM () Source #

rememberContract :: AliasBehavior -> ContractAddress -> ContractAlias -> MorleyOnlyRpcM () Source #

getAliasesAndAddresses :: MorleyOnlyRpcM [(Text, Text)] Source #

getKeyPassword :: ImplicitAddress -> MorleyOnlyRpcM (Maybe ScrubbedBytes) Source #

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 #

MonadReader MorleyOnlyRpcEnv MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

HasLog MorleyOnlyRpcEnv Message MorleyOnlyRpcM Source # 
Instance details

Defined in Morley.Client.OnlyRPC

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

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