{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Polkadot.Rpc.Author where
import Data.ByteArray.HexString (HexString)
import Data.Text (Text)
import Network.JsonRpc.TinyClient (JsonRpc (..))
hasKey :: JsonRpc m
=> HexString
-> Text
-> m Bool
{-# INLINE hasKey #-}
hasKey :: forall (m :: * -> *). JsonRpc m => HexString -> Text -> m Bool
hasKey = Text -> HexString -> Text -> m Bool
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_hasKey"
hasSessionKeys :: JsonRpc m
=> HexString
-> m Bool
{-# INLINE hasSessionKeys #-}
hasSessionKeys :: forall (m :: * -> *). JsonRpc m => HexString -> m Bool
hasSessionKeys = Text -> HexString -> m Bool
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_hasSessionKeys"
insertKey :: JsonRpc m
=> Text
-> Text
-> HexString
-> m HexString
{-# INLINE insertKey #-}
insertKey :: forall (m :: * -> *).
JsonRpc m =>
Text -> Text -> HexString -> m HexString
insertKey = Text -> Text -> Text -> HexString -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_insertKey"
pendingExtrinsics :: JsonRpc m => m [HexString]
{-# INLINE pendingExtrinsics #-}
pendingExtrinsics :: forall (m :: * -> *). JsonRpc m => m [HexString]
pendingExtrinsics = Text -> m [HexString]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_pendingExtrinsics"
removeExtrinsic :: JsonRpc m
=> [HexString]
-> m HexString
{-# INLINE removeExtrinsic #-}
removeExtrinsic :: forall (m :: * -> *). JsonRpc m => [HexString] -> m HexString
removeExtrinsic = Text -> [HexString] -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_removeExtrinsic"
rotateKeys :: JsonRpc m => m HexString
{-# INLINE rotateKeys #-}
rotateKeys :: forall (m :: * -> *). JsonRpc m => m HexString
rotateKeys = Text -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_rotateKeys"
submitExtrinsic :: JsonRpc m
=> HexString
-> m HexString
{-# INLINE submitExtrinsic #-}
submitExtrinsic :: forall (m :: * -> *). JsonRpc m => HexString -> m HexString
submitExtrinsic = Text -> HexString -> m HexString
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"author_submitExtrinsic"