{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}
module Network.Polkadot.Metadata.V13 where
import Codec.Scale (Decode, Encode, Generic)
import Data.Aeson (Options (constructorTagModifier, fieldLabelModifier, sumEncoding),
SumEncoding (ObjectWithSingleField),
defaultOptions)
import Data.Aeson.TH (deriveJSON)
import Data.ByteArray.HexString (HexString)
import Data.Char (toLower)
import Data.Text (Text)
import Data.Word (Word8)
import qualified GHC.Generics as GHC (Generic)
import Lens.Micro (_head, over)
import Network.Polkadot.Metadata.Type (Type)
import qualified Network.Polkadot.Metadata.V12 as V12
type ExtrinsicMetadata = V12.ExtrinsicMetadata
type FunctionMetadata = V12.FunctionMetadata
type EventMetadata = V12.EventMetadata
type ModuleConstantMetadata = V12.ModuleConstantMetadata
type ErrorMetadata = V12.ErrorMetadata
type StorageHasher = V12.StorageHasher
type MapType = V12.MapType
type DoubleMapType = V12.DoubleMapType
data NMapType = NMapType
{ NMapType -> [Type]
nmapKeyVec :: ![Type]
, NMapType -> [StorageHasher]
nmapHashers :: ![StorageHasher]
, NMapType -> Type
nmapValue :: !Type
} deriving (NMapType -> NMapType -> Bool
(NMapType -> NMapType -> Bool)
-> (NMapType -> NMapType -> Bool) -> Eq NMapType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NMapType -> NMapType -> Bool
== :: NMapType -> NMapType -> Bool
$c/= :: NMapType -> NMapType -> Bool
/= :: NMapType -> NMapType -> Bool
Eq, Int -> NMapType -> ShowS
[NMapType] -> ShowS
NMapType -> String
(Int -> NMapType -> ShowS)
-> (NMapType -> String) -> ([NMapType] -> ShowS) -> Show NMapType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NMapType -> ShowS
showsPrec :: Int -> NMapType -> ShowS
$cshow :: NMapType -> String
show :: NMapType -> String
$cshowList :: [NMapType] -> ShowS
showList :: [NMapType] -> ShowS
Show, All SListI (Code NMapType)
All SListI (Code NMapType) =>
(NMapType -> Rep NMapType)
-> (Rep NMapType -> NMapType) -> Generic NMapType
Rep NMapType -> NMapType
NMapType -> Rep NMapType
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: NMapType -> Rep NMapType
from :: NMapType -> Rep NMapType
$cto :: Rep NMapType -> NMapType
to :: Rep NMapType -> NMapType
Generic, (forall x. NMapType -> Rep NMapType x)
-> (forall x. Rep NMapType x -> NMapType) -> Generic NMapType
forall x. Rep NMapType x -> NMapType
forall x. NMapType -> Rep NMapType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. NMapType -> Rep NMapType x
from :: forall x. NMapType -> Rep NMapType x
$cto :: forall x. Rep NMapType x -> NMapType
to :: forall x. Rep NMapType x -> NMapType
GHC.Generic, Putter NMapType
Putter NMapType -> Encode NMapType
forall a. Putter a -> Encode a
$cput :: Putter NMapType
put :: Putter NMapType
Encode, Get NMapType
Get NMapType -> Decode NMapType
forall a. Get a -> Decode a
$cget :: Get NMapType
get :: Get NMapType
Decode)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = over _head toLower . drop 4 }) ''NMapType)
data StorageEntryType
= Plain !Type
| Map !MapType
| DoubleMap !DoubleMapType
| NMap !NMapType
deriving (StorageEntryType -> StorageEntryType -> Bool
(StorageEntryType -> StorageEntryType -> Bool)
-> (StorageEntryType -> StorageEntryType -> Bool)
-> Eq StorageEntryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StorageEntryType -> StorageEntryType -> Bool
== :: StorageEntryType -> StorageEntryType -> Bool
$c/= :: StorageEntryType -> StorageEntryType -> Bool
/= :: StorageEntryType -> StorageEntryType -> Bool
Eq, Int -> StorageEntryType -> ShowS
[StorageEntryType] -> ShowS
StorageEntryType -> String
(Int -> StorageEntryType -> ShowS)
-> (StorageEntryType -> String)
-> ([StorageEntryType] -> ShowS)
-> Show StorageEntryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StorageEntryType -> ShowS
showsPrec :: Int -> StorageEntryType -> ShowS
$cshow :: StorageEntryType -> String
show :: StorageEntryType -> String
$cshowList :: [StorageEntryType] -> ShowS
showList :: [StorageEntryType] -> ShowS
Show, All SListI (Code StorageEntryType)
All SListI (Code StorageEntryType) =>
(StorageEntryType -> Rep StorageEntryType)
-> (Rep StorageEntryType -> StorageEntryType)
-> Generic StorageEntryType
Rep StorageEntryType -> StorageEntryType
StorageEntryType -> Rep StorageEntryType
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: StorageEntryType -> Rep StorageEntryType
from :: StorageEntryType -> Rep StorageEntryType
$cto :: Rep StorageEntryType -> StorageEntryType
to :: Rep StorageEntryType -> StorageEntryType
Generic, (forall x. StorageEntryType -> Rep StorageEntryType x)
-> (forall x. Rep StorageEntryType x -> StorageEntryType)
-> Generic StorageEntryType
forall x. Rep StorageEntryType x -> StorageEntryType
forall x. StorageEntryType -> Rep StorageEntryType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StorageEntryType -> Rep StorageEntryType x
from :: forall x. StorageEntryType -> Rep StorageEntryType x
$cto :: forall x. Rep StorageEntryType x -> StorageEntryType
to :: forall x. Rep StorageEntryType x -> StorageEntryType
GHC.Generic, Putter StorageEntryType
Putter StorageEntryType -> Encode StorageEntryType
forall a. Putter a -> Encode a
$cput :: Putter StorageEntryType
put :: Putter StorageEntryType
Encode, Get StorageEntryType
Get StorageEntryType -> Decode StorageEntryType
forall a. Get a -> Decode a
$cget :: Get StorageEntryType
get :: Get StorageEntryType
Decode)
$(deriveJSON (defaultOptions
{ constructorTagModifier = over _head toLower, sumEncoding = ObjectWithSingleField }) ''StorageEntryType)
data StorageEntryMetadata = StorageEntryMetadata
{ StorageEntryMetadata -> Text
entryName :: !Text
, StorageEntryMetadata -> StorageEntryModifier
entryModifier :: !V12.StorageEntryModifier
, StorageEntryMetadata -> StorageEntryType
entryType :: !StorageEntryType
, StorageEntryMetadata -> HexString
entryFallback :: !HexString
, StorageEntryMetadata -> [Text]
entryDocumentation :: ![Text]
} deriving (StorageEntryMetadata -> StorageEntryMetadata -> Bool
(StorageEntryMetadata -> StorageEntryMetadata -> Bool)
-> (StorageEntryMetadata -> StorageEntryMetadata -> Bool)
-> Eq StorageEntryMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StorageEntryMetadata -> StorageEntryMetadata -> Bool
== :: StorageEntryMetadata -> StorageEntryMetadata -> Bool
$c/= :: StorageEntryMetadata -> StorageEntryMetadata -> Bool
/= :: StorageEntryMetadata -> StorageEntryMetadata -> Bool
Eq, Int -> StorageEntryMetadata -> ShowS
[StorageEntryMetadata] -> ShowS
StorageEntryMetadata -> String
(Int -> StorageEntryMetadata -> ShowS)
-> (StorageEntryMetadata -> String)
-> ([StorageEntryMetadata] -> ShowS)
-> Show StorageEntryMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StorageEntryMetadata -> ShowS
showsPrec :: Int -> StorageEntryMetadata -> ShowS
$cshow :: StorageEntryMetadata -> String
show :: StorageEntryMetadata -> String
$cshowList :: [StorageEntryMetadata] -> ShowS
showList :: [StorageEntryMetadata] -> ShowS
Show, All SListI (Code StorageEntryMetadata)
All SListI (Code StorageEntryMetadata) =>
(StorageEntryMetadata -> Rep StorageEntryMetadata)
-> (Rep StorageEntryMetadata -> StorageEntryMetadata)
-> Generic StorageEntryMetadata
Rep StorageEntryMetadata -> StorageEntryMetadata
StorageEntryMetadata -> Rep StorageEntryMetadata
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: StorageEntryMetadata -> Rep StorageEntryMetadata
from :: StorageEntryMetadata -> Rep StorageEntryMetadata
$cto :: Rep StorageEntryMetadata -> StorageEntryMetadata
to :: Rep StorageEntryMetadata -> StorageEntryMetadata
Generic, (forall x. StorageEntryMetadata -> Rep StorageEntryMetadata x)
-> (forall x. Rep StorageEntryMetadata x -> StorageEntryMetadata)
-> Generic StorageEntryMetadata
forall x. Rep StorageEntryMetadata x -> StorageEntryMetadata
forall x. StorageEntryMetadata -> Rep StorageEntryMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StorageEntryMetadata -> Rep StorageEntryMetadata x
from :: forall x. StorageEntryMetadata -> Rep StorageEntryMetadata x
$cto :: forall x. Rep StorageEntryMetadata x -> StorageEntryMetadata
to :: forall x. Rep StorageEntryMetadata x -> StorageEntryMetadata
GHC.Generic, Putter StorageEntryMetadata
Putter StorageEntryMetadata -> Encode StorageEntryMetadata
forall a. Putter a -> Encode a
$cput :: Putter StorageEntryMetadata
put :: Putter StorageEntryMetadata
Encode, Get StorageEntryMetadata
Get StorageEntryMetadata -> Decode StorageEntryMetadata
forall a. Get a -> Decode a
$cget :: Get StorageEntryMetadata
get :: Get StorageEntryMetadata
Decode)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = over _head toLower . drop 5 }) ''StorageEntryMetadata)
data StorageMetadata = StorageMetadata
{ StorageMetadata -> Text
storagePrefix :: !Text
, StorageMetadata -> [StorageEntryMetadata]
storageItems :: ![StorageEntryMetadata]
} deriving (StorageMetadata -> StorageMetadata -> Bool
(StorageMetadata -> StorageMetadata -> Bool)
-> (StorageMetadata -> StorageMetadata -> Bool)
-> Eq StorageMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StorageMetadata -> StorageMetadata -> Bool
== :: StorageMetadata -> StorageMetadata -> Bool
$c/= :: StorageMetadata -> StorageMetadata -> Bool
/= :: StorageMetadata -> StorageMetadata -> Bool
Eq, Int -> StorageMetadata -> ShowS
[StorageMetadata] -> ShowS
StorageMetadata -> String
(Int -> StorageMetadata -> ShowS)
-> (StorageMetadata -> String)
-> ([StorageMetadata] -> ShowS)
-> Show StorageMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StorageMetadata -> ShowS
showsPrec :: Int -> StorageMetadata -> ShowS
$cshow :: StorageMetadata -> String
show :: StorageMetadata -> String
$cshowList :: [StorageMetadata] -> ShowS
showList :: [StorageMetadata] -> ShowS
Show, All SListI (Code StorageMetadata)
All SListI (Code StorageMetadata) =>
(StorageMetadata -> Rep StorageMetadata)
-> (Rep StorageMetadata -> StorageMetadata)
-> Generic StorageMetadata
Rep StorageMetadata -> StorageMetadata
StorageMetadata -> Rep StorageMetadata
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: StorageMetadata -> Rep StorageMetadata
from :: StorageMetadata -> Rep StorageMetadata
$cto :: Rep StorageMetadata -> StorageMetadata
to :: Rep StorageMetadata -> StorageMetadata
Generic, (forall x. StorageMetadata -> Rep StorageMetadata x)
-> (forall x. Rep StorageMetadata x -> StorageMetadata)
-> Generic StorageMetadata
forall x. Rep StorageMetadata x -> StorageMetadata
forall x. StorageMetadata -> Rep StorageMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StorageMetadata -> Rep StorageMetadata x
from :: forall x. StorageMetadata -> Rep StorageMetadata x
$cto :: forall x. Rep StorageMetadata x -> StorageMetadata
to :: forall x. Rep StorageMetadata x -> StorageMetadata
GHC.Generic, Putter StorageMetadata
Putter StorageMetadata -> Encode StorageMetadata
forall a. Putter a -> Encode a
$cput :: Putter StorageMetadata
put :: Putter StorageMetadata
Encode, Get StorageMetadata
Get StorageMetadata -> Decode StorageMetadata
forall a. Get a -> Decode a
$cget :: Get StorageMetadata
get :: Get StorageMetadata
Decode)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = over _head toLower . drop 7 }) ''StorageMetadata)
data ModuleMetadata = ModuleMetadata
{ ModuleMetadata -> Text
moduleName :: !Text
, ModuleMetadata -> Maybe StorageMetadata
moduleStorage :: !(Maybe StorageMetadata)
, ModuleMetadata -> Maybe [FunctionMetadata]
moduleCalls :: !(Maybe [FunctionMetadata])
, ModuleMetadata -> Maybe [EventMetadata]
moduleEvents :: !(Maybe [EventMetadata])
, ModuleMetadata -> [ModuleConstantMetadata]
moduleConstants :: ![ModuleConstantMetadata]
, ModuleMetadata -> [ErrorMetadata]
moduleErrors :: ![ErrorMetadata]
, ModuleMetadata -> Word8
moduleIndex :: !Word8
} deriving (ModuleMetadata -> ModuleMetadata -> Bool
(ModuleMetadata -> ModuleMetadata -> Bool)
-> (ModuleMetadata -> ModuleMetadata -> Bool) -> Eq ModuleMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModuleMetadata -> ModuleMetadata -> Bool
== :: ModuleMetadata -> ModuleMetadata -> Bool
$c/= :: ModuleMetadata -> ModuleMetadata -> Bool
/= :: ModuleMetadata -> ModuleMetadata -> Bool
Eq, Int -> ModuleMetadata -> ShowS
[ModuleMetadata] -> ShowS
ModuleMetadata -> String
(Int -> ModuleMetadata -> ShowS)
-> (ModuleMetadata -> String)
-> ([ModuleMetadata] -> ShowS)
-> Show ModuleMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModuleMetadata -> ShowS
showsPrec :: Int -> ModuleMetadata -> ShowS
$cshow :: ModuleMetadata -> String
show :: ModuleMetadata -> String
$cshowList :: [ModuleMetadata] -> ShowS
showList :: [ModuleMetadata] -> ShowS
Show, All SListI (Code ModuleMetadata)
All SListI (Code ModuleMetadata) =>
(ModuleMetadata -> Rep ModuleMetadata)
-> (Rep ModuleMetadata -> ModuleMetadata) -> Generic ModuleMetadata
Rep ModuleMetadata -> ModuleMetadata
ModuleMetadata -> Rep ModuleMetadata
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: ModuleMetadata -> Rep ModuleMetadata
from :: ModuleMetadata -> Rep ModuleMetadata
$cto :: Rep ModuleMetadata -> ModuleMetadata
to :: Rep ModuleMetadata -> ModuleMetadata
Generic, (forall x. ModuleMetadata -> Rep ModuleMetadata x)
-> (forall x. Rep ModuleMetadata x -> ModuleMetadata)
-> Generic ModuleMetadata
forall x. Rep ModuleMetadata x -> ModuleMetadata
forall x. ModuleMetadata -> Rep ModuleMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ModuleMetadata -> Rep ModuleMetadata x
from :: forall x. ModuleMetadata -> Rep ModuleMetadata x
$cto :: forall x. Rep ModuleMetadata x -> ModuleMetadata
to :: forall x. Rep ModuleMetadata x -> ModuleMetadata
GHC.Generic, Putter ModuleMetadata
Putter ModuleMetadata -> Encode ModuleMetadata
forall a. Putter a -> Encode a
$cput :: Putter ModuleMetadata
put :: Putter ModuleMetadata
Encode, Get ModuleMetadata
Get ModuleMetadata -> Decode ModuleMetadata
forall a. Get a -> Decode a
$cget :: Get ModuleMetadata
get :: Get ModuleMetadata
Decode)
$(deriveJSON (defaultOptions
{ fieldLabelModifier = over _head toLower . drop 6 }) ''ModuleMetadata)
data Metadata = Metadata
{ Metadata -> [ModuleMetadata]
modules :: ![ModuleMetadata]
, Metadata -> ExtrinsicMetadata
extrinsic :: !ExtrinsicMetadata
} deriving (Metadata -> Metadata -> Bool
(Metadata -> Metadata -> Bool)
-> (Metadata -> Metadata -> Bool) -> Eq Metadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Metadata -> Metadata -> Bool
== :: Metadata -> Metadata -> Bool
$c/= :: Metadata -> Metadata -> Bool
/= :: Metadata -> Metadata -> Bool
Eq, Int -> Metadata -> ShowS
[Metadata] -> ShowS
Metadata -> String
(Int -> Metadata -> ShowS)
-> (Metadata -> String) -> ([Metadata] -> ShowS) -> Show Metadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Metadata -> ShowS
showsPrec :: Int -> Metadata -> ShowS
$cshow :: Metadata -> String
show :: Metadata -> String
$cshowList :: [Metadata] -> ShowS
showList :: [Metadata] -> ShowS
Show, All SListI (Code Metadata)
All SListI (Code Metadata) =>
(Metadata -> Rep Metadata)
-> (Rep Metadata -> Metadata) -> Generic Metadata
Rep Metadata -> Metadata
Metadata -> Rep Metadata
forall a.
All SListI (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
$cfrom :: Metadata -> Rep Metadata
from :: Metadata -> Rep Metadata
$cto :: Rep Metadata -> Metadata
to :: Rep Metadata -> Metadata
Generic, (forall x. Metadata -> Rep Metadata x)
-> (forall x. Rep Metadata x -> Metadata) -> Generic Metadata
forall x. Rep Metadata x -> Metadata
forall x. Metadata -> Rep Metadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Metadata -> Rep Metadata x
from :: forall x. Metadata -> Rep Metadata x
$cto :: forall x. Rep Metadata x -> Metadata
to :: forall x. Rep Metadata x -> Metadata
GHC.Generic, Putter Metadata
Putter Metadata -> Encode Metadata
forall a. Putter a -> Encode a
$cput :: Putter Metadata
put :: Putter Metadata
Encode, Get Metadata
Get Metadata -> Decode Metadata
forall a. Get a -> Decode a
$cget :: Get Metadata
get :: Get Metadata
Decode)
$(deriveJSON defaultOptions ''Metadata)