{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Polkadot.Rpc.State where
import Data.ByteArray.HexString (HexString)
import Data.Text (Text)
import Network.JsonRpc.TinyClient (JsonRpc (..))
import Network.Polkadot.Rpc.Types (ReadProof, RuntimeVersion,
StorageChangeSet)
call :: JsonRpc m
=> Text
-> HexString
-> Maybe HexString
-> m HexString
{-# INLINE call #-}
call :: forall (m :: * -> *).
JsonRpc m =>
Text -> HexString -> Maybe HexString -> m HexString
call = Text -> Text -> HexString -> Maybe HexString -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_call"
getChildKeys :: JsonRpc m
=> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m [HexString]
{-# INLINE getChildKeys #-}
getChildKeys :: forall (m :: * -> *).
JsonRpc m =>
HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m [HexString]
getChildKeys = Text
-> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m [HexString]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getChildKeys"
getChildStorage :: JsonRpc m
=> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m HexString
{-# INLINE getChildStorage #-}
getChildStorage :: forall (m :: * -> *).
JsonRpc m =>
HexString
-> HexString -> Int -> HexString -> Maybe HexString -> m HexString
getChildStorage = Text
-> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getChildStorage"
getChildStorageHash :: JsonRpc m
=> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m HexString
{-# INLINE getChildStorageHash #-}
getChildStorageHash :: forall (m :: * -> *).
JsonRpc m =>
HexString
-> HexString -> Int -> HexString -> Maybe HexString -> m HexString
getChildStorageHash = Text
-> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getChildStorageHash"
getChildStorageSize :: JsonRpc m
=> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m Int
{-# INLINE getChildStorageSize #-}
getChildStorageSize :: forall (m :: * -> *).
JsonRpc m =>
HexString
-> HexString -> Int -> HexString -> Maybe HexString -> m Int
getChildStorageSize = Text
-> HexString
-> HexString
-> Int
-> HexString
-> Maybe HexString
-> m Int
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getChildStorageSize"
getKeys :: JsonRpc m
=> HexString
-> Maybe HexString
-> m [HexString]
{-# INLINE getKeys #-}
getKeys :: forall (m :: * -> *).
JsonRpc m =>
HexString -> Maybe HexString -> m [HexString]
getKeys = Text -> HexString -> Maybe HexString -> m [HexString]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getKeys"
getMetadata :: JsonRpc m => m HexString
{-# INLINE getMetadata #-}
getMetadata :: forall (m :: * -> *). JsonRpc m => m HexString
getMetadata = Text -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getMetadata"
getReadProof :: JsonRpc m
=> [HexString]
-> Maybe HexString
-> m ReadProof
{-# INLINE getReadProof #-}
getReadProof :: forall (m :: * -> *).
JsonRpc m =>
[HexString] -> Maybe HexString -> m ReadProof
getReadProof = Text -> [HexString] -> Maybe HexString -> m ReadProof
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getReadProof"
getRuntimeVersion :: JsonRpc m
=> Maybe HexString
-> m RuntimeVersion
{-# INLINE getRuntimeVersion #-}
getRuntimeVersion :: forall (m :: * -> *).
JsonRpc m =>
Maybe HexString -> m RuntimeVersion
getRuntimeVersion = Text -> Maybe HexString -> m RuntimeVersion
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getRuntimeVersion"
getStorage :: JsonRpc m
=> HexString
-> Maybe HexString
-> m HexString
{-# INLINE getStorage #-}
getStorage :: forall (m :: * -> *).
JsonRpc m =>
HexString -> Maybe HexString -> m HexString
getStorage = Text -> HexString -> Maybe HexString -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getStorage"
getStorageHash :: JsonRpc m
=> HexString
-> Maybe HexString
-> m HexString
{-# INLINE getStorageHash #-}
getStorageHash :: forall (m :: * -> *).
JsonRpc m =>
HexString -> Maybe HexString -> m HexString
getStorageHash = Text -> HexString -> Maybe HexString -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getStorageHash"
getStorageSize :: JsonRpc m
=> HexString
-> Maybe HexString
-> m Int
{-# INLINE getStorageSize #-}
getStorageSize :: forall (m :: * -> *).
JsonRpc m =>
HexString -> Maybe HexString -> m Int
getStorageSize = Text -> HexString -> Maybe HexString -> m Int
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_getStorageSize"
queryStorage :: JsonRpc m
=> [HexString]
-> HexString
-> Maybe HexString
-> m [StorageChangeSet]
{-# INLINE queryStorage #-}
queryStorage :: forall (m :: * -> *).
JsonRpc m =>
[HexString] -> HexString -> Maybe HexString -> m [StorageChangeSet]
queryStorage = Text
-> [HexString]
-> HexString
-> Maybe HexString
-> m [StorageChangeSet]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_queryStorage"
queryStorageAt :: JsonRpc m
=> [HexString]
-> Maybe HexString
-> m [StorageChangeSet]
{-# INLINE queryStorageAt #-}
queryStorageAt :: forall (m :: * -> *).
JsonRpc m =>
[HexString] -> Maybe HexString -> m [StorageChangeSet]
queryStorageAt = Text -> [HexString] -> Maybe HexString -> m [StorageChangeSet]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"state_queryStorageAt"