{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Network.Polkadot.Rpc.System where
import Data.Aeson (Object)
import Data.Text (Text)
import Network.JsonRpc.TinyClient (JsonRpc (..))
import Network.Polkadot.Rpc.Types (ChainType, Health, NodeRole,
PeerInfo)
addReservedPeer :: JsonRpc m
=> Text
-> m Text
{-# INLINE addReservedPeer #-}
addReservedPeer :: forall (m :: * -> *). JsonRpc m => Text -> m Text
addReservedPeer = Text -> Text -> m Text
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_addReservedPeer"
chain :: JsonRpc m => m Text
{-# INLINE chain #-}
chain :: forall (m :: * -> *). JsonRpc m => m Text
chain = Text -> m Text
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_chain"
chainType :: JsonRpc m => m ChainType
{-# INLINE chainType #-}
chainType :: forall (m :: * -> *). JsonRpc m => m ChainType
chainType = Text -> m ChainType
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_chainType"
health :: JsonRpc m => m Health
{-# INLINE health #-}
health :: forall (m :: * -> *). JsonRpc m => m Health
health = Text -> m Health
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_health"
localListenAddresses :: JsonRpc m => m [Text]
{-# INLINE localListenAddresses #-}
localListenAddresses :: forall (m :: * -> *). JsonRpc m => m [Text]
localListenAddresses = Text -> m [Text]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_localListenAddresses"
localPeerId :: JsonRpc m => m Text
{-# INLINE localPeerId #-}
localPeerId :: forall (m :: * -> *). JsonRpc m => m Text
localPeerId = Text -> m Text
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_localPeerId"
name :: JsonRpc m => m Text
{-# INLINE name #-}
name :: forall (m :: * -> *). JsonRpc m => m Text
name = Text -> m Text
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_name"
networkState :: JsonRpc m => m Object
{-# INLINE networkState #-}
networkState :: forall (m :: * -> *). JsonRpc m => m Object
networkState = Text -> m Object
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_networkState"
nodeRoles :: JsonRpc m => m [NodeRole]
{-# INLINE nodeRoles #-}
nodeRoles :: forall (m :: * -> *). JsonRpc m => m [NodeRole]
nodeRoles = Text -> m [NodeRole]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_nodeRoles"
peers :: JsonRpc m => m [PeerInfo]
{-# INLINE peers #-}
peers :: forall (m :: * -> *). JsonRpc m => m [PeerInfo]
peers = Text -> m [PeerInfo]
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_peers"
properties :: JsonRpc m => m Object
{-# INLINE properties #-}
properties :: forall (m :: * -> *). JsonRpc m => m Object
properties = Text -> m Object
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_properties"
removeReservedPeer :: JsonRpc m
=> Text
-> m Text
{-# INLINE removeReservedPeer #-}
removeReservedPeer :: forall (m :: * -> *). JsonRpc m => Text -> m Text
removeReservedPeer = Text -> Text -> m Text
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_removeReservedPeer"
version :: JsonRpc m => m Text
{-# INLINE version #-}
version :: forall (m :: * -> *). JsonRpc m => m Text
version = Text -> m Text
forall a. Remote m a => Text -> a
forall (m :: * -> *) a. (JsonRpc m, Remote m a) => Text -> a
remote Text
"system_version"