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

Morley.Client.Full

Description

Implementation of full-featured Morley client.

Synopsis

Documentation

data MorleyClientM a Source #

Instances

Instances details
MonadIO MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

liftIO :: IO a -> MorleyClientM a #

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

Monad MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

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

MonadThrow MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

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

HasTezosRpc MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

getBlockHash :: BlockId -> MorleyClientM BlockHash Source #

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

getBlockHeader :: BlockId -> MorleyClientM BlockHeader Source #

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

getBlockConstants :: BlockId -> MorleyClientM BlockConstants Source #

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

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

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

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

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

getChainId :: MorleyClientM ChainId Source #

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

waitForOperation :: MorleyClientM OperationHash -> MorleyClientM OperationHash Source #

HasTezosClient MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

Methods

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

genKey :: ImplicitAlias -> MorleyClientM ImplicitAddress Source #

genFreshKey :: ImplicitAlias -> MorleyClientM ImplicitAddress Source #

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

rememberContract :: Bool -> ContractAddress -> ContractAlias -> MorleyClientM () Source #

resolveAddressMaybe :: forall (kind :: AddressKind). AddressOrAlias kind -> MorleyClientM (Maybe (KindedAddress kind)) Source #

getAlias :: forall (kind :: AddressKind). L1AddressKind kind => AddressOrAlias kind -> MorleyClientM (Alias kind) Source #

registerDelegate :: ImplicitAlias -> Maybe ScrubbedBytes -> MorleyClientM () Source #

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

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 #

MonadReader MorleyClientEnv MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

HasLog MorleyClientEnv Message MorleyClientM Source # 
Instance details

Defined in Morley.Client.Full

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

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