{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.Metadata
( Metadata (..),
MetadataM (..),
MetadataModifier (..),
MetadataNoSources (..),
MetadataVersion (..),
currentMetadataVersion,
dropComputedFieldInMetadata,
dropEventTriggerInMetadata,
dropFunctionInMetadata,
dropPermissionInMetadata,
dropRelationshipInMetadata,
dropRemoteRelationshipInMetadata,
dropTableInMetadata,
dropRemoteSchemaInMetadata,
dropRemoteSchemaPermissionInMetadata,
dropRemoteSchemaRemoteRelationshipInMetadata,
emptyMetadata,
functionMetadataSetter,
metaActions,
metaAllowlist,
metaApiLimits,
metaBackendConfigs,
metaCronTriggers,
metaCustomTypes,
metaInheritedRoles,
metaMetricsConfig,
metaNetwork,
metaQueryCollections,
metaRemoteSchemas,
metaRestEndpoints,
metaSetGraphqlIntrospectionOptions,
metaSources,
metadataToDTO,
metadataToOrdJSON,
tableMetadataSetter,
module Hasura.RQL.Types.Metadata.Common,
)
where
import Control.Lens hiding (set, (.=))
import Data.Aeson.Extended (FromJSONWithContext (..), mapWithJSONPath)
import Data.Aeson.Ordered qualified as AO
import Data.Aeson.TH
import Data.Aeson.Types
import Data.HashMap.Strict.InsOrd.Extended qualified as OM
import Data.Monoid (Dual (..), Endo (..))
import Hasura.Metadata.DTO.MetadataV3 (MetadataV3 (..))
import Hasura.Metadata.DTO.Placeholder (IsPlaceholder (placeholder))
import Hasura.Prelude
import Hasura.RQL.Types.Allowlist
import Hasura.RQL.Types.ApiLimit
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ComputedField
import Hasura.RQL.Types.CustomTypes
import Hasura.RQL.Types.Endpoint
import Hasura.RQL.Types.EventTrigger
import Hasura.RQL.Types.Function
import Hasura.RQL.Types.GraphqlSchemaIntrospection
import Hasura.RQL.Types.Metadata.Common
import Hasura.RQL.Types.Metadata.Serialization
import Hasura.RQL.Types.Network
import Hasura.RQL.Types.Permission
import Hasura.RQL.Types.RemoteSchema
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.SQL.Backend
import Hasura.SQL.BackendMap (BackendMap)
import Hasura.Session
import Hasura.Tracing (TraceT)
import Language.GraphQL.Draft.Syntax qualified as G
data MetadataVersion
= MVVersion1
| MVVersion2
| MVVersion3
deriving (Int -> MetadataVersion -> ShowS
[MetadataVersion] -> ShowS
MetadataVersion -> String
(Int -> MetadataVersion -> ShowS)
-> (MetadataVersion -> String)
-> ([MetadataVersion] -> ShowS)
-> Show MetadataVersion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetadataVersion] -> ShowS
$cshowList :: [MetadataVersion] -> ShowS
show :: MetadataVersion -> String
$cshow :: MetadataVersion -> String
showsPrec :: Int -> MetadataVersion -> ShowS
$cshowsPrec :: Int -> MetadataVersion -> ShowS
Show, MetadataVersion -> MetadataVersion -> Bool
(MetadataVersion -> MetadataVersion -> Bool)
-> (MetadataVersion -> MetadataVersion -> Bool)
-> Eq MetadataVersion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetadataVersion -> MetadataVersion -> Bool
$c/= :: MetadataVersion -> MetadataVersion -> Bool
== :: MetadataVersion -> MetadataVersion -> Bool
$c== :: MetadataVersion -> MetadataVersion -> Bool
Eq, (forall x. MetadataVersion -> Rep MetadataVersion x)
-> (forall x. Rep MetadataVersion x -> MetadataVersion)
-> Generic MetadataVersion
forall x. Rep MetadataVersion x -> MetadataVersion
forall x. MetadataVersion -> Rep MetadataVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MetadataVersion x -> MetadataVersion
$cfrom :: forall x. MetadataVersion -> Rep MetadataVersion x
Generic)
instance ToJSON MetadataVersion where
toJSON :: MetadataVersion -> Value
toJSON = \case
MetadataVersion
MVVersion1 -> Int -> Value
forall a. ToJSON a => a -> Value
toJSON @Int Int
1
MetadataVersion
MVVersion2 -> Int -> Value
forall a. ToJSON a => a -> Value
toJSON @Int Int
2
MetadataVersion
MVVersion3 -> Int -> Value
forall a. ToJSON a => a -> Value
toJSON @Int Int
3
instance FromJSON MetadataVersion where
parseJSON :: Value -> Parser MetadataVersion
parseJSON Value
v = do
Int
version :: Int <- Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
case Int
version of
Int
1 -> MetadataVersion -> Parser MetadataVersion
forall (f :: * -> *) a. Applicative f => a -> f a
pure MetadataVersion
MVVersion1
Int
2 -> MetadataVersion -> Parser MetadataVersion
forall (f :: * -> *) a. Applicative f => a -> f a
pure MetadataVersion
MVVersion2
Int
3 -> MetadataVersion -> Parser MetadataVersion
forall (f :: * -> *) a. Applicative f => a -> f a
pure MetadataVersion
MVVersion3
Int
i -> String -> Parser MetadataVersion
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser MetadataVersion)
-> String -> Parser MetadataVersion
forall a b. (a -> b) -> a -> b
$ String
"expected 1, 2 or 3, encountered " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
i
currentMetadataVersion :: MetadataVersion
currentMetadataVersion :: MetadataVersion
currentMetadataVersion = MetadataVersion
MVVersion3
data Metadata = Metadata
{ Metadata -> Sources
_metaSources :: Sources,
Metadata -> RemoteSchemas
_metaRemoteSchemas :: RemoteSchemas,
Metadata -> QueryCollections
_metaQueryCollections :: QueryCollections,
Metadata -> MetadataAllowlist
_metaAllowlist :: MetadataAllowlist,
Metadata -> CustomTypes
_metaCustomTypes :: CustomTypes,
Metadata -> Actions
_metaActions :: Actions,
Metadata -> CronTriggers
_metaCronTriggers :: CronTriggers,
Metadata -> Endpoints
_metaRestEndpoints :: Endpoints,
Metadata -> ApiLimit
_metaApiLimits :: ApiLimit,
Metadata -> MetricsConfig
_metaMetricsConfig :: MetricsConfig,
Metadata -> InheritedRoles
_metaInheritedRoles :: InheritedRoles,
Metadata -> SetGraphqlIntrospectionOptions
_metaSetGraphqlIntrospectionOptions :: SetGraphqlIntrospectionOptions,
Metadata -> Network
_metaNetwork :: Network,
Metadata -> BackendMap BackendConfigWrapper
_metaBackendConfigs :: BackendMap BackendConfigWrapper
}
deriving (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
showList :: [Metadata] -> ShowS
$cshowList :: [Metadata] -> ShowS
show :: Metadata -> String
$cshow :: Metadata -> String
showsPrec :: Int -> Metadata -> ShowS
$cshowsPrec :: Int -> Metadata -> ShowS
Show, Metadata -> Metadata -> Bool
(Metadata -> Metadata -> Bool)
-> (Metadata -> Metadata -> Bool) -> Eq Metadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Metadata -> Metadata -> Bool
$c/= :: Metadata -> Metadata -> Bool
== :: Metadata -> Metadata -> Bool
$c== :: Metadata -> Metadata -> Bool
Eq, (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
$cto :: forall x. Rep Metadata x -> Metadata
$cfrom :: forall x. Metadata -> Rep Metadata x
Generic)
$(makeLenses ''Metadata)
instance FromJSON Metadata where
parseJSON :: Value -> Parser Metadata
parseJSON = String -> (Object -> Parser Metadata) -> Value -> Parser Metadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Metadata" ((Object -> Parser Metadata) -> Value -> Parser Metadata)
-> (Object -> Parser Metadata) -> Value -> Parser Metadata
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
MetadataVersion
version <- Object
o Object -> Key -> Parser (Maybe MetadataVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"version" Parser (Maybe MetadataVersion)
-> MetadataVersion -> Parser MetadataVersion
forall a. Parser (Maybe a) -> a -> Parser a
.!= MetadataVersion
MVVersion1
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (MetadataVersion
version MetadataVersion -> MetadataVersion -> Bool
forall a. Eq a => a -> a -> Bool
/= MetadataVersion
MVVersion3) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$
String -> Parser ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser ()) -> String -> Parser ()
forall a b. (a -> b) -> a -> b
$ String
"unexpected metadata version from storage: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> MetadataVersion -> String
forall a. Show a => a -> String
show MetadataVersion
version
[Value]
rawSources <- Object
o Object -> Key -> Parser [Value]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"sources"
BackendMap BackendConfigWrapper
backendConfigs <- Object
o Object -> Key -> Parser (Maybe (BackendMap BackendConfigWrapper))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"backend_configs" Parser (Maybe (BackendMap BackendConfigWrapper))
-> BackendMap BackendConfigWrapper
-> Parser (BackendMap BackendConfigWrapper)
forall a. Parser (Maybe a) -> a -> Parser a
.!= BackendMap BackendConfigWrapper
forall a. Monoid a => a
mempty
Sources
sources <- (BackendSourceMetadata -> SourceName)
-> [BackendSourceMetadata] -> Sources
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL BackendSourceMetadata -> SourceName
getSourceName ([BackendSourceMetadata] -> Sources)
-> Parser [BackendSourceMetadata] -> Parser Sources
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser BackendSourceMetadata)
-> [Value] -> Parser [BackendSourceMetadata]
forall a b. (a -> Parser b) -> [a] -> Parser [b]
mapWithJSONPath Value -> Parser BackendSourceMetadata
parseSourceMetadata [Value]
rawSources Parser [BackendSourceMetadata]
-> JSONPathElement -> Parser [BackendSourceMetadata]
forall a. Parser a -> JSONPathElement -> Parser a
<?> Key -> JSONPathElement
Key Key
"sources"
Endpoints
endpoints <- (EndpointMetadata QueryReference -> EndpointName)
-> [EndpointMetadata QueryReference] -> Endpoints
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL EndpointMetadata QueryReference -> EndpointName
forall query. EndpointMetadata query -> EndpointName
_ceName ([EndpointMetadata QueryReference] -> Endpoints)
-> Parser [EndpointMetadata QueryReference] -> Parser Endpoints
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe [EndpointMetadata QueryReference])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"rest_endpoints" Parser (Maybe [EndpointMetadata QueryReference])
-> [EndpointMetadata QueryReference]
-> Parser [EndpointMetadata QueryReference]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
Network
network <- Object
o Object -> Key -> Parser (Maybe Network)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"network" Parser (Maybe Network) -> Network -> Parser Network
forall a. Parser (Maybe a) -> a -> Parser a
.!= Network
emptyNetwork
( RemoteSchemas
remoteSchemas,
QueryCollections
queryCollections,
MetadataAllowlist
allowlist,
CustomTypes
customTypes,
Actions
actions,
CronTriggers
cronTriggers,
ApiLimit
apiLimits,
MetricsConfig
metricsConfig,
InheritedRoles
inheritedRoles,
SetGraphqlIntrospectionOptions
disabledSchemaIntrospectionRoles
) <-
Object
-> Parser
(RemoteSchemas, QueryCollections, MetadataAllowlist, CustomTypes,
Actions, CronTriggers, ApiLimit, MetricsConfig, InheritedRoles,
SetGraphqlIntrospectionOptions)
parseNonSourcesMetadata Object
o
Metadata -> Parser Metadata
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Metadata -> Parser Metadata) -> Metadata -> Parser Metadata
forall a b. (a -> b) -> a -> b
$
Sources
-> RemoteSchemas
-> QueryCollections
-> MetadataAllowlist
-> CustomTypes
-> Actions
-> CronTriggers
-> Endpoints
-> ApiLimit
-> MetricsConfig
-> InheritedRoles
-> SetGraphqlIntrospectionOptions
-> Network
-> BackendMap BackendConfigWrapper
-> Metadata
Metadata
Sources
sources
RemoteSchemas
remoteSchemas
QueryCollections
queryCollections
MetadataAllowlist
allowlist
CustomTypes
customTypes
Actions
actions
CronTriggers
cronTriggers
Endpoints
endpoints
ApiLimit
apiLimits
MetricsConfig
metricsConfig
InheritedRoles
inheritedRoles
SetGraphqlIntrospectionOptions
disabledSchemaIntrospectionRoles
Network
network
BackendMap BackendConfigWrapper
backendConfigs
where
parseSourceMetadata :: Value -> Parser BackendSourceMetadata
parseSourceMetadata :: Value -> Parser BackendSourceMetadata
parseSourceMetadata = String
-> (Object -> Parser BackendSourceMetadata)
-> Value
-> Parser BackendSourceMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SourceMetadata" \Object
o -> do
AnyBackend BackendSourceKind
backendSourceKind <- (Value -> Parser (AnyBackend BackendSourceKind))
-> Object -> Key -> Parser (Maybe (AnyBackend BackendSourceKind))
forall a. (Value -> Parser a) -> Object -> Key -> Parser (Maybe a)
explicitParseFieldMaybe Value -> Parser (AnyBackend BackendSourceKind)
AB.parseBackendSourceKindFromJSON Object
o Key
"kind" Parser (Maybe (AnyBackend BackendSourceKind))
-> AnyBackend BackendSourceKind
-> Parser (AnyBackend BackendSourceKind)
forall a. Parser (Maybe a) -> a -> Parser a
.!= BackendSourceKind ('Postgres 'Vanilla)
-> AnyBackend BackendSourceKind
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend BackendSourceKind ('Postgres 'Vanilla)
PostgresVanillaKind
AnyBackend BackendSourceKind
-> (forall (b :: BackendType).
Backend b =>
BackendSourceKind b -> Parser BackendSourceMetadata)
-> Parser BackendSourceMetadata
forall (c :: BackendType -> Constraint) (i :: BackendType -> *) r.
AllBackendsSatisfy c =>
AnyBackend i -> (forall (b :: BackendType). c b => i b -> r) -> r
AB.dispatchAnyBackend @Backend
AnyBackend BackendSourceKind
backendSourceKind
( \(BackendSourceKind b
kind :: BackendSourceKind b) ->
AnyBackend SourceMetadata -> BackendSourceMetadata
BackendSourceMetadata (AnyBackend SourceMetadata -> BackendSourceMetadata)
-> (SourceMetadata b -> AnyBackend SourceMetadata)
-> SourceMetadata b
-> BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
forall (i :: BackendType -> *). HasTag b => i b -> AnyBackend i
AB.mkAnyBackend @b (SourceMetadata b -> BackendSourceMetadata)
-> Parser (SourceMetadata b) -> Parser BackendSourceMetadata
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BackendSourceKind b -> Value -> Parser (SourceMetadata b)
forall ctx a. FromJSONWithContext ctx a => ctx -> Value -> Parser a
parseJSONWithContext BackendSourceKind b
kind (Object -> Value
Object Object
o)
)
emptyMetadata :: Metadata
emptyMetadata :: Metadata
emptyMetadata =
Metadata :: Sources
-> RemoteSchemas
-> QueryCollections
-> MetadataAllowlist
-> CustomTypes
-> Actions
-> CronTriggers
-> Endpoints
-> ApiLimit
-> MetricsConfig
-> InheritedRoles
-> SetGraphqlIntrospectionOptions
-> Network
-> BackendMap BackendConfigWrapper
-> Metadata
Metadata
{ _metaSources :: Sources
_metaSources = Sources
forall a. Monoid a => a
mempty,
_metaRemoteSchemas :: RemoteSchemas
_metaRemoteSchemas = RemoteSchemas
forall a. Monoid a => a
mempty,
_metaQueryCollections :: QueryCollections
_metaQueryCollections = QueryCollections
forall a. Monoid a => a
mempty,
_metaAllowlist :: MetadataAllowlist
_metaAllowlist = MetadataAllowlist
forall a. Monoid a => a
mempty,
_metaActions :: Actions
_metaActions = Actions
forall a. Monoid a => a
mempty,
_metaCronTriggers :: CronTriggers
_metaCronTriggers = CronTriggers
forall a. Monoid a => a
mempty,
_metaRestEndpoints :: Endpoints
_metaRestEndpoints = Endpoints
forall a. Monoid a => a
mempty,
_metaInheritedRoles :: InheritedRoles
_metaInheritedRoles = InheritedRoles
forall a. Monoid a => a
mempty,
_metaSetGraphqlIntrospectionOptions :: SetGraphqlIntrospectionOptions
_metaSetGraphqlIntrospectionOptions = SetGraphqlIntrospectionOptions
forall a. Monoid a => a
mempty,
_metaCustomTypes :: CustomTypes
_metaCustomTypes = CustomTypes
emptyCustomTypes,
_metaApiLimits :: ApiLimit
_metaApiLimits = ApiLimit
emptyApiLimit,
_metaMetricsConfig :: MetricsConfig
_metaMetricsConfig = MetricsConfig
emptyMetricsConfig,
_metaNetwork :: Network
_metaNetwork = Network
emptyNetwork,
_metaBackendConfigs :: BackendMap BackendConfigWrapper
_metaBackendConfigs = BackendMap BackendConfigWrapper
forall a. Monoid a => a
mempty
}
tableMetadataSetter ::
(Backend b) =>
SourceName ->
TableName b ->
ASetter' Metadata (TableMetadata b)
tableMetadataSetter :: SourceName -> TableName b -> ASetter' Metadata (TableMetadata b)
tableMetadataSetter SourceName
source TableName b
table =
(Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((TableMetadata b -> Identity (TableMetadata b))
-> Sources -> Identity Sources)
-> ASetter' Metadata (TableMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
source ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((TableMetadata b -> Identity (TableMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (TableMetadata b -> Identity (TableMetadata b))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((TableMetadata b -> Identity (TableMetadata b))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (TableMetadata b -> Identity (TableMetadata b))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType). Lens' (SourceMetadata b) (Tables b)
smTables ((InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> ((TableMetadata b -> Identity (TableMetadata b))
-> InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> (TableMetadata b -> Identity (TableMetadata b))
-> SourceMetadata b
-> Identity (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (InsOrdHashMap (TableName b) (TableMetadata b))
-> Traversal'
(InsOrdHashMap (TableName b) (TableMetadata b))
(IxValue (InsOrdHashMap (TableName b) (TableMetadata b)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (InsOrdHashMap (TableName b) (TableMetadata b))
TableName b
table
functionMetadataSetter ::
(Backend b) =>
SourceName ->
FunctionName b ->
ASetter' Metadata (FunctionMetadata b)
functionMetadataSetter :: SourceName
-> FunctionName b -> ASetter' Metadata (FunctionMetadata b)
functionMetadataSetter SourceName
source FunctionName b
function =
(Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((FunctionMetadata b -> Identity (FunctionMetadata b))
-> Sources -> Identity Sources)
-> ASetter' Metadata (FunctionMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
source ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((FunctionMetadata b -> Identity (FunctionMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (FunctionMetadata b -> Identity (FunctionMetadata b))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((FunctionMetadata b -> Identity (FunctionMetadata b))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (FunctionMetadata b -> Identity (FunctionMetadata b))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType). Lens' (SourceMetadata b) (Functions b)
smFunctions ((InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> ((FunctionMetadata b -> Identity (FunctionMetadata b))
-> InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> (FunctionMetadata b -> Identity (FunctionMetadata b))
-> SourceMetadata b
-> Identity (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (InsOrdHashMap (FunctionName b) (FunctionMetadata b))
-> Traversal'
(InsOrdHashMap (FunctionName b) (FunctionMetadata b))
(IxValue (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (InsOrdHashMap (FunctionName b) (FunctionMetadata b))
FunctionName b
function
class (Monad m) => MetadataM m where
getMetadata :: m Metadata
putMetadata :: Metadata -> m ()
instance (MetadataM m) => MetadataM (ReaderT r m) where
getMetadata :: ReaderT r m Metadata
getMetadata = m Metadata -> ReaderT r m Metadata
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
putMetadata :: Metadata -> ReaderT r m ()
putMetadata = m () -> ReaderT r m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> ReaderT r m ())
-> (Metadata -> m ()) -> Metadata -> ReaderT r m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> m ()
forall (m :: * -> *). MetadataM m => Metadata -> m ()
putMetadata
instance (MetadataM m) => MetadataM (StateT r m) where
getMetadata :: StateT r m Metadata
getMetadata = m Metadata -> StateT r m Metadata
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
putMetadata :: Metadata -> StateT r m ()
putMetadata = m () -> StateT r m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> StateT r m ())
-> (Metadata -> m ()) -> Metadata -> StateT r m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> m ()
forall (m :: * -> *). MetadataM m => Metadata -> m ()
putMetadata
instance (MetadataM m) => MetadataM (TraceT m) where
getMetadata :: TraceT m Metadata
getMetadata = m Metadata -> TraceT m Metadata
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
putMetadata :: Metadata -> TraceT m ()
putMetadata = m () -> TraceT m ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> TraceT m ())
-> (Metadata -> m ()) -> Metadata -> TraceT m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> m ()
forall (m :: * -> *). MetadataM m => Metadata -> m ()
putMetadata
data MetadataNoSources = MetadataNoSources
{ MetadataNoSources -> Tables ('Postgres 'Vanilla)
_mnsTables :: Tables ('Postgres 'Vanilla),
MetadataNoSources -> Functions ('Postgres 'Vanilla)
_mnsFunctions :: Functions ('Postgres 'Vanilla),
MetadataNoSources -> RemoteSchemas
_mnsRemoteSchemas :: RemoteSchemas,
MetadataNoSources -> QueryCollections
_mnsQueryCollections :: QueryCollections,
MetadataNoSources -> MetadataAllowlist
_mnsAllowlist :: MetadataAllowlist,
MetadataNoSources -> CustomTypes
_mnsCustomTypes :: CustomTypes,
MetadataNoSources -> Actions
_mnsActions :: Actions,
MetadataNoSources -> CronTriggers
_mnsCronTriggers :: CronTriggers
}
deriving (MetadataNoSources -> MetadataNoSources -> Bool
(MetadataNoSources -> MetadataNoSources -> Bool)
-> (MetadataNoSources -> MetadataNoSources -> Bool)
-> Eq MetadataNoSources
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetadataNoSources -> MetadataNoSources -> Bool
$c/= :: MetadataNoSources -> MetadataNoSources -> Bool
== :: MetadataNoSources -> MetadataNoSources -> Bool
$c== :: MetadataNoSources -> MetadataNoSources -> Bool
Eq)
$(deriveToJSON hasuraJSON ''MetadataNoSources)
instance FromJSON MetadataNoSources where
parseJSON :: Value -> Parser MetadataNoSources
parseJSON = String
-> (Object -> Parser MetadataNoSources)
-> Value
-> Parser MetadataNoSources
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"MetadataNoSources" ((Object -> Parser MetadataNoSources)
-> Value -> Parser MetadataNoSources)
-> (Object -> Parser MetadataNoSources)
-> Value
-> Parser MetadataNoSources
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
MetadataVersion
version <- Object
o Object -> Key -> Parser (Maybe MetadataVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"version" Parser (Maybe MetadataVersion)
-> MetadataVersion -> Parser MetadataVersion
forall a. Parser (Maybe a) -> a -> Parser a
.!= MetadataVersion
MVVersion1
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables, InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions) <-
case MetadataVersion
version of
MetadataVersion
MVVersion1 -> do
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables <- (TableMetadata ('Postgres 'Vanilla) -> QualifiedTable)
-> [TableMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL TableMetadata ('Postgres 'Vanilla) -> QualifiedTable
forall (b :: BackendType). TableMetadata b -> TableName b
_tmTable ([TableMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Parser [TableMetadata ('Postgres 'Vanilla)]
-> Parser
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [TableMetadata ('Postgres 'Vanilla)]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tables"
[QualifiedFunction]
functionList <- Object
o Object -> Key -> Parser (Maybe [QualifiedFunction])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"functions" Parser (Maybe [QualifiedFunction])
-> [QualifiedFunction] -> Parser [QualifiedFunction]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
let functions :: InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions = [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
forall k v. (Eq k, Hashable k) => [(k, v)] -> InsOrdHashMap k v
OM.fromList ([(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
-> [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
forall a b. (a -> b) -> a -> b
$
((QualifiedFunction
-> (QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla)))
-> [QualifiedFunction]
-> [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))])
-> [QualifiedFunction]
-> (QualifiedFunction
-> (QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla)))
-> [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (QualifiedFunction
-> (QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla)))
-> [QualifiedFunction]
-> [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))]
forall a b. (a -> b) -> [a] -> [b]
map [QualifiedFunction]
functionList ((QualifiedFunction
-> (QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla)))
-> [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))])
-> (QualifiedFunction
-> (QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla)))
-> [(QualifiedFunction, FunctionMetadata ('Postgres 'Vanilla))]
forall a b. (a -> b) -> a -> b
$
\QualifiedFunction
function -> (QualifiedFunction
function, FunctionName ('Postgres 'Vanilla)
-> FunctionConfig
-> [FunctionPermissionInfo]
-> Maybe Text
-> FunctionMetadata ('Postgres 'Vanilla)
forall (b :: BackendType).
FunctionName b
-> FunctionConfig
-> [FunctionPermissionInfo]
-> Maybe Text
-> FunctionMetadata b
FunctionMetadata FunctionName ('Postgres 'Vanilla)
QualifiedFunction
function FunctionConfig
emptyFunctionConfig [FunctionPermissionInfo]
forall a. Monoid a => a
mempty Maybe Text
forall a. Maybe a
Nothing)
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)),
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
-> Parser
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)),
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables, InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions)
MetadataVersion
MVVersion2 -> do
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables <- (TableMetadata ('Postgres 'Vanilla) -> QualifiedTable)
-> [TableMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla))
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL TableMetadata ('Postgres 'Vanilla) -> QualifiedTable
forall (b :: BackendType). TableMetadata b -> TableName b
_tmTable ([TableMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
-> Parser [TableMetadata ('Postgres 'Vanilla)]
-> Parser
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser [TableMetadata ('Postgres 'Vanilla)]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tables"
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions <- (FunctionMetadata ('Postgres 'Vanilla) -> QualifiedFunction)
-> [FunctionMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
forall k a.
(Eq k, Hashable k) =>
(a -> k) -> [a] -> InsOrdHashMap k a
oMapFromL FunctionMetadata ('Postgres 'Vanilla) -> QualifiedFunction
forall (b :: BackendType). FunctionMetadata b -> FunctionName b
_fmFunction ([FunctionMetadata ('Postgres 'Vanilla)]
-> InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
-> Parser [FunctionMetadata ('Postgres 'Vanilla)]
-> Parser
(InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object
-> Key -> Parser (Maybe [FunctionMetadata ('Postgres 'Vanilla)])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"functions" Parser (Maybe [FunctionMetadata ('Postgres 'Vanilla)])
-> [FunctionMetadata ('Postgres 'Vanilla)]
-> Parser [FunctionMetadata ('Postgres 'Vanilla)]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)),
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
-> Parser
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)),
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables, InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions)
MetadataVersion
MVVersion3 -> String
-> Parser
(InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla)),
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla)))
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected version for metadata without sources: 3"
( RemoteSchemas
remoteSchemas,
QueryCollections
queryCollections,
MetadataAllowlist
allowlist,
CustomTypes
customTypes,
Actions
actions,
CronTriggers
cronTriggers,
ApiLimit
_,
MetricsConfig
_,
InheritedRoles
_,
SetGraphqlIntrospectionOptions
_
) <-
Object
-> Parser
(RemoteSchemas, QueryCollections, MetadataAllowlist, CustomTypes,
Actions, CronTriggers, ApiLimit, MetricsConfig, InheritedRoles,
SetGraphqlIntrospectionOptions)
parseNonSourcesMetadata Object
o
MetadataNoSources -> Parser MetadataNoSources
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MetadataNoSources -> Parser MetadataNoSources)
-> MetadataNoSources -> Parser MetadataNoSources
forall a b. (a -> b) -> a -> b
$
Tables ('Postgres 'Vanilla)
-> Functions ('Postgres 'Vanilla)
-> RemoteSchemas
-> QueryCollections
-> MetadataAllowlist
-> CustomTypes
-> Actions
-> CronTriggers
-> MetadataNoSources
MetadataNoSources
Tables ('Postgres 'Vanilla)
InsOrdHashMap QualifiedTable (TableMetadata ('Postgres 'Vanilla))
tables
Functions ('Postgres 'Vanilla)
InsOrdHashMap
QualifiedFunction (FunctionMetadata ('Postgres 'Vanilla))
functions
RemoteSchemas
remoteSchemas
QueryCollections
queryCollections
MetadataAllowlist
allowlist
CustomTypes
customTypes
Actions
actions
CronTriggers
cronTriggers
newtype MetadataModifier = MetadataModifier {MetadataModifier -> Metadata -> Metadata
runMetadataModifier :: Metadata -> Metadata}
deriving (b -> MetadataModifier -> MetadataModifier
NonEmpty MetadataModifier -> MetadataModifier
MetadataModifier -> MetadataModifier -> MetadataModifier
(MetadataModifier -> MetadataModifier -> MetadataModifier)
-> (NonEmpty MetadataModifier -> MetadataModifier)
-> (forall b.
Integral b =>
b -> MetadataModifier -> MetadataModifier)
-> Semigroup MetadataModifier
forall b. Integral b => b -> MetadataModifier -> MetadataModifier
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: b -> MetadataModifier -> MetadataModifier
$cstimes :: forall b. Integral b => b -> MetadataModifier -> MetadataModifier
sconcat :: NonEmpty MetadataModifier -> MetadataModifier
$csconcat :: NonEmpty MetadataModifier -> MetadataModifier
<> :: MetadataModifier -> MetadataModifier -> MetadataModifier
$c<> :: MetadataModifier -> MetadataModifier -> MetadataModifier
Semigroup, Semigroup MetadataModifier
MetadataModifier
Semigroup MetadataModifier
-> MetadataModifier
-> (MetadataModifier -> MetadataModifier -> MetadataModifier)
-> ([MetadataModifier] -> MetadataModifier)
-> Monoid MetadataModifier
[MetadataModifier] -> MetadataModifier
MetadataModifier -> MetadataModifier -> MetadataModifier
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [MetadataModifier] -> MetadataModifier
$cmconcat :: [MetadataModifier] -> MetadataModifier
mappend :: MetadataModifier -> MetadataModifier -> MetadataModifier
$cmappend :: MetadataModifier -> MetadataModifier -> MetadataModifier
mempty :: MetadataModifier
$cmempty :: MetadataModifier
$cp1Monoid :: Semigroup MetadataModifier
Monoid) via (Dual (Endo Metadata))
dropTableInMetadata ::
forall b. (Backend b) => SourceName -> TableName b -> MetadataModifier
dropTableInMetadata :: SourceName -> TableName b -> MetadataModifier
dropTableInMetadata SourceName
source TableName b
table =
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ (Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> Sources -> Identity Sources)
-> (InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
source ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Backend b => Prism' BackendSourceMetadata (SourceMetadata b)
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b) ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType). Lens' (SourceMetadata b) (Tables b)
smTables ((InsOrdHashMap (TableName b) (TableMetadata b)
-> Identity (InsOrdHashMap (TableName b) (TableMetadata b)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap (TableName b) (TableMetadata b)
-> InsOrdHashMap (TableName b) (TableMetadata b))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ TableName b
-> InsOrdHashMap (TableName b) (TableMetadata b)
-> InsOrdHashMap (TableName b) (TableMetadata b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete TableName b
table
dropRelationshipInMetadata ::
RelName -> TableMetadata b -> TableMetadata b
dropRelationshipInMetadata :: RelName -> TableMetadata b -> TableMetadata b
dropRelationshipInMetadata RelName
relName =
((Relationships (ObjRelDef b)
-> Identity (Relationships (ObjRelDef b)))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (Relationships (ObjRelDef b))
tmObjectRelationships ((Relationships (ObjRelDef b)
-> Identity (Relationships (ObjRelDef b)))
-> TableMetadata b -> Identity (TableMetadata b))
-> (Relationships (ObjRelDef b) -> Relationships (ObjRelDef b))
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RelName
-> Relationships (ObjRelDef b) -> Relationships (ObjRelDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RelName
relName)
(TableMetadata b -> TableMetadata b)
-> (TableMetadata b -> TableMetadata b)
-> TableMetadata b
-> TableMetadata b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Relationships (ArrRelDef b)
-> Identity (Relationships (ArrRelDef b)))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (Relationships (ArrRelDef b))
tmArrayRelationships ((Relationships (ArrRelDef b)
-> Identity (Relationships (ArrRelDef b)))
-> TableMetadata b -> Identity (TableMetadata b))
-> (Relationships (ArrRelDef b) -> Relationships (ArrRelDef b))
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RelName
-> Relationships (ArrRelDef b) -> Relationships (ArrRelDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RelName
relName)
dropPermissionInMetadata ::
RoleName -> PermType -> TableMetadata b -> TableMetadata b
dropPermissionInMetadata :: RoleName -> PermType -> TableMetadata b -> TableMetadata b
dropPermissionInMetadata RoleName
rn = \case
PermType
PTInsert -> (Permissions (InsPermDef b)
-> Identity (Permissions (InsPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (InsPermDef b))
tmInsertPermissions ((Permissions (InsPermDef b)
-> Identity (Permissions (InsPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b))
-> (Permissions (InsPermDef b) -> Permissions (InsPermDef b))
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RoleName
-> Permissions (InsPermDef b) -> Permissions (InsPermDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RoleName
rn
PermType
PTSelect -> (Permissions (SelPermDef b)
-> Identity (Permissions (SelPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (SelPermDef b))
tmSelectPermissions ((Permissions (SelPermDef b)
-> Identity (Permissions (SelPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b))
-> (Permissions (SelPermDef b) -> Permissions (SelPermDef b))
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RoleName
-> Permissions (SelPermDef b) -> Permissions (SelPermDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RoleName
rn
PermType
PTDelete -> (Permissions (DelPermDef b)
-> Identity (Permissions (DelPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (DelPermDef b))
tmDeletePermissions ((Permissions (DelPermDef b)
-> Identity (Permissions (DelPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b))
-> (Permissions (DelPermDef b) -> Permissions (DelPermDef b))
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RoleName
-> Permissions (DelPermDef b) -> Permissions (DelPermDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RoleName
rn
PermType
PTUpdate -> (Permissions (UpdPermDef b)
-> Identity (Permissions (UpdPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (Permissions (UpdPermDef b))
tmUpdatePermissions ((Permissions (UpdPermDef b)
-> Identity (Permissions (UpdPermDef b)))
-> TableMetadata b -> Identity (TableMetadata b))
-> (Permissions (UpdPermDef b) -> Permissions (UpdPermDef b))
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RoleName
-> Permissions (UpdPermDef b) -> Permissions (UpdPermDef b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RoleName
rn
dropComputedFieldInMetadata ::
ComputedFieldName -> TableMetadata b -> TableMetadata b
dropComputedFieldInMetadata :: ComputedFieldName -> TableMetadata b -> TableMetadata b
dropComputedFieldInMetadata ComputedFieldName
name =
(ComputedFields b -> Identity (ComputedFields b))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (ComputedFields b)
tmComputedFields ((ComputedFields b -> Identity (ComputedFields b))
-> TableMetadata b -> Identity (TableMetadata b))
-> (ComputedFields b -> ComputedFields b)
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ComputedFieldName -> ComputedFields b -> ComputedFields b
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete ComputedFieldName
name
dropEventTriggerInMetadata :: TriggerName -> TableMetadata b -> TableMetadata b
dropEventTriggerInMetadata :: TriggerName -> TableMetadata b -> TableMetadata b
dropEventTriggerInMetadata TriggerName
name =
(EventTriggers b -> Identity (EventTriggers b))
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) (EventTriggers b)
tmEventTriggers ((EventTriggers b -> Identity (EventTriggers b))
-> TableMetadata b -> Identity (TableMetadata b))
-> (EventTriggers b -> EventTriggers b)
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ TriggerName -> EventTriggers b -> EventTriggers b
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete TriggerName
name
dropRemoteRelationshipInMetadata ::
RelName -> TableMetadata b -> TableMetadata b
dropRemoteRelationshipInMetadata :: RelName -> TableMetadata b -> TableMetadata b
dropRemoteRelationshipInMetadata RelName
name =
(RemoteRelationships -> Identity RemoteRelationships)
-> TableMetadata b -> Identity (TableMetadata b)
forall (b :: BackendType).
Lens' (TableMetadata b) RemoteRelationships
tmRemoteRelationships ((RemoteRelationships -> Identity RemoteRelationships)
-> TableMetadata b -> Identity (TableMetadata b))
-> (RemoteRelationships -> RemoteRelationships)
-> TableMetadata b
-> TableMetadata b
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RelName -> RemoteRelationships -> RemoteRelationships
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RelName
name
dropFunctionInMetadata ::
forall b. (Backend b) => SourceName -> FunctionName b -> MetadataModifier
dropFunctionInMetadata :: SourceName -> FunctionName b -> MetadataModifier
dropFunctionInMetadata SourceName
source FunctionName b
function =
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$
(Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> Sources -> Identity Sources)
-> (InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
source ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (b :: BackendType). Lens' (SourceMetadata b) (Functions b)
Lens'
(SourceMetadata b)
(InsOrdHashMap (FunctionName b) (FunctionMetadata b))
smFunctions @b) ((InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> Identity (InsOrdHashMap (FunctionName b) (FunctionMetadata b)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> InsOrdHashMap (FunctionName b) (FunctionMetadata b))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ FunctionName b
-> InsOrdHashMap (FunctionName b) (FunctionMetadata b)
-> InsOrdHashMap (FunctionName b) (FunctionMetadata b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete FunctionName b
function
dropRemoteSchemaInMetadata :: RemoteSchemaName -> MetadataModifier
dropRemoteSchemaInMetadata :: RemoteSchemaName -> MetadataModifier
dropRemoteSchemaInMetadata RemoteSchemaName
name =
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ (RemoteSchemas -> Identity RemoteSchemas)
-> Metadata -> Identity Metadata
Lens' Metadata RemoteSchemas
metaRemoteSchemas ((RemoteSchemas -> Identity RemoteSchemas)
-> Metadata -> Identity Metadata)
-> (RemoteSchemas -> RemoteSchemas) -> Metadata -> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RemoteSchemaName -> RemoteSchemas -> RemoteSchemas
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RemoteSchemaName
name
dropRemoteSchemaPermissionInMetadata :: RemoteSchemaName -> RoleName -> MetadataModifier
dropRemoteSchemaPermissionInMetadata :: RemoteSchemaName -> RoleName -> MetadataModifier
dropRemoteSchemaPermissionInMetadata RemoteSchemaName
remoteSchemaName RoleName
roleName =
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ (RemoteSchemas -> Identity RemoteSchemas)
-> Metadata -> Identity Metadata
Lens' Metadata RemoteSchemas
metaRemoteSchemas ((RemoteSchemas -> Identity RemoteSchemas)
-> Metadata -> Identity Metadata)
-> (([RemoteSchemaPermissionMetadata]
-> Identity [RemoteSchemaPermissionMetadata])
-> RemoteSchemas -> Identity RemoteSchemas)
-> ([RemoteSchemaPermissionMetadata]
-> Identity [RemoteSchemaPermissionMetadata])
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index RemoteSchemas
-> Traversal' RemoteSchemas (IxValue RemoteSchemas)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index RemoteSchemas
RemoteSchemaName
remoteSchemaName ((RemoteSchemaMetadata -> Identity RemoteSchemaMetadata)
-> RemoteSchemas -> Identity RemoteSchemas)
-> (([RemoteSchemaPermissionMetadata]
-> Identity [RemoteSchemaPermissionMetadata])
-> RemoteSchemaMetadata -> Identity RemoteSchemaMetadata)
-> ([RemoteSchemaPermissionMetadata]
-> Identity [RemoteSchemaPermissionMetadata])
-> RemoteSchemas
-> Identity RemoteSchemas
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([RemoteSchemaPermissionMetadata]
-> Identity [RemoteSchemaPermissionMetadata])
-> RemoteSchemaMetadata -> Identity RemoteSchemaMetadata
Lens' RemoteSchemaMetadata [RemoteSchemaPermissionMetadata]
rsmPermissions (([RemoteSchemaPermissionMetadata]
-> Identity [RemoteSchemaPermissionMetadata])
-> Metadata -> Identity Metadata)
-> ([RemoteSchemaPermissionMetadata]
-> [RemoteSchemaPermissionMetadata])
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (RemoteSchemaPermissionMetadata -> Bool)
-> [RemoteSchemaPermissionMetadata]
-> [RemoteSchemaPermissionMetadata]
forall a. (a -> Bool) -> [a] -> [a]
filter (RoleName -> RoleName -> Bool
forall a. Eq a => a -> a -> Bool
(/=) RoleName
roleName (RoleName -> Bool)
-> (RemoteSchemaPermissionMetadata -> RoleName)
-> RemoteSchemaPermissionMetadata
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RemoteSchemaPermissionMetadata -> RoleName
_rspmRole)
dropRemoteSchemaRemoteRelationshipInMetadata :: RemoteSchemaName -> G.Name -> RelName -> MetadataModifier
dropRemoteSchemaRemoteRelationshipInMetadata :: RemoteSchemaName -> Name -> RelName -> MetadataModifier
dropRemoteSchemaRemoteRelationshipInMetadata RemoteSchemaName
remoteSchemaName Name
typeName RelName
relationshipName =
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier ((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$
(RemoteSchemas -> Identity RemoteSchemas)
-> Metadata -> Identity Metadata
Lens' Metadata RemoteSchemas
metaRemoteSchemas
((RemoteSchemas -> Identity RemoteSchemas)
-> Metadata -> Identity Metadata)
-> ((RemoteRelationships -> Identity RemoteRelationships)
-> RemoteSchemas -> Identity RemoteSchemas)
-> (RemoteRelationships -> Identity RemoteRelationships)
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index RemoteSchemas
-> Traversal' RemoteSchemas (IxValue RemoteSchemas)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index RemoteSchemas
RemoteSchemaName
remoteSchemaName
((RemoteSchemaMetadata -> Identity RemoteSchemaMetadata)
-> RemoteSchemas -> Identity RemoteSchemas)
-> ((RemoteRelationships -> Identity RemoteRelationships)
-> RemoteSchemaMetadata -> Identity RemoteSchemaMetadata)
-> (RemoteRelationships -> Identity RemoteRelationships)
-> RemoteSchemas
-> Identity RemoteSchemas
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SchemaRemoteRelationships -> Identity SchemaRemoteRelationships)
-> RemoteSchemaMetadata -> Identity RemoteSchemaMetadata
Lens' RemoteSchemaMetadata SchemaRemoteRelationships
rsmRemoteRelationships
((SchemaRemoteRelationships -> Identity SchemaRemoteRelationships)
-> RemoteSchemaMetadata -> Identity RemoteSchemaMetadata)
-> ((RemoteRelationships -> Identity RemoteRelationships)
-> SchemaRemoteRelationships -> Identity SchemaRemoteRelationships)
-> (RemoteRelationships -> Identity RemoteRelationships)
-> RemoteSchemaMetadata
-> Identity RemoteSchemaMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index SchemaRemoteRelationships
-> Traversal'
SchemaRemoteRelationships (IxValue SchemaRemoteRelationships)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index SchemaRemoteRelationships
Name
typeName
((RemoteSchemaTypeRelationships
-> Identity RemoteSchemaTypeRelationships)
-> SchemaRemoteRelationships -> Identity SchemaRemoteRelationships)
-> ((RemoteRelationships -> Identity RemoteRelationships)
-> RemoteSchemaTypeRelationships
-> Identity RemoteSchemaTypeRelationships)
-> (RemoteRelationships -> Identity RemoteRelationships)
-> SchemaRemoteRelationships
-> Identity SchemaRemoteRelationships
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RemoteRelationships -> Identity RemoteRelationships)
-> RemoteSchemaTypeRelationships
-> Identity RemoteSchemaTypeRelationships
Lens' RemoteSchemaTypeRelationships RemoteRelationships
rstrsRelationships
((RemoteRelationships -> Identity RemoteRelationships)
-> Metadata -> Identity Metadata)
-> (RemoteRelationships -> RemoteRelationships)
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ RelName -> RemoteRelationships -> RemoteRelationships
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
OM.delete RelName
relationshipName
metadataToOrdJSON :: Metadata -> AO.Value
metadataToOrdJSON :: Metadata -> Value
metadataToOrdJSON
( Metadata
Sources
sources
RemoteSchemas
remoteSchemas
QueryCollections
queryCollections
MetadataAllowlist
allowlist
CustomTypes
customTypes
Actions
actions
CronTriggers
cronTriggers
Endpoints
endpoints
ApiLimit
apiLimits
MetricsConfig
metricsConfig
InheritedRoles
inheritedRoles
SetGraphqlIntrospectionOptions
introspectionDisabledRoles
Network
networkConfig
BackendMap BackendConfigWrapper
backendConfigs
) =
[(Text, Value)] -> Value
AO.object ([(Text, Value)] -> Value) -> [(Text, Value)] -> Value
forall a b. (a -> b) -> a -> b
$
[(Text, Value)
versionPair, (Text, Value)
sourcesPair]
[(Text, Value)] -> [(Text, Value)] -> [(Text, Value)]
forall a. Semigroup a => a -> a -> a
<> [Maybe (Text, Value)] -> [(Text, Value)]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes
[ Maybe (Text, Value)
remoteSchemasPair,
Maybe (Text, Value)
queryCollectionsPair,
Maybe (Text, Value)
allowlistPair,
Maybe (Text, Value)
actionsPair,
Maybe (Text, Value)
customTypesPair,
Maybe (Text, Value)
cronTriggersPair,
Maybe (Text, Value)
endpointsPair,
Maybe (Text, Value)
apiLimitsPair,
Maybe (Text, Value)
metricsConfigPair,
Maybe (Text, Value)
inheritedRolesPair,
Maybe (Text, Value)
introspectionDisabledRolesPair,
Maybe (Text, Value)
networkPair,
Maybe (Text, Value)
backendConfigsPair
]
where
versionPair :: (Text, Value)
versionPair = (Text
"version", MetadataVersion -> Value
forall a. ToJSON a => a -> Value
AO.toOrdered MetadataVersion
currentMetadataVersion)
sourcesPair :: (Text, Value)
sourcesPair = (Text
"sources", Array -> Value
AO.Array (Array -> Value) -> Array -> Value
forall a b. (a -> b) -> a -> b
$ Sources -> Array
sourcesToOrdJSONList Sources
sources)
remoteSchemasPair :: Maybe (Text, Value)
remoteSchemasPair = (Text
"remote_schemas",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RemoteSchemas -> Maybe Array
remoteSchemasToOrdJSONList RemoteSchemas
remoteSchemas
queryCollectionsPair :: Maybe (Text, Value)
queryCollectionsPair = (Text
"query_collections",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> QueryCollections -> Maybe Array
queryCollectionsToOrdJSONList QueryCollections
queryCollections
allowlistPair :: Maybe (Text, Value)
allowlistPair = (Text
"allowlist",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MetadataAllowlist -> Maybe Array
allowlistToOrdJSONList MetadataAllowlist
allowlist
customTypesPair :: Maybe (Text, Value)
customTypesPair = (Text
"custom_types",) (Value -> (Text, Value))
-> (Object -> Value) -> Object -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Object -> Value
AO.Object (Object -> (Text, Value)) -> Maybe Object -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CustomTypes -> Maybe Object
customTypesToOrdJSON CustomTypes
customTypes
actionsPair :: Maybe (Text, Value)
actionsPair = (Text
"actions",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Actions -> Maybe Array
actionMetadataToOrdJSONList Actions
actions
cronTriggersPair :: Maybe (Text, Value)
cronTriggersPair = (Text
"cron_triggers",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CronTriggers -> Maybe Array
cronTriggersToOrdJSONList CronTriggers
cronTriggers
inheritedRolesPair :: Maybe (Text, Value)
inheritedRolesPair = (Text
"inherited_roles",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InheritedRoles -> Maybe Array
inheritedRolesToOrdJSONList InheritedRoles
inheritedRoles
endpointsPair :: Maybe (Text, Value)
endpointsPair = (Text
"rest_endpoints",) (Value -> (Text, Value))
-> (Array -> Value) -> Array -> (Text, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array -> Value
AO.Array (Array -> (Text, Value)) -> Maybe Array -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Endpoints -> Maybe Array
endpointsToOrdJSONList Endpoints
endpoints
apiLimitsPair :: Maybe (Text, Value)
apiLimitsPair = (Text
"api_limits",) (Value -> (Text, Value)) -> Maybe Value -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ApiLimit -> Maybe Value
apiLimitsToOrdJSON ApiLimit
apiLimits
metricsConfigPair :: Maybe (Text, Value)
metricsConfigPair = (Text
"metrics_config",) (Value -> (Text, Value)) -> Maybe Value -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MetricsConfig -> Maybe Value
metricsConfigToOrdJSON MetricsConfig
metricsConfig
introspectionDisabledRolesPair :: Maybe (Text, Value)
introspectionDisabledRolesPair =
(Text
"graphql_schema_introspection",) (Value -> (Text, Value)) -> Maybe Value -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SetGraphqlIntrospectionOptions -> Maybe Value
introspectionDisabledRolesToOrdJSON SetGraphqlIntrospectionOptions
introspectionDisabledRoles
networkPair :: Maybe (Text, Value)
networkPair = (Text
"network",) (Value -> (Text, Value)) -> Maybe Value -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Network -> Maybe Value
networkConfigToOrdJSON Network
networkConfig
backendConfigsPair :: Maybe (Text, Value)
backendConfigsPair = (Text
"backend_configs",) (Value -> (Text, Value)) -> Maybe Value -> Maybe (Text, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BackendMap BackendConfigWrapper -> Maybe Value
backendConfigsToOrdJSON BackendMap BackendConfigWrapper
backendConfigs
instance ToJSON Metadata where
toJSON :: Metadata -> Value
toJSON = Value -> Value
AO.fromOrdered (Value -> Value) -> (Metadata -> Value) -> Metadata -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Metadata -> Value
metadataToOrdJSON
metadataToDTO :: Metadata -> MetadataV3
metadataToDTO :: Metadata -> MetadataV3
metadataToDTO
( Metadata
Sources
sources
RemoteSchemas
remoteSchemas
QueryCollections
queryCollections
MetadataAllowlist
allowlist
CustomTypes
customTypes
Actions
actions
CronTriggers
cronTriggers
Endpoints
endpoints
ApiLimit
apiLimits
MetricsConfig
metricsConfig
InheritedRoles
inheritedRoles
SetGraphqlIntrospectionOptions
introspectionDisabledRoles
Network
networkConfig
BackendMap BackendConfigWrapper
backendConfigs
) =
MetadataV3 :: Sources
-> Maybe PlaceholderArray
-> Maybe PlaceholderArray
-> Maybe PlaceholderArray
-> Maybe PlaceholderArray
-> Maybe PlaceholderObject
-> Maybe PlaceholderArray
-> Maybe PlaceholderArray
-> Maybe PlaceholderObject
-> Maybe PlaceholderObject
-> Maybe PlaceholderArray
-> Maybe PlaceholderObject
-> Maybe PlaceholderObject
-> Maybe PlaceholderObject
-> MetadataV3
MetadataV3
{ metaV3Sources :: Sources
metaV3Sources = Sources
sources,
metaV3RemoteSchemas :: Maybe PlaceholderArray
metaV3RemoteSchemas = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> RemoteSchemas -> Maybe Array
remoteSchemasToOrdJSONList RemoteSchemas
remoteSchemas,
metaV3QueryCollections :: Maybe PlaceholderArray
metaV3QueryCollections = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> QueryCollections -> Maybe Array
queryCollectionsToOrdJSONList QueryCollections
queryCollections,
metaV3Allowlist :: Maybe PlaceholderArray
metaV3Allowlist = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MetadataAllowlist -> Maybe Array
allowlistToOrdJSONList MetadataAllowlist
allowlist,
metaV3Actions :: Maybe PlaceholderArray
metaV3Actions = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Actions -> Maybe Array
actionMetadataToOrdJSONList Actions
actions,
metaV3CustomTypes :: Maybe PlaceholderObject
metaV3CustomTypes = Object -> PlaceholderObject
forall p a. IsPlaceholder p a => a -> p
placeholder (Object -> PlaceholderObject)
-> Maybe Object -> Maybe PlaceholderObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CustomTypes -> Maybe Object
customTypesToOrdJSON CustomTypes
customTypes,
metaV3CronTriggers :: Maybe PlaceholderArray
metaV3CronTriggers = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CronTriggers -> Maybe Array
cronTriggersToOrdJSONList CronTriggers
cronTriggers,
metaV3RestEndpoints :: Maybe PlaceholderArray
metaV3RestEndpoints = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Endpoints -> Maybe Array
endpointsToOrdJSONList Endpoints
endpoints,
metaV3ApiLimits :: Maybe PlaceholderObject
metaV3ApiLimits = Object -> PlaceholderObject
forall p a. IsPlaceholder p a => a -> p
placeholder (Object -> PlaceholderObject)
-> (Value -> Object) -> Value -> PlaceholderObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Object
objectFromOrdJSON (Value -> PlaceholderObject)
-> Maybe Value -> Maybe PlaceholderObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ApiLimit -> Maybe Value
apiLimitsToOrdJSON ApiLimit
apiLimits,
metaV3MetricsConfig :: Maybe PlaceholderObject
metaV3MetricsConfig = Object -> PlaceholderObject
forall p a. IsPlaceholder p a => a -> p
placeholder (Object -> PlaceholderObject)
-> (Value -> Object) -> Value -> PlaceholderObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Object
objectFromOrdJSON (Value -> PlaceholderObject)
-> Maybe Value -> Maybe PlaceholderObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MetricsConfig -> Maybe Value
metricsConfigToOrdJSON MetricsConfig
metricsConfig,
metaV3InheritedRoles :: Maybe PlaceholderArray
metaV3InheritedRoles = Array -> PlaceholderArray
forall p a. IsPlaceholder p a => a -> p
placeholder (Array -> PlaceholderArray)
-> Maybe Array -> Maybe PlaceholderArray
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InheritedRoles -> Maybe Array
inheritedRolesToOrdJSONList InheritedRoles
inheritedRoles,
metaV3GraphqlSchemaIntrospection :: Maybe PlaceholderObject
metaV3GraphqlSchemaIntrospection = Object -> PlaceholderObject
forall p a. IsPlaceholder p a => a -> p
placeholder (Object -> PlaceholderObject)
-> (Value -> Object) -> Value -> PlaceholderObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Object
objectFromOrdJSON (Value -> PlaceholderObject)
-> Maybe Value -> Maybe PlaceholderObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SetGraphqlIntrospectionOptions -> Maybe Value
introspectionDisabledRolesToOrdJSON SetGraphqlIntrospectionOptions
introspectionDisabledRoles,
metaV3Network :: Maybe PlaceholderObject
metaV3Network = Object -> PlaceholderObject
forall p a. IsPlaceholder p a => a -> p
placeholder (Object -> PlaceholderObject)
-> (Value -> Object) -> Value -> PlaceholderObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Object
objectFromOrdJSON (Value -> PlaceholderObject)
-> Maybe Value -> Maybe PlaceholderObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Network -> Maybe Value
networkConfigToOrdJSON Network
networkConfig,
metaV3BackendConfigs :: Maybe PlaceholderObject
metaV3BackendConfigs = Object -> PlaceholderObject
forall p a. IsPlaceholder p a => a -> p
placeholder (Object -> PlaceholderObject)
-> (Value -> Object) -> Value -> PlaceholderObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Object
objectFromOrdJSON (Value -> PlaceholderObject)
-> Maybe Value -> Maybe PlaceholderObject
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BackendMap BackendConfigWrapper -> Maybe Value
backendConfigsToOrdJSON BackendMap BackendConfigWrapper
backendConfigs
}
where
objectFromOrdJSON :: Value -> Object
objectFromOrdJSON (AO.Object Object
obj) = Object
obj
objectFromOrdJSON Value
_ = String -> Object
forall a. HasCallStack => String -> a
error String
"expected an object"