{-# LANGUAGE TemplateHaskell #-}
module Hasura.RQL.Types.RemoteSchema
( AddRemoteSchemaPermission (..),
AddRemoteSchemaQuery (..),
AliasMapping,
DropRemoteSchemaPermissions (..),
RemoteFieldCustomization (..),
RemoteSchemaCustomization (..),
RemoteSchemaCustomizer (..),
RemoteSchemaDef (..),
RemoteSchemaInfo (..),
RemoteSchemaInputValueDefinition (..),
RemoteSchemaIntrospection (..),
RemoteSchemaName (..),
RemoteSchemaNameQuery (..),
RemoteSchemaPermissionDefinition (..),
RemoteSchemaVariable (..),
RemoteTypeCustomization (..),
SessionArgumentPresetInfo (..),
UrlFromEnv,
ValidatedRemoteSchemaDef (..),
applyAliasMapping,
customizeTypeNameString,
getUrlFromEnv,
hasTypeOrFieldCustomizations,
identityCustomizer,
lookupEnum,
lookupInputObject,
lookupInterface,
lookupObject,
lookupScalar,
lookupType,
lookupUnion,
modifyFieldByName,
remoteSchemaCustomizeFieldName,
getTypeName,
remoteSchemaCustomizeTypeName,
singletonAliasMapping,
validateRemoteSchemaCustomization,
validateRemoteSchemaDef,
)
where
import Data.Aeson qualified as J
import Data.Aeson.TH qualified as J
import Data.Environment qualified as Env
import Data.HashMap.Strict qualified as Map
import Data.HashSet qualified as Set
import Data.Text qualified as T
import Data.Text.Extended
import Data.Text.NonEmpty
import Data.URL.Template (printURLTemplate)
import Database.PG.Query qualified as Q
import Hasura.Base.Error
import Hasura.GraphQL.Parser.Variable
import Hasura.GraphQL.Schema.Typename
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Hasura.RQL.DDL.Headers (HeaderConf (..))
import Hasura.RQL.Types.Common
import Hasura.RQL.Types.ResultCustomization
import Hasura.RQL.Types.SourceCustomization
import Hasura.Session
import Language.GraphQL.Draft.Printer qualified as G
import Language.GraphQL.Draft.Syntax qualified as G
import Network.URI.Extended qualified as N
import Text.Builder qualified as TB
type UrlFromEnv = Text
newtype RemoteSchemaName = RemoteSchemaName
{RemoteSchemaName -> NonEmptyText
unRemoteSchemaName :: NonEmptyText}
deriving
( Int -> RemoteSchemaName -> ShowS
[RemoteSchemaName] -> ShowS
RemoteSchemaName -> String
(Int -> RemoteSchemaName -> ShowS)
-> (RemoteSchemaName -> String)
-> ([RemoteSchemaName] -> ShowS)
-> Show RemoteSchemaName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaName] -> ShowS
$cshowList :: [RemoteSchemaName] -> ShowS
show :: RemoteSchemaName -> String
$cshow :: RemoteSchemaName -> String
showsPrec :: Int -> RemoteSchemaName -> ShowS
$cshowsPrec :: Int -> RemoteSchemaName -> ShowS
Show,
RemoteSchemaName -> RemoteSchemaName -> Bool
(RemoteSchemaName -> RemoteSchemaName -> Bool)
-> (RemoteSchemaName -> RemoteSchemaName -> Bool)
-> Eq RemoteSchemaName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaName -> RemoteSchemaName -> Bool
$c/= :: RemoteSchemaName -> RemoteSchemaName -> Bool
== :: RemoteSchemaName -> RemoteSchemaName -> Bool
$c== :: RemoteSchemaName -> RemoteSchemaName -> Bool
Eq,
Eq RemoteSchemaName
Eq RemoteSchemaName
-> (RemoteSchemaName -> RemoteSchemaName -> Ordering)
-> (RemoteSchemaName -> RemoteSchemaName -> Bool)
-> (RemoteSchemaName -> RemoteSchemaName -> Bool)
-> (RemoteSchemaName -> RemoteSchemaName -> Bool)
-> (RemoteSchemaName -> RemoteSchemaName -> Bool)
-> (RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName)
-> (RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName)
-> Ord RemoteSchemaName
RemoteSchemaName -> RemoteSchemaName -> Bool
RemoteSchemaName -> RemoteSchemaName -> Ordering
RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName
$cmin :: RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName
max :: RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName
$cmax :: RemoteSchemaName -> RemoteSchemaName -> RemoteSchemaName
>= :: RemoteSchemaName -> RemoteSchemaName -> Bool
$c>= :: RemoteSchemaName -> RemoteSchemaName -> Bool
> :: RemoteSchemaName -> RemoteSchemaName -> Bool
$c> :: RemoteSchemaName -> RemoteSchemaName -> Bool
<= :: RemoteSchemaName -> RemoteSchemaName -> Bool
$c<= :: RemoteSchemaName -> RemoteSchemaName -> Bool
< :: RemoteSchemaName -> RemoteSchemaName -> Bool
$c< :: RemoteSchemaName -> RemoteSchemaName -> Bool
compare :: RemoteSchemaName -> RemoteSchemaName -> Ordering
$ccompare :: RemoteSchemaName -> RemoteSchemaName -> Ordering
$cp1Ord :: Eq RemoteSchemaName
Ord,
Int -> RemoteSchemaName -> Int
RemoteSchemaName -> Int
(Int -> RemoteSchemaName -> Int)
-> (RemoteSchemaName -> Int) -> Hashable RemoteSchemaName
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RemoteSchemaName -> Int
$chash :: RemoteSchemaName -> Int
hashWithSalt :: Int -> RemoteSchemaName -> Int
$chashWithSalt :: Int -> RemoteSchemaName -> Int
Hashable,
[RemoteSchemaName] -> Value
[RemoteSchemaName] -> Encoding
RemoteSchemaName -> Value
RemoteSchemaName -> Encoding
(RemoteSchemaName -> Value)
-> (RemoteSchemaName -> Encoding)
-> ([RemoteSchemaName] -> Value)
-> ([RemoteSchemaName] -> Encoding)
-> ToJSON RemoteSchemaName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [RemoteSchemaName] -> Encoding
$ctoEncodingList :: [RemoteSchemaName] -> Encoding
toJSONList :: [RemoteSchemaName] -> Value
$ctoJSONList :: [RemoteSchemaName] -> Value
toEncoding :: RemoteSchemaName -> Encoding
$ctoEncoding :: RemoteSchemaName -> Encoding
toJSON :: RemoteSchemaName -> Value
$ctoJSON :: RemoteSchemaName -> Value
J.ToJSON,
ToJSONKeyFunction [RemoteSchemaName]
ToJSONKeyFunction RemoteSchemaName
ToJSONKeyFunction RemoteSchemaName
-> ToJSONKeyFunction [RemoteSchemaName]
-> ToJSONKey RemoteSchemaName
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [RemoteSchemaName]
$ctoJSONKeyList :: ToJSONKeyFunction [RemoteSchemaName]
toJSONKey :: ToJSONKeyFunction RemoteSchemaName
$ctoJSONKey :: ToJSONKeyFunction RemoteSchemaName
J.ToJSONKey,
Value -> Parser [RemoteSchemaName]
Value -> Parser RemoteSchemaName
(Value -> Parser RemoteSchemaName)
-> (Value -> Parser [RemoteSchemaName])
-> FromJSON RemoteSchemaName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [RemoteSchemaName]
$cparseJSONList :: Value -> Parser [RemoteSchemaName]
parseJSON :: Value -> Parser RemoteSchemaName
$cparseJSON :: Value -> Parser RemoteSchemaName
J.FromJSON,
RemoteSchemaName -> PrepArg
(RemoteSchemaName -> PrepArg) -> ToPrepArg RemoteSchemaName
forall a. (a -> PrepArg) -> ToPrepArg a
toPrepVal :: RemoteSchemaName -> PrepArg
$ctoPrepVal :: RemoteSchemaName -> PrepArg
Q.ToPrepArg,
Maybe ByteString -> Either Text RemoteSchemaName
(Maybe ByteString -> Either Text RemoteSchemaName)
-> FromCol RemoteSchemaName
forall a. (Maybe ByteString -> Either Text a) -> FromCol a
fromCol :: Maybe ByteString -> Either Text RemoteSchemaName
$cfromCol :: Maybe ByteString -> Either Text RemoteSchemaName
Q.FromCol,
RemoteSchemaName -> Text
(RemoteSchemaName -> Text) -> ToTxt RemoteSchemaName
forall a. (a -> Text) -> ToTxt a
toTxt :: RemoteSchemaName -> Text
$ctoTxt :: RemoteSchemaName -> Text
ToTxt,
RemoteSchemaName -> ()
(RemoteSchemaName -> ()) -> NFData RemoteSchemaName
forall a. (a -> ()) -> NFData a
rnf :: RemoteSchemaName -> ()
$crnf :: RemoteSchemaName -> ()
NFData,
(forall x. RemoteSchemaName -> Rep RemoteSchemaName x)
-> (forall x. Rep RemoteSchemaName x -> RemoteSchemaName)
-> Generic RemoteSchemaName
forall x. Rep RemoteSchemaName x -> RemoteSchemaName
forall x. RemoteSchemaName -> Rep RemoteSchemaName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteSchemaName x -> RemoteSchemaName
$cfrom :: forall x. RemoteSchemaName -> Rep RemoteSchemaName x
Generic,
Eq RemoteSchemaName
Eq RemoteSchemaName
-> (Accesses -> RemoteSchemaName -> RemoteSchemaName -> Bool)
-> Cacheable RemoteSchemaName
Accesses -> RemoteSchemaName -> RemoteSchemaName -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses -> RemoteSchemaName -> RemoteSchemaName -> Bool
$cunchanged :: Accesses -> RemoteSchemaName -> RemoteSchemaName -> Bool
$cp1Cacheable :: Eq RemoteSchemaName
Cacheable
)
data RemoteTypeCustomization = RemoteTypeCustomization
{ RemoteTypeCustomization -> Maybe Name
_rtcPrefix :: Maybe G.Name,
RemoteTypeCustomization -> Maybe Name
_rtcSuffix :: Maybe G.Name,
RemoteTypeCustomization -> HashMap Name Name
_rtcMapping :: HashMap G.Name G.Name
}
deriving (Int -> RemoteTypeCustomization -> ShowS
[RemoteTypeCustomization] -> ShowS
RemoteTypeCustomization -> String
(Int -> RemoteTypeCustomization -> ShowS)
-> (RemoteTypeCustomization -> String)
-> ([RemoteTypeCustomization] -> ShowS)
-> Show RemoteTypeCustomization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteTypeCustomization] -> ShowS
$cshowList :: [RemoteTypeCustomization] -> ShowS
show :: RemoteTypeCustomization -> String
$cshow :: RemoteTypeCustomization -> String
showsPrec :: Int -> RemoteTypeCustomization -> ShowS
$cshowsPrec :: Int -> RemoteTypeCustomization -> ShowS
Show, RemoteTypeCustomization -> RemoteTypeCustomization -> Bool
(RemoteTypeCustomization -> RemoteTypeCustomization -> Bool)
-> (RemoteTypeCustomization -> RemoteTypeCustomization -> Bool)
-> Eq RemoteTypeCustomization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteTypeCustomization -> RemoteTypeCustomization -> Bool
$c/= :: RemoteTypeCustomization -> RemoteTypeCustomization -> Bool
== :: RemoteTypeCustomization -> RemoteTypeCustomization -> Bool
$c== :: RemoteTypeCustomization -> RemoteTypeCustomization -> Bool
Eq, (forall x.
RemoteTypeCustomization -> Rep RemoteTypeCustomization x)
-> (forall x.
Rep RemoteTypeCustomization x -> RemoteTypeCustomization)
-> Generic RemoteTypeCustomization
forall x. Rep RemoteTypeCustomization x -> RemoteTypeCustomization
forall x. RemoteTypeCustomization -> Rep RemoteTypeCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteTypeCustomization x -> RemoteTypeCustomization
$cfrom :: forall x. RemoteTypeCustomization -> Rep RemoteTypeCustomization x
Generic)
instance NFData RemoteTypeCustomization
instance Cacheable RemoteTypeCustomization
instance Hashable RemoteTypeCustomization
$(J.deriveToJSON hasuraJSON {J.omitNothingFields = True} ''RemoteTypeCustomization)
instance J.FromJSON RemoteTypeCustomization where
parseJSON :: Value -> Parser RemoteTypeCustomization
parseJSON = String
-> (Object -> Parser RemoteTypeCustomization)
-> Value
-> Parser RemoteTypeCustomization
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"RemoteTypeCustomization" ((Object -> Parser RemoteTypeCustomization)
-> Value -> Parser RemoteTypeCustomization)
-> (Object -> Parser RemoteTypeCustomization)
-> Value
-> Parser RemoteTypeCustomization
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Maybe Name
-> Maybe Name -> HashMap Name Name -> RemoteTypeCustomization
RemoteTypeCustomization
(Maybe Name
-> Maybe Name -> HashMap Name Name -> RemoteTypeCustomization)
-> Parser (Maybe Name)
-> Parser
(Maybe Name -> HashMap Name Name -> RemoteTypeCustomization)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Name)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"prefix"
Parser (Maybe Name -> HashMap Name Name -> RemoteTypeCustomization)
-> Parser (Maybe Name)
-> Parser (HashMap Name Name -> RemoteTypeCustomization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Name)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"suffix"
Parser (HashMap Name Name -> RemoteTypeCustomization)
-> Parser (HashMap Name Name) -> Parser RemoteTypeCustomization
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe (HashMap Name Name))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"mapping" Parser (Maybe (HashMap Name Name))
-> HashMap Name Name -> Parser (HashMap Name Name)
forall a. Parser (Maybe a) -> a -> Parser a
J..!= HashMap Name Name
forall a. Monoid a => a
mempty
data RemoteFieldCustomization = RemoteFieldCustomization
{ RemoteFieldCustomization -> Name
_rfcParentType :: G.Name,
RemoteFieldCustomization -> Maybe Name
_rfcPrefix :: Maybe G.Name,
RemoteFieldCustomization -> Maybe Name
_rfcSuffix :: Maybe G.Name,
RemoteFieldCustomization -> HashMap Name Name
_rfcMapping :: HashMap G.Name G.Name
}
deriving (Int -> RemoteFieldCustomization -> ShowS
[RemoteFieldCustomization] -> ShowS
RemoteFieldCustomization -> String
(Int -> RemoteFieldCustomization -> ShowS)
-> (RemoteFieldCustomization -> String)
-> ([RemoteFieldCustomization] -> ShowS)
-> Show RemoteFieldCustomization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteFieldCustomization] -> ShowS
$cshowList :: [RemoteFieldCustomization] -> ShowS
show :: RemoteFieldCustomization -> String
$cshow :: RemoteFieldCustomization -> String
showsPrec :: Int -> RemoteFieldCustomization -> ShowS
$cshowsPrec :: Int -> RemoteFieldCustomization -> ShowS
Show, RemoteFieldCustomization -> RemoteFieldCustomization -> Bool
(RemoteFieldCustomization -> RemoteFieldCustomization -> Bool)
-> (RemoteFieldCustomization -> RemoteFieldCustomization -> Bool)
-> Eq RemoteFieldCustomization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteFieldCustomization -> RemoteFieldCustomization -> Bool
$c/= :: RemoteFieldCustomization -> RemoteFieldCustomization -> Bool
== :: RemoteFieldCustomization -> RemoteFieldCustomization -> Bool
$c== :: RemoteFieldCustomization -> RemoteFieldCustomization -> Bool
Eq, (forall x.
RemoteFieldCustomization -> Rep RemoteFieldCustomization x)
-> (forall x.
Rep RemoteFieldCustomization x -> RemoteFieldCustomization)
-> Generic RemoteFieldCustomization
forall x.
Rep RemoteFieldCustomization x -> RemoteFieldCustomization
forall x.
RemoteFieldCustomization -> Rep RemoteFieldCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoteFieldCustomization x -> RemoteFieldCustomization
$cfrom :: forall x.
RemoteFieldCustomization -> Rep RemoteFieldCustomization x
Generic)
instance NFData RemoteFieldCustomization
instance Cacheable RemoteFieldCustomization
instance Hashable RemoteFieldCustomization
$(J.deriveToJSON hasuraJSON {J.omitNothingFields = True} ''RemoteFieldCustomization)
instance J.FromJSON RemoteFieldCustomization where
parseJSON :: Value -> Parser RemoteFieldCustomization
parseJSON = String
-> (Object -> Parser RemoteFieldCustomization)
-> Value
-> Parser RemoteFieldCustomization
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"RemoteFieldCustomization" ((Object -> Parser RemoteFieldCustomization)
-> Value -> Parser RemoteFieldCustomization)
-> (Object -> Parser RemoteFieldCustomization)
-> Value
-> Parser RemoteFieldCustomization
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Name
-> Maybe Name
-> Maybe Name
-> HashMap Name Name
-> RemoteFieldCustomization
RemoteFieldCustomization
(Name
-> Maybe Name
-> Maybe Name
-> HashMap Name Name
-> RemoteFieldCustomization)
-> Parser Name
-> Parser
(Maybe Name
-> Maybe Name -> HashMap Name Name -> RemoteFieldCustomization)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Name
forall a. FromJSON a => Object -> Key -> Parser a
J..: Key
"parent_type"
Parser
(Maybe Name
-> Maybe Name -> HashMap Name Name -> RemoteFieldCustomization)
-> Parser (Maybe Name)
-> Parser
(Maybe Name -> HashMap Name Name -> RemoteFieldCustomization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Name)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"prefix"
Parser
(Maybe Name -> HashMap Name Name -> RemoteFieldCustomization)
-> Parser (Maybe Name)
-> Parser (HashMap Name Name -> RemoteFieldCustomization)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Name)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"suffix"
Parser (HashMap Name Name -> RemoteFieldCustomization)
-> Parser (HashMap Name Name) -> Parser RemoteFieldCustomization
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe (HashMap Name Name))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"mapping" Parser (Maybe (HashMap Name Name))
-> HashMap Name Name -> Parser (HashMap Name Name)
forall a. Parser (Maybe a) -> a -> Parser a
J..!= HashMap Name Name
forall a. Monoid a => a
mempty
data RemoteSchemaCustomization = RemoteSchemaCustomization
{ RemoteSchemaCustomization -> Maybe Name
_rscRootFieldsNamespace :: Maybe G.Name,
RemoteSchemaCustomization -> Maybe RemoteTypeCustomization
_rscTypeNames :: Maybe RemoteTypeCustomization,
RemoteSchemaCustomization -> Maybe [RemoteFieldCustomization]
_rscFieldNames :: Maybe [RemoteFieldCustomization]
}
deriving (Int -> RemoteSchemaCustomization -> ShowS
[RemoteSchemaCustomization] -> ShowS
RemoteSchemaCustomization -> String
(Int -> RemoteSchemaCustomization -> ShowS)
-> (RemoteSchemaCustomization -> String)
-> ([RemoteSchemaCustomization] -> ShowS)
-> Show RemoteSchemaCustomization
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaCustomization] -> ShowS
$cshowList :: [RemoteSchemaCustomization] -> ShowS
show :: RemoteSchemaCustomization -> String
$cshow :: RemoteSchemaCustomization -> String
showsPrec :: Int -> RemoteSchemaCustomization -> ShowS
$cshowsPrec :: Int -> RemoteSchemaCustomization -> ShowS
Show, RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool
(RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool)
-> (RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool)
-> Eq RemoteSchemaCustomization
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool
$c/= :: RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool
== :: RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool
$c== :: RemoteSchemaCustomization -> RemoteSchemaCustomization -> Bool
Eq, (forall x.
RemoteSchemaCustomization -> Rep RemoteSchemaCustomization x)
-> (forall x.
Rep RemoteSchemaCustomization x -> RemoteSchemaCustomization)
-> Generic RemoteSchemaCustomization
forall x.
Rep RemoteSchemaCustomization x -> RemoteSchemaCustomization
forall x.
RemoteSchemaCustomization -> Rep RemoteSchemaCustomization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoteSchemaCustomization x -> RemoteSchemaCustomization
$cfrom :: forall x.
RemoteSchemaCustomization -> Rep RemoteSchemaCustomization x
Generic)
instance NFData RemoteSchemaCustomization
instance Cacheable RemoteSchemaCustomization
instance Hashable RemoteSchemaCustomization
$(J.deriveJSON hasuraJSON {J.omitNothingFields = True} ''RemoteSchemaCustomization)
data ValidatedRemoteSchemaDef = ValidatedRemoteSchemaDef
{ ValidatedRemoteSchemaDef -> EnvRecord URI
_vrsdUrl :: EnvRecord N.URI,
:: [HeaderConf],
:: Bool,
ValidatedRemoteSchemaDef -> Int
_vrsdTimeoutSeconds :: Int,
ValidatedRemoteSchemaDef -> Maybe RemoteSchemaCustomization
_vrsdCustomization :: Maybe RemoteSchemaCustomization
}
deriving (Int -> ValidatedRemoteSchemaDef -> ShowS
[ValidatedRemoteSchemaDef] -> ShowS
ValidatedRemoteSchemaDef -> String
(Int -> ValidatedRemoteSchemaDef -> ShowS)
-> (ValidatedRemoteSchemaDef -> String)
-> ([ValidatedRemoteSchemaDef] -> ShowS)
-> Show ValidatedRemoteSchemaDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidatedRemoteSchemaDef] -> ShowS
$cshowList :: [ValidatedRemoteSchemaDef] -> ShowS
show :: ValidatedRemoteSchemaDef -> String
$cshow :: ValidatedRemoteSchemaDef -> String
showsPrec :: Int -> ValidatedRemoteSchemaDef -> ShowS
$cshowsPrec :: Int -> ValidatedRemoteSchemaDef -> ShowS
Show, ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool
(ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool)
-> (ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool)
-> Eq ValidatedRemoteSchemaDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool
$c/= :: ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool
== :: ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool
$c== :: ValidatedRemoteSchemaDef -> ValidatedRemoteSchemaDef -> Bool
Eq, (forall x.
ValidatedRemoteSchemaDef -> Rep ValidatedRemoteSchemaDef x)
-> (forall x.
Rep ValidatedRemoteSchemaDef x -> ValidatedRemoteSchemaDef)
-> Generic ValidatedRemoteSchemaDef
forall x.
Rep ValidatedRemoteSchemaDef x -> ValidatedRemoteSchemaDef
forall x.
ValidatedRemoteSchemaDef -> Rep ValidatedRemoteSchemaDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ValidatedRemoteSchemaDef x -> ValidatedRemoteSchemaDef
$cfrom :: forall x.
ValidatedRemoteSchemaDef -> Rep ValidatedRemoteSchemaDef x
Generic)
instance NFData ValidatedRemoteSchemaDef
instance Cacheable ValidatedRemoteSchemaDef
instance Hashable ValidatedRemoteSchemaDef
$(J.deriveJSON hasuraJSON ''ValidatedRemoteSchemaDef)
data RemoteSchemaCustomizer = RemoteSchemaCustomizer
{ RemoteSchemaCustomizer -> Maybe Name
_rscNamespaceFieldName :: Maybe G.Name,
RemoteSchemaCustomizer -> HashMap Name Name
_rscCustomizeTypeName :: HashMap G.Name G.Name,
RemoteSchemaCustomizer -> HashMap Name (HashMap Name Name)
_rscCustomizeFieldName :: HashMap G.Name (HashMap G.Name G.Name)
}
deriving (Int -> RemoteSchemaCustomizer -> ShowS
[RemoteSchemaCustomizer] -> ShowS
RemoteSchemaCustomizer -> String
(Int -> RemoteSchemaCustomizer -> ShowS)
-> (RemoteSchemaCustomizer -> String)
-> ([RemoteSchemaCustomizer] -> ShowS)
-> Show RemoteSchemaCustomizer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaCustomizer] -> ShowS
$cshowList :: [RemoteSchemaCustomizer] -> ShowS
show :: RemoteSchemaCustomizer -> String
$cshow :: RemoteSchemaCustomizer -> String
showsPrec :: Int -> RemoteSchemaCustomizer -> ShowS
$cshowsPrec :: Int -> RemoteSchemaCustomizer -> ShowS
Show, RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool
(RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool)
-> (RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool)
-> Eq RemoteSchemaCustomizer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool
$c/= :: RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool
== :: RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool
$c== :: RemoteSchemaCustomizer -> RemoteSchemaCustomizer -> Bool
Eq, (forall x. RemoteSchemaCustomizer -> Rep RemoteSchemaCustomizer x)
-> (forall x.
Rep RemoteSchemaCustomizer x -> RemoteSchemaCustomizer)
-> Generic RemoteSchemaCustomizer
forall x. Rep RemoteSchemaCustomizer x -> RemoteSchemaCustomizer
forall x. RemoteSchemaCustomizer -> Rep RemoteSchemaCustomizer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteSchemaCustomizer x -> RemoteSchemaCustomizer
$cfrom :: forall x. RemoteSchemaCustomizer -> Rep RemoteSchemaCustomizer x
Generic)
identityCustomizer :: RemoteSchemaCustomizer
identityCustomizer :: RemoteSchemaCustomizer
identityCustomizer = Maybe Name
-> HashMap Name Name
-> HashMap Name (HashMap Name Name)
-> RemoteSchemaCustomizer
RemoteSchemaCustomizer Maybe Name
forall a. Maybe a
Nothing HashMap Name Name
forall a. Monoid a => a
mempty HashMap Name (HashMap Name Name)
forall a. Monoid a => a
mempty
instance NFData RemoteSchemaCustomizer
instance Cacheable RemoteSchemaCustomizer
instance Hashable RemoteSchemaCustomizer
$(J.deriveJSON hasuraJSON ''RemoteSchemaCustomizer)
remoteSchemaCustomizeTypeName :: RemoteSchemaCustomizer -> MkTypename
remoteSchemaCustomizeTypeName :: RemoteSchemaCustomizer -> MkTypename
remoteSchemaCustomizeTypeName RemoteSchemaCustomizer {Maybe Name
HashMap Name (HashMap Name Name)
HashMap Name Name
_rscCustomizeFieldName :: HashMap Name (HashMap Name Name)
_rscCustomizeTypeName :: HashMap Name Name
_rscNamespaceFieldName :: Maybe Name
_rscCustomizeFieldName :: RemoteSchemaCustomizer -> HashMap Name (HashMap Name Name)
_rscCustomizeTypeName :: RemoteSchemaCustomizer -> HashMap Name Name
_rscNamespaceFieldName :: RemoteSchemaCustomizer -> Maybe Name
..} = (Name -> Name) -> MkTypename
MkTypename ((Name -> Name) -> MkTypename) -> (Name -> Name) -> MkTypename
forall a b. (a -> b) -> a -> b
$ \Name
typeName ->
Name -> Name -> HashMap Name Name -> Name
forall k v. (Eq k, Hashable k) => v -> k -> HashMap k v -> v
Map.lookupDefault Name
typeName Name
typeName HashMap Name Name
_rscCustomizeTypeName
remoteSchemaCustomizeFieldName :: RemoteSchemaCustomizer -> CustomizeRemoteFieldName
remoteSchemaCustomizeFieldName :: RemoteSchemaCustomizer -> CustomizeRemoteFieldName
remoteSchemaCustomizeFieldName RemoteSchemaCustomizer {Maybe Name
HashMap Name (HashMap Name Name)
HashMap Name Name
_rscCustomizeFieldName :: HashMap Name (HashMap Name Name)
_rscCustomizeTypeName :: HashMap Name Name
_rscNamespaceFieldName :: Maybe Name
_rscCustomizeFieldName :: RemoteSchemaCustomizer -> HashMap Name (HashMap Name Name)
_rscCustomizeTypeName :: RemoteSchemaCustomizer -> HashMap Name Name
_rscNamespaceFieldName :: RemoteSchemaCustomizer -> Maybe Name
..} = (Name -> Name -> Name) -> CustomizeRemoteFieldName
CustomizeRemoteFieldName ((Name -> Name -> Name) -> CustomizeRemoteFieldName)
-> (Name -> Name -> Name) -> CustomizeRemoteFieldName
forall a b. (a -> b) -> a -> b
$ \Name
typeName Name
fieldName ->
Name
-> HashMap Name (HashMap Name Name) -> Maybe (HashMap Name Name)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup Name
typeName HashMap Name (HashMap Name Name)
_rscCustomizeFieldName Maybe (HashMap Name Name)
-> (HashMap Name Name -> Maybe Name) -> Maybe Name
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Name -> HashMap Name Name -> Maybe Name
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup Name
fieldName Maybe Name -> (Maybe Name -> Name) -> Name
forall a b. a -> (a -> b) -> b
& Name -> Maybe Name -> Name
forall a. a -> Maybe a -> a
fromMaybe Name
fieldName
hasTypeOrFieldCustomizations :: RemoteSchemaCustomizer -> Bool
hasTypeOrFieldCustomizations :: RemoteSchemaCustomizer -> Bool
hasTypeOrFieldCustomizations RemoteSchemaCustomizer {Maybe Name
HashMap Name (HashMap Name Name)
HashMap Name Name
_rscCustomizeFieldName :: HashMap Name (HashMap Name Name)
_rscCustomizeTypeName :: HashMap Name Name
_rscNamespaceFieldName :: Maybe Name
_rscCustomizeFieldName :: RemoteSchemaCustomizer -> HashMap Name (HashMap Name Name)
_rscCustomizeTypeName :: RemoteSchemaCustomizer -> HashMap Name Name
_rscNamespaceFieldName :: RemoteSchemaCustomizer -> Maybe Name
..} =
Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ HashMap Name Name -> Bool
forall k v. HashMap k v -> Bool
Map.null HashMap Name Name
_rscCustomizeTypeName Bool -> Bool -> Bool
&& HashMap Name (HashMap Name Name) -> Bool
forall k v. HashMap k v -> Bool
Map.null HashMap Name (HashMap Name Name)
_rscCustomizeFieldName
data RemoteSchemaInfo = RemoteSchemaInfo
{ RemoteSchemaInfo -> ValidatedRemoteSchemaDef
rsDef :: ValidatedRemoteSchemaDef,
RemoteSchemaInfo -> RemoteSchemaCustomizer
rsCustomizer :: RemoteSchemaCustomizer
}
deriving (Int -> RemoteSchemaInfo -> ShowS
[RemoteSchemaInfo] -> ShowS
RemoteSchemaInfo -> String
(Int -> RemoteSchemaInfo -> ShowS)
-> (RemoteSchemaInfo -> String)
-> ([RemoteSchemaInfo] -> ShowS)
-> Show RemoteSchemaInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaInfo] -> ShowS
$cshowList :: [RemoteSchemaInfo] -> ShowS
show :: RemoteSchemaInfo -> String
$cshow :: RemoteSchemaInfo -> String
showsPrec :: Int -> RemoteSchemaInfo -> ShowS
$cshowsPrec :: Int -> RemoteSchemaInfo -> ShowS
Show, RemoteSchemaInfo -> RemoteSchemaInfo -> Bool
(RemoteSchemaInfo -> RemoteSchemaInfo -> Bool)
-> (RemoteSchemaInfo -> RemoteSchemaInfo -> Bool)
-> Eq RemoteSchemaInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaInfo -> RemoteSchemaInfo -> Bool
$c/= :: RemoteSchemaInfo -> RemoteSchemaInfo -> Bool
== :: RemoteSchemaInfo -> RemoteSchemaInfo -> Bool
$c== :: RemoteSchemaInfo -> RemoteSchemaInfo -> Bool
Eq, (forall x. RemoteSchemaInfo -> Rep RemoteSchemaInfo x)
-> (forall x. Rep RemoteSchemaInfo x -> RemoteSchemaInfo)
-> Generic RemoteSchemaInfo
forall x. Rep RemoteSchemaInfo x -> RemoteSchemaInfo
forall x. RemoteSchemaInfo -> Rep RemoteSchemaInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteSchemaInfo x -> RemoteSchemaInfo
$cfrom :: forall x. RemoteSchemaInfo -> Rep RemoteSchemaInfo x
Generic)
instance NFData RemoteSchemaInfo
instance Cacheable RemoteSchemaInfo
instance Hashable RemoteSchemaInfo
$(J.deriveJSON hasuraJSON ''RemoteSchemaInfo)
data RemoteSchemaDef = RemoteSchemaDef
{ RemoteSchemaDef -> Maybe InputWebhook
_rsdUrl :: Maybe InputWebhook,
RemoteSchemaDef -> Maybe Text
_rsdUrlFromEnv :: Maybe UrlFromEnv,
:: Maybe [HeaderConf],
:: Bool,
RemoteSchemaDef -> Maybe Int
_rsdTimeoutSeconds :: Maybe Int,
RemoteSchemaDef -> Maybe RemoteSchemaCustomization
_rsdCustomization :: Maybe RemoteSchemaCustomization
}
deriving (Int -> RemoteSchemaDef -> ShowS
[RemoteSchemaDef] -> ShowS
RemoteSchemaDef -> String
(Int -> RemoteSchemaDef -> ShowS)
-> (RemoteSchemaDef -> String)
-> ([RemoteSchemaDef] -> ShowS)
-> Show RemoteSchemaDef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaDef] -> ShowS
$cshowList :: [RemoteSchemaDef] -> ShowS
show :: RemoteSchemaDef -> String
$cshow :: RemoteSchemaDef -> String
showsPrec :: Int -> RemoteSchemaDef -> ShowS
$cshowsPrec :: Int -> RemoteSchemaDef -> ShowS
Show, RemoteSchemaDef -> RemoteSchemaDef -> Bool
(RemoteSchemaDef -> RemoteSchemaDef -> Bool)
-> (RemoteSchemaDef -> RemoteSchemaDef -> Bool)
-> Eq RemoteSchemaDef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaDef -> RemoteSchemaDef -> Bool
$c/= :: RemoteSchemaDef -> RemoteSchemaDef -> Bool
== :: RemoteSchemaDef -> RemoteSchemaDef -> Bool
$c== :: RemoteSchemaDef -> RemoteSchemaDef -> Bool
Eq, (forall x. RemoteSchemaDef -> Rep RemoteSchemaDef x)
-> (forall x. Rep RemoteSchemaDef x -> RemoteSchemaDef)
-> Generic RemoteSchemaDef
forall x. Rep RemoteSchemaDef x -> RemoteSchemaDef
forall x. RemoteSchemaDef -> Rep RemoteSchemaDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteSchemaDef x -> RemoteSchemaDef
$cfrom :: forall x. RemoteSchemaDef -> Rep RemoteSchemaDef x
Generic)
instance NFData RemoteSchemaDef
instance Cacheable RemoteSchemaDef
$(J.deriveToJSON hasuraJSON {J.omitNothingFields = True} ''RemoteSchemaDef)
instance J.FromJSON RemoteSchemaDef where
parseJSON :: Value -> Parser RemoteSchemaDef
parseJSON = String
-> (Object -> Parser RemoteSchemaDef)
-> Value
-> Parser RemoteSchemaDef
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"Object" ((Object -> Parser RemoteSchemaDef)
-> Value -> Parser RemoteSchemaDef)
-> (Object -> Parser RemoteSchemaDef)
-> Value
-> Parser RemoteSchemaDef
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Maybe InputWebhook
-> Maybe Text
-> Maybe [HeaderConf]
-> Bool
-> Maybe Int
-> Maybe RemoteSchemaCustomization
-> RemoteSchemaDef
RemoteSchemaDef
(Maybe InputWebhook
-> Maybe Text
-> Maybe [HeaderConf]
-> Bool
-> Maybe Int
-> Maybe RemoteSchemaCustomization
-> RemoteSchemaDef)
-> Parser (Maybe InputWebhook)
-> Parser
(Maybe Text
-> Maybe [HeaderConf]
-> Bool
-> Maybe Int
-> Maybe RemoteSchemaCustomization
-> RemoteSchemaDef)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe InputWebhook)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"url"
Parser
(Maybe Text
-> Maybe [HeaderConf]
-> Bool
-> Maybe Int
-> Maybe RemoteSchemaCustomization
-> RemoteSchemaDef)
-> Parser (Maybe Text)
-> Parser
(Maybe [HeaderConf]
-> Bool
-> Maybe Int
-> Maybe RemoteSchemaCustomization
-> RemoteSchemaDef)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"url_from_env"
Parser
(Maybe [HeaderConf]
-> Bool
-> Maybe Int
-> Maybe RemoteSchemaCustomization
-> RemoteSchemaDef)
-> Parser (Maybe [HeaderConf])
-> Parser
(Bool
-> Maybe Int -> Maybe RemoteSchemaCustomization -> RemoteSchemaDef)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe [HeaderConf])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"headers"
Parser
(Bool
-> Maybe Int -> Maybe RemoteSchemaCustomization -> RemoteSchemaDef)
-> Parser Bool
-> Parser
(Maybe Int -> Maybe RemoteSchemaCustomization -> RemoteSchemaDef)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"forward_client_headers" Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
J..!= Bool
False
Parser
(Maybe Int -> Maybe RemoteSchemaCustomization -> RemoteSchemaDef)
-> Parser (Maybe Int)
-> Parser (Maybe RemoteSchemaCustomization -> RemoteSchemaDef)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"timeout_seconds"
Parser (Maybe RemoteSchemaCustomization -> RemoteSchemaDef)
-> Parser (Maybe RemoteSchemaCustomization)
-> Parser RemoteSchemaDef
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe RemoteSchemaCustomization)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
J..:? Key
"customization"
data AddRemoteSchemaQuery = AddRemoteSchemaQuery
{
AddRemoteSchemaQuery -> RemoteSchemaName
_arsqName :: RemoteSchemaName,
AddRemoteSchemaQuery -> RemoteSchemaDef
_arsqDefinition :: RemoteSchemaDef,
:: Maybe Text
}
deriving (Int -> AddRemoteSchemaQuery -> ShowS
[AddRemoteSchemaQuery] -> ShowS
AddRemoteSchemaQuery -> String
(Int -> AddRemoteSchemaQuery -> ShowS)
-> (AddRemoteSchemaQuery -> String)
-> ([AddRemoteSchemaQuery] -> ShowS)
-> Show AddRemoteSchemaQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddRemoteSchemaQuery] -> ShowS
$cshowList :: [AddRemoteSchemaQuery] -> ShowS
show :: AddRemoteSchemaQuery -> String
$cshow :: AddRemoteSchemaQuery -> String
showsPrec :: Int -> AddRemoteSchemaQuery -> ShowS
$cshowsPrec :: Int -> AddRemoteSchemaQuery -> ShowS
Show, AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool
(AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool)
-> (AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool)
-> Eq AddRemoteSchemaQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool
$c/= :: AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool
== :: AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool
$c== :: AddRemoteSchemaQuery -> AddRemoteSchemaQuery -> Bool
Eq, (forall x. AddRemoteSchemaQuery -> Rep AddRemoteSchemaQuery x)
-> (forall x. Rep AddRemoteSchemaQuery x -> AddRemoteSchemaQuery)
-> Generic AddRemoteSchemaQuery
forall x. Rep AddRemoteSchemaQuery x -> AddRemoteSchemaQuery
forall x. AddRemoteSchemaQuery -> Rep AddRemoteSchemaQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddRemoteSchemaQuery x -> AddRemoteSchemaQuery
$cfrom :: forall x. AddRemoteSchemaQuery -> Rep AddRemoteSchemaQuery x
Generic)
instance NFData AddRemoteSchemaQuery
instance Cacheable AddRemoteSchemaQuery
$(J.deriveJSON hasuraJSON ''AddRemoteSchemaQuery)
newtype RemoteSchemaNameQuery = RemoteSchemaNameQuery
{ RemoteSchemaNameQuery -> RemoteSchemaName
_rsnqName :: RemoteSchemaName
}
deriving (Int -> RemoteSchemaNameQuery -> ShowS
[RemoteSchemaNameQuery] -> ShowS
RemoteSchemaNameQuery -> String
(Int -> RemoteSchemaNameQuery -> ShowS)
-> (RemoteSchemaNameQuery -> String)
-> ([RemoteSchemaNameQuery] -> ShowS)
-> Show RemoteSchemaNameQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaNameQuery] -> ShowS
$cshowList :: [RemoteSchemaNameQuery] -> ShowS
show :: RemoteSchemaNameQuery -> String
$cshow :: RemoteSchemaNameQuery -> String
showsPrec :: Int -> RemoteSchemaNameQuery -> ShowS
$cshowsPrec :: Int -> RemoteSchemaNameQuery -> ShowS
Show, RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool
(RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool)
-> (RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool)
-> Eq RemoteSchemaNameQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool
$c/= :: RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool
== :: RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool
$c== :: RemoteSchemaNameQuery -> RemoteSchemaNameQuery -> Bool
Eq)
$(J.deriveJSON hasuraJSON ''RemoteSchemaNameQuery)
getUrlFromEnv :: (MonadIO m, MonadError QErr m) => Env.Environment -> Text -> m (EnvRecord N.URI)
getUrlFromEnv :: Environment -> Text -> m (EnvRecord URI)
getUrlFromEnv Environment
env Text
urlFromEnv = do
let mEnv :: Maybe String
mEnv = Environment -> String -> Maybe String
Env.lookupEnv Environment
env (String -> Maybe String) -> String -> Maybe String
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
urlFromEnv
String
uri <- Maybe String -> m String -> m String
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing Maybe String
mEnv (Code -> Text -> m String
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams (Text -> m String) -> Text -> m String
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. (Semigroup a, IsString a) => a -> a
envNotFoundMsg Text
urlFromEnv)
case (String -> Maybe URI
N.parseURI String
uri) of
Just URI
uri' -> EnvRecord URI -> m (EnvRecord URI)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EnvRecord URI -> m (EnvRecord URI))
-> EnvRecord URI -> m (EnvRecord URI)
forall a b. (a -> b) -> a -> b
$ Text -> URI -> EnvRecord URI
forall a. Text -> a -> EnvRecord a
EnvRecord Text
urlFromEnv URI
uri'
Maybe URI
Nothing -> Code -> Text -> m (EnvRecord URI)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams (Text -> m (EnvRecord URI)) -> Text -> m (EnvRecord URI)
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. (Semigroup a, IsString a) => a -> a
invalidUri Text
urlFromEnv
where
invalidUri :: a -> a
invalidUri a
x = a
"not a valid URI in environment variable: " a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
x
envNotFoundMsg :: a -> a
envNotFoundMsg a
e = a
"environment variable '" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
e a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
"' not set"
validateRemoteSchemaCustomization ::
(MonadError QErr m) =>
Maybe RemoteSchemaCustomization ->
m ()
validateRemoteSchemaCustomization :: Maybe RemoteSchemaCustomization -> m ()
validateRemoteSchemaCustomization Maybe RemoteSchemaCustomization
Nothing = () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
validateRemoteSchemaCustomization (Just RemoteSchemaCustomization {Maybe [RemoteFieldCustomization]
Maybe Name
Maybe RemoteTypeCustomization
_rscFieldNames :: Maybe [RemoteFieldCustomization]
_rscTypeNames :: Maybe RemoteTypeCustomization
_rscRootFieldsNamespace :: Maybe Name
_rscFieldNames :: RemoteSchemaCustomization -> Maybe [RemoteFieldCustomization]
_rscTypeNames :: RemoteSchemaCustomization -> Maybe RemoteTypeCustomization
_rscRootFieldsNamespace :: RemoteSchemaCustomization -> Maybe Name
..}) =
Maybe [RemoteFieldCustomization]
-> ([RemoteFieldCustomization] -> m ()) -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe [RemoteFieldCustomization]
_rscFieldNames (([RemoteFieldCustomization] -> m ()) -> m ())
-> ([RemoteFieldCustomization] -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \[RemoteFieldCustomization]
fieldCustomizations ->
[RemoteFieldCustomization]
-> (RemoteFieldCustomization -> m ()) -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ [RemoteFieldCustomization]
fieldCustomizations ((RemoteFieldCustomization -> m ()) -> m ())
-> (RemoteFieldCustomization -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \RemoteFieldCustomization {Maybe Name
HashMap Name Name
Name
_rfcMapping :: HashMap Name Name
_rfcSuffix :: Maybe Name
_rfcPrefix :: Maybe Name
_rfcParentType :: Name
_rfcMapping :: RemoteFieldCustomization -> HashMap Name Name
_rfcSuffix :: RemoteFieldCustomization -> Maybe Name
_rfcPrefix :: RemoteFieldCustomization -> Maybe Name
_rfcParentType :: RemoteFieldCustomization -> Name
..} ->
[Name] -> (Name -> m ()) -> m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ (HashMap Name Name -> [Name]
forall k v. HashMap k v -> [k]
Map.keys HashMap Name Name
_rfcMapping) ((Name -> m ()) -> m ()) -> (Name -> m ()) -> m ()
forall a b. (a -> b) -> a -> b
$ \Name
fieldName ->
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Name -> Bool
isReservedName Name
fieldName) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"attempt to customize reserved field name " Text -> Name -> Text
forall t. ToTxt t => Text -> t -> Text
<>> Name
fieldName
where
isReservedName :: Name -> Bool
isReservedName = (Text
"__" Text -> Text -> Bool
`T.isPrefixOf`) (Text -> Bool) -> (Name -> Text) -> Name -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Text
G.unName
validateRemoteSchemaDef ::
(MonadError QErr m, MonadIO m) =>
Env.Environment ->
RemoteSchemaDef ->
m ValidatedRemoteSchemaDef
validateRemoteSchemaDef :: Environment -> RemoteSchemaDef -> m ValidatedRemoteSchemaDef
validateRemoteSchemaDef Environment
env (RemoteSchemaDef Maybe InputWebhook
mUrl Maybe Text
mUrlEnv Maybe [HeaderConf]
hdrC Bool
fwdHdrs Maybe Int
mTimeout Maybe RemoteSchemaCustomization
customization) = do
Maybe RemoteSchemaCustomization -> m ()
forall (m :: * -> *).
MonadError QErr m =>
Maybe RemoteSchemaCustomization -> m ()
validateRemoteSchemaCustomization Maybe RemoteSchemaCustomization
customization
case (Maybe InputWebhook
mUrl, Maybe Text
mUrlEnv) of
(Just InputWebhook
url, Maybe Text
Nothing) -> do
Text
resolvedWebhookTxt <- ResolvedWebhook -> Text
unResolvedWebhook (ResolvedWebhook -> Text) -> m ResolvedWebhook -> m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Environment -> InputWebhook -> m ResolvedWebhook
forall (m :: * -> *).
QErrM m =>
Environment -> InputWebhook -> m ResolvedWebhook
resolveWebhook Environment
env InputWebhook
url
case String -> Maybe URI
N.parseURI (String -> Maybe URI) -> String -> Maybe URI
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
resolvedWebhookTxt of
Maybe URI
Nothing -> Code -> Text -> m ValidatedRemoteSchemaDef
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams (Text -> m ValidatedRemoteSchemaDef)
-> Text -> m ValidatedRemoteSchemaDef
forall a b. (a -> b) -> a -> b
$ Text
"not a valid URI generated from the template: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> InputWebhook -> Text
getTemplateFromUrl InputWebhook
url
Just URI
uri -> ValidatedRemoteSchemaDef -> m ValidatedRemoteSchemaDef
forall (m :: * -> *) a. Monad m => a -> m a
return (ValidatedRemoteSchemaDef -> m ValidatedRemoteSchemaDef)
-> ValidatedRemoteSchemaDef -> m ValidatedRemoteSchemaDef
forall a b. (a -> b) -> a -> b
$ EnvRecord URI
-> [HeaderConf]
-> Bool
-> Int
-> Maybe RemoteSchemaCustomization
-> ValidatedRemoteSchemaDef
ValidatedRemoteSchemaDef (Text -> URI -> EnvRecord URI
forall a. Text -> a -> EnvRecord a
EnvRecord (InputWebhook -> Text
getTemplateFromUrl InputWebhook
url) URI
uri) [HeaderConf]
hdrs Bool
fwdHdrs Int
timeout Maybe RemoteSchemaCustomization
customization
(Maybe InputWebhook
Nothing, Just Text
urlEnv) -> do
EnvRecord URI
urlEnv' <- Environment -> Text -> m (EnvRecord URI)
forall (m :: * -> *).
(MonadIO m, MonadError QErr m) =>
Environment -> Text -> m (EnvRecord URI)
getUrlFromEnv Environment
env Text
urlEnv
ValidatedRemoteSchemaDef -> m ValidatedRemoteSchemaDef
forall (m :: * -> *) a. Monad m => a -> m a
return (ValidatedRemoteSchemaDef -> m ValidatedRemoteSchemaDef)
-> ValidatedRemoteSchemaDef -> m ValidatedRemoteSchemaDef
forall a b. (a -> b) -> a -> b
$ EnvRecord URI
-> [HeaderConf]
-> Bool
-> Int
-> Maybe RemoteSchemaCustomization
-> ValidatedRemoteSchemaDef
ValidatedRemoteSchemaDef EnvRecord URI
urlEnv' [HeaderConf]
hdrs Bool
fwdHdrs Int
timeout Maybe RemoteSchemaCustomization
customization
(Maybe InputWebhook
Nothing, Maybe Text
Nothing) ->
Code -> Text -> m ValidatedRemoteSchemaDef
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams Text
"both `url` and `url_from_env` can't be empty"
(Just InputWebhook
_, Just Text
_) ->
Code -> Text -> m ValidatedRemoteSchemaDef
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
InvalidParams Text
"both `url` and `url_from_env` can't be present"
where
hdrs :: [HeaderConf]
hdrs = [HeaderConf] -> Maybe [HeaderConf] -> [HeaderConf]
forall a. a -> Maybe a -> a
fromMaybe [] Maybe [HeaderConf]
hdrC
timeout :: Int
timeout = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
60 Maybe Int
mTimeout
getTemplateFromUrl :: InputWebhook -> Text
getTemplateFromUrl InputWebhook
url = URLTemplate -> Text
printURLTemplate (URLTemplate -> Text) -> URLTemplate -> Text
forall a b. (a -> b) -> a -> b
$ InputWebhook -> URLTemplate
unInputWebhook InputWebhook
url
newtype RemoteSchemaPermissionDefinition = RemoteSchemaPermissionDefinition
{ RemoteSchemaPermissionDefinition -> SchemaDocument
_rspdSchema :: G.SchemaDocument
}
deriving (Int -> RemoteSchemaPermissionDefinition -> ShowS
[RemoteSchemaPermissionDefinition] -> ShowS
RemoteSchemaPermissionDefinition -> String
(Int -> RemoteSchemaPermissionDefinition -> ShowS)
-> (RemoteSchemaPermissionDefinition -> String)
-> ([RemoteSchemaPermissionDefinition] -> ShowS)
-> Show RemoteSchemaPermissionDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaPermissionDefinition] -> ShowS
$cshowList :: [RemoteSchemaPermissionDefinition] -> ShowS
show :: RemoteSchemaPermissionDefinition -> String
$cshow :: RemoteSchemaPermissionDefinition -> String
showsPrec :: Int -> RemoteSchemaPermissionDefinition -> ShowS
$cshowsPrec :: Int -> RemoteSchemaPermissionDefinition -> ShowS
Show, RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool
(RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool)
-> (RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool)
-> Eq RemoteSchemaPermissionDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool
$c/= :: RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool
== :: RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool
$c== :: RemoteSchemaPermissionDefinition
-> RemoteSchemaPermissionDefinition -> Bool
Eq, (forall x.
RemoteSchemaPermissionDefinition
-> Rep RemoteSchemaPermissionDefinition x)
-> (forall x.
Rep RemoteSchemaPermissionDefinition x
-> RemoteSchemaPermissionDefinition)
-> Generic RemoteSchemaPermissionDefinition
forall x.
Rep RemoteSchemaPermissionDefinition x
-> RemoteSchemaPermissionDefinition
forall x.
RemoteSchemaPermissionDefinition
-> Rep RemoteSchemaPermissionDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoteSchemaPermissionDefinition x
-> RemoteSchemaPermissionDefinition
$cfrom :: forall x.
RemoteSchemaPermissionDefinition
-> Rep RemoteSchemaPermissionDefinition x
Generic)
instance NFData RemoteSchemaPermissionDefinition
instance Cacheable RemoteSchemaPermissionDefinition
instance Hashable RemoteSchemaPermissionDefinition
instance J.FromJSON RemoteSchemaPermissionDefinition where
parseJSON :: Value -> Parser RemoteSchemaPermissionDefinition
parseJSON = String
-> (Object -> Parser RemoteSchemaPermissionDefinition)
-> Value
-> Parser RemoteSchemaPermissionDefinition
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"RemoteSchemaPermissionDefinition" ((Object -> Parser RemoteSchemaPermissionDefinition)
-> Value -> Parser RemoteSchemaPermissionDefinition)
-> (Object -> Parser RemoteSchemaPermissionDefinition)
-> Value
-> Parser RemoteSchemaPermissionDefinition
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
(SchemaDocument -> RemoteSchemaPermissionDefinition)
-> Parser SchemaDocument -> Parser RemoteSchemaPermissionDefinition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SchemaDocument -> RemoteSchemaPermissionDefinition
RemoteSchemaPermissionDefinition (Parser SchemaDocument -> Parser RemoteSchemaPermissionDefinition)
-> Parser SchemaDocument -> Parser RemoteSchemaPermissionDefinition
forall a b. (a -> b) -> a -> b
$ Object
obj Object -> Key -> Parser SchemaDocument
forall a. FromJSON a => Object -> Key -> Parser a
J..: Key
"schema"
instance J.ToJSON RemoteSchemaPermissionDefinition where
toJSON :: RemoteSchemaPermissionDefinition -> Value
toJSON (RemoteSchemaPermissionDefinition SchemaDocument
schema) =
[Pair] -> Value
J.object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Key
"schema" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
J..= Text -> Value
J.String (Builder -> Text
TB.run (Builder -> Text)
-> (SchemaDocument -> Builder) -> SchemaDocument -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SchemaDocument -> Builder
forall a. Printer a => SchemaDocument -> a
G.schemaDocument (SchemaDocument -> Text) -> SchemaDocument -> Text
forall a b. (a -> b) -> a -> b
$ SchemaDocument
schema)]
data AddRemoteSchemaPermission = AddRemoteSchemaPermission
{ AddRemoteSchemaPermission -> RemoteSchemaName
_arspRemoteSchema :: RemoteSchemaName,
AddRemoteSchemaPermission -> RoleName
_arspRole :: RoleName,
AddRemoteSchemaPermission -> RemoteSchemaPermissionDefinition
_arspDefinition :: RemoteSchemaPermissionDefinition,
:: Maybe Text
}
deriving (Int -> AddRemoteSchemaPermission -> ShowS
[AddRemoteSchemaPermission] -> ShowS
AddRemoteSchemaPermission -> String
(Int -> AddRemoteSchemaPermission -> ShowS)
-> (AddRemoteSchemaPermission -> String)
-> ([AddRemoteSchemaPermission] -> ShowS)
-> Show AddRemoteSchemaPermission
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddRemoteSchemaPermission] -> ShowS
$cshowList :: [AddRemoteSchemaPermission] -> ShowS
show :: AddRemoteSchemaPermission -> String
$cshow :: AddRemoteSchemaPermission -> String
showsPrec :: Int -> AddRemoteSchemaPermission -> ShowS
$cshowsPrec :: Int -> AddRemoteSchemaPermission -> ShowS
Show, AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool
(AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool)
-> (AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool)
-> Eq AddRemoteSchemaPermission
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool
$c/= :: AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool
== :: AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool
$c== :: AddRemoteSchemaPermission -> AddRemoteSchemaPermission -> Bool
Eq, (forall x.
AddRemoteSchemaPermission -> Rep AddRemoteSchemaPermission x)
-> (forall x.
Rep AddRemoteSchemaPermission x -> AddRemoteSchemaPermission)
-> Generic AddRemoteSchemaPermission
forall x.
Rep AddRemoteSchemaPermission x -> AddRemoteSchemaPermission
forall x.
AddRemoteSchemaPermission -> Rep AddRemoteSchemaPermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddRemoteSchemaPermission x -> AddRemoteSchemaPermission
$cfrom :: forall x.
AddRemoteSchemaPermission -> Rep AddRemoteSchemaPermission x
Generic)
instance NFData AddRemoteSchemaPermission
instance Cacheable AddRemoteSchemaPermission
$(J.deriveJSON hasuraJSON ''AddRemoteSchemaPermission)
data DropRemoteSchemaPermissions = DropRemoteSchemaPermissions
{ DropRemoteSchemaPermissions -> RemoteSchemaName
_drspRemoteSchema :: RemoteSchemaName,
DropRemoteSchemaPermissions -> RoleName
_drspRole :: RoleName
}
deriving (Int -> DropRemoteSchemaPermissions -> ShowS
[DropRemoteSchemaPermissions] -> ShowS
DropRemoteSchemaPermissions -> String
(Int -> DropRemoteSchemaPermissions -> ShowS)
-> (DropRemoteSchemaPermissions -> String)
-> ([DropRemoteSchemaPermissions] -> ShowS)
-> Show DropRemoteSchemaPermissions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DropRemoteSchemaPermissions] -> ShowS
$cshowList :: [DropRemoteSchemaPermissions] -> ShowS
show :: DropRemoteSchemaPermissions -> String
$cshow :: DropRemoteSchemaPermissions -> String
showsPrec :: Int -> DropRemoteSchemaPermissions -> ShowS
$cshowsPrec :: Int -> DropRemoteSchemaPermissions -> ShowS
Show, DropRemoteSchemaPermissions -> DropRemoteSchemaPermissions -> Bool
(DropRemoteSchemaPermissions
-> DropRemoteSchemaPermissions -> Bool)
-> (DropRemoteSchemaPermissions
-> DropRemoteSchemaPermissions -> Bool)
-> Eq DropRemoteSchemaPermissions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DropRemoteSchemaPermissions -> DropRemoteSchemaPermissions -> Bool
$c/= :: DropRemoteSchemaPermissions -> DropRemoteSchemaPermissions -> Bool
== :: DropRemoteSchemaPermissions -> DropRemoteSchemaPermissions -> Bool
$c== :: DropRemoteSchemaPermissions -> DropRemoteSchemaPermissions -> Bool
Eq, (forall x.
DropRemoteSchemaPermissions -> Rep DropRemoteSchemaPermissions x)
-> (forall x.
Rep DropRemoteSchemaPermissions x -> DropRemoteSchemaPermissions)
-> Generic DropRemoteSchemaPermissions
forall x.
Rep DropRemoteSchemaPermissions x -> DropRemoteSchemaPermissions
forall x.
DropRemoteSchemaPermissions -> Rep DropRemoteSchemaPermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DropRemoteSchemaPermissions x -> DropRemoteSchemaPermissions
$cfrom :: forall x.
DropRemoteSchemaPermissions -> Rep DropRemoteSchemaPermissions x
Generic)
instance NFData DropRemoteSchemaPermissions
instance Cacheable DropRemoteSchemaPermissions
$(J.deriveJSON hasuraJSON ''DropRemoteSchemaPermissions)
data SessionArgumentPresetInfo
= SessionArgumentPresetScalar
| SessionArgumentPresetEnum (Set.HashSet G.EnumValue)
deriving (Int -> SessionArgumentPresetInfo -> ShowS
[SessionArgumentPresetInfo] -> ShowS
SessionArgumentPresetInfo -> String
(Int -> SessionArgumentPresetInfo -> ShowS)
-> (SessionArgumentPresetInfo -> String)
-> ([SessionArgumentPresetInfo] -> ShowS)
-> Show SessionArgumentPresetInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SessionArgumentPresetInfo] -> ShowS
$cshowList :: [SessionArgumentPresetInfo] -> ShowS
show :: SessionArgumentPresetInfo -> String
$cshow :: SessionArgumentPresetInfo -> String
showsPrec :: Int -> SessionArgumentPresetInfo -> ShowS
$cshowsPrec :: Int -> SessionArgumentPresetInfo -> ShowS
Show, SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
(SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool)
-> (SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool)
-> Eq SessionArgumentPresetInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
$c/= :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
== :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
$c== :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
Eq, (forall x.
SessionArgumentPresetInfo -> Rep SessionArgumentPresetInfo x)
-> (forall x.
Rep SessionArgumentPresetInfo x -> SessionArgumentPresetInfo)
-> Generic SessionArgumentPresetInfo
forall x.
Rep SessionArgumentPresetInfo x -> SessionArgumentPresetInfo
forall x.
SessionArgumentPresetInfo -> Rep SessionArgumentPresetInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SessionArgumentPresetInfo x -> SessionArgumentPresetInfo
$cfrom :: forall x.
SessionArgumentPresetInfo -> Rep SessionArgumentPresetInfo x
Generic, Eq SessionArgumentPresetInfo
Eq SessionArgumentPresetInfo
-> (SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> Ordering)
-> (SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool)
-> (SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool)
-> (SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool)
-> (SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool)
-> (SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo)
-> (SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo)
-> Ord SessionArgumentPresetInfo
SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Ordering
SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo
$cmin :: SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo
max :: SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo
$cmax :: SessionArgumentPresetInfo
-> SessionArgumentPresetInfo -> SessionArgumentPresetInfo
>= :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
$c>= :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
> :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
$c> :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
<= :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
$c<= :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
< :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
$c< :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Bool
compare :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Ordering
$ccompare :: SessionArgumentPresetInfo -> SessionArgumentPresetInfo -> Ordering
$cp1Ord :: Eq SessionArgumentPresetInfo
Ord)
instance Hashable SessionArgumentPresetInfo
instance Cacheable SessionArgumentPresetInfo
data RemoteSchemaVariable
= SessionPresetVariable SessionVariable G.Name SessionArgumentPresetInfo
| QueryVariable Variable
| RemoteJSONValue G.GType J.Value
deriving (Int -> RemoteSchemaVariable -> ShowS
[RemoteSchemaVariable] -> ShowS
RemoteSchemaVariable -> String
(Int -> RemoteSchemaVariable -> ShowS)
-> (RemoteSchemaVariable -> String)
-> ([RemoteSchemaVariable] -> ShowS)
-> Show RemoteSchemaVariable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaVariable] -> ShowS
$cshowList :: [RemoteSchemaVariable] -> ShowS
show :: RemoteSchemaVariable -> String
$cshow :: RemoteSchemaVariable -> String
showsPrec :: Int -> RemoteSchemaVariable -> ShowS
$cshowsPrec :: Int -> RemoteSchemaVariable -> ShowS
Show, RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
(RemoteSchemaVariable -> RemoteSchemaVariable -> Bool)
-> (RemoteSchemaVariable -> RemoteSchemaVariable -> Bool)
-> Eq RemoteSchemaVariable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
$c/= :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
== :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
$c== :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
Eq, (forall x. RemoteSchemaVariable -> Rep RemoteSchemaVariable x)
-> (forall x. Rep RemoteSchemaVariable x -> RemoteSchemaVariable)
-> Generic RemoteSchemaVariable
forall x. Rep RemoteSchemaVariable x -> RemoteSchemaVariable
forall x. RemoteSchemaVariable -> Rep RemoteSchemaVariable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteSchemaVariable x -> RemoteSchemaVariable
$cfrom :: forall x. RemoteSchemaVariable -> Rep RemoteSchemaVariable x
Generic, Eq RemoteSchemaVariable
Eq RemoteSchemaVariable
-> (RemoteSchemaVariable -> RemoteSchemaVariable -> Ordering)
-> (RemoteSchemaVariable -> RemoteSchemaVariable -> Bool)
-> (RemoteSchemaVariable -> RemoteSchemaVariable -> Bool)
-> (RemoteSchemaVariable -> RemoteSchemaVariable -> Bool)
-> (RemoteSchemaVariable -> RemoteSchemaVariable -> Bool)
-> (RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable)
-> (RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable)
-> Ord RemoteSchemaVariable
RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
RemoteSchemaVariable -> RemoteSchemaVariable -> Ordering
RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable
$cmin :: RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable
max :: RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable
$cmax :: RemoteSchemaVariable
-> RemoteSchemaVariable -> RemoteSchemaVariable
>= :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
$c>= :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
> :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
$c> :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
<= :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
$c<= :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
< :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
$c< :: RemoteSchemaVariable -> RemoteSchemaVariable -> Bool
compare :: RemoteSchemaVariable -> RemoteSchemaVariable -> Ordering
$ccompare :: RemoteSchemaVariable -> RemoteSchemaVariable -> Ordering
$cp1Ord :: Eq RemoteSchemaVariable
Ord)
instance Hashable RemoteSchemaVariable
instance Cacheable RemoteSchemaVariable
data RemoteSchemaInputValueDefinition = RemoteSchemaInputValueDefinition
{ RemoteSchemaInputValueDefinition -> InputValueDefinition
_rsitdDefinition :: G.InputValueDefinition,
RemoteSchemaInputValueDefinition
-> Maybe (Value RemoteSchemaVariable)
_rsitdPresetArgument :: Maybe (G.Value RemoteSchemaVariable)
}
deriving (Int -> RemoteSchemaInputValueDefinition -> ShowS
[RemoteSchemaInputValueDefinition] -> ShowS
RemoteSchemaInputValueDefinition -> String
(Int -> RemoteSchemaInputValueDefinition -> ShowS)
-> (RemoteSchemaInputValueDefinition -> String)
-> ([RemoteSchemaInputValueDefinition] -> ShowS)
-> Show RemoteSchemaInputValueDefinition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaInputValueDefinition] -> ShowS
$cshowList :: [RemoteSchemaInputValueDefinition] -> ShowS
show :: RemoteSchemaInputValueDefinition -> String
$cshow :: RemoteSchemaInputValueDefinition -> String
showsPrec :: Int -> RemoteSchemaInputValueDefinition -> ShowS
$cshowsPrec :: Int -> RemoteSchemaInputValueDefinition -> ShowS
Show, RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
(RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool)
-> Eq RemoteSchemaInputValueDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
$c/= :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
== :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
$c== :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
Eq, (forall x.
RemoteSchemaInputValueDefinition
-> Rep RemoteSchemaInputValueDefinition x)
-> (forall x.
Rep RemoteSchemaInputValueDefinition x
-> RemoteSchemaInputValueDefinition)
-> Generic RemoteSchemaInputValueDefinition
forall x.
Rep RemoteSchemaInputValueDefinition x
-> RemoteSchemaInputValueDefinition
forall x.
RemoteSchemaInputValueDefinition
-> Rep RemoteSchemaInputValueDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoteSchemaInputValueDefinition x
-> RemoteSchemaInputValueDefinition
$cfrom :: forall x.
RemoteSchemaInputValueDefinition
-> Rep RemoteSchemaInputValueDefinition x
Generic, Eq RemoteSchemaInputValueDefinition
Eq RemoteSchemaInputValueDefinition
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Ordering)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition)
-> (RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition)
-> Ord RemoteSchemaInputValueDefinition
RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Ordering
RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
$cmin :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
max :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
$cmax :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition
>= :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
$c>= :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
> :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
$c> :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
<= :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
$c<= :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
< :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
$c< :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Bool
compare :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Ordering
$ccompare :: RemoteSchemaInputValueDefinition
-> RemoteSchemaInputValueDefinition -> Ordering
$cp1Ord :: Eq RemoteSchemaInputValueDefinition
Ord)
instance Hashable RemoteSchemaInputValueDefinition
instance Cacheable RemoteSchemaInputValueDefinition
newtype RemoteSchemaIntrospection
= RemoteSchemaIntrospection (HashMap G.Name (G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition))
deriving (Int -> RemoteSchemaIntrospection -> ShowS
[RemoteSchemaIntrospection] -> ShowS
RemoteSchemaIntrospection -> String
(Int -> RemoteSchemaIntrospection -> ShowS)
-> (RemoteSchemaIntrospection -> String)
-> ([RemoteSchemaIntrospection] -> ShowS)
-> Show RemoteSchemaIntrospection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteSchemaIntrospection] -> ShowS
$cshowList :: [RemoteSchemaIntrospection] -> ShowS
show :: RemoteSchemaIntrospection -> String
$cshow :: RemoteSchemaIntrospection -> String
showsPrec :: Int -> RemoteSchemaIntrospection -> ShowS
$cshowsPrec :: Int -> RemoteSchemaIntrospection -> ShowS
Show, RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
(RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> (RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> Eq RemoteSchemaIntrospection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$c/= :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
== :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$c== :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
Eq, (forall x.
RemoteSchemaIntrospection -> Rep RemoteSchemaIntrospection x)
-> (forall x.
Rep RemoteSchemaIntrospection x -> RemoteSchemaIntrospection)
-> Generic RemoteSchemaIntrospection
forall x.
Rep RemoteSchemaIntrospection x -> RemoteSchemaIntrospection
forall x.
RemoteSchemaIntrospection -> Rep RemoteSchemaIntrospection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoteSchemaIntrospection x -> RemoteSchemaIntrospection
$cfrom :: forall x.
RemoteSchemaIntrospection -> Rep RemoteSchemaIntrospection x
Generic, Int -> RemoteSchemaIntrospection -> Int
RemoteSchemaIntrospection -> Int
(Int -> RemoteSchemaIntrospection -> Int)
-> (RemoteSchemaIntrospection -> Int)
-> Hashable RemoteSchemaIntrospection
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RemoteSchemaIntrospection -> Int
$chash :: RemoteSchemaIntrospection -> Int
hashWithSalt :: Int -> RemoteSchemaIntrospection -> Int
$chashWithSalt :: Int -> RemoteSchemaIntrospection -> Int
Hashable, Eq RemoteSchemaIntrospection
Eq RemoteSchemaIntrospection
-> (Accesses
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> Cacheable RemoteSchemaIntrospection
Accesses
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
forall a. Eq a -> (Accesses -> a -> a -> Bool) -> Cacheable a
unchanged :: Accesses
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$cunchanged :: Accesses
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$cp1Cacheable :: Eq RemoteSchemaIntrospection
Cacheable, Eq RemoteSchemaIntrospection
Eq RemoteSchemaIntrospection
-> (RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> Ordering)
-> (RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> (RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> (RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> (RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool)
-> (RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection)
-> (RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection)
-> Ord RemoteSchemaIntrospection
RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Ordering
RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection
$cmin :: RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection
max :: RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection
$cmax :: RemoteSchemaIntrospection
-> RemoteSchemaIntrospection -> RemoteSchemaIntrospection
>= :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$c>= :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
> :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$c> :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
<= :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$c<= :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
< :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
$c< :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Bool
compare :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Ordering
$ccompare :: RemoteSchemaIntrospection -> RemoteSchemaIntrospection -> Ordering
$cp1Ord :: Eq RemoteSchemaIntrospection
Ord)
getTypeName :: G.TypeDefinition possibleTypes inputType -> G.Name
getTypeName :: TypeDefinition possibleTypes inputType -> Name
getTypeName = \case
G.TypeDefinitionScalar ScalarTypeDefinition
t -> ScalarTypeDefinition -> Name
G._stdName ScalarTypeDefinition
t
G.TypeDefinitionObject ObjectTypeDefinition inputType
t -> ObjectTypeDefinition inputType -> Name
forall inputType. ObjectTypeDefinition inputType -> Name
G._otdName ObjectTypeDefinition inputType
t
G.TypeDefinitionInterface InterfaceTypeDefinition possibleTypes inputType
t -> InterfaceTypeDefinition possibleTypes inputType -> Name
forall possibleTypes inputType.
InterfaceTypeDefinition possibleTypes inputType -> Name
G._itdName InterfaceTypeDefinition possibleTypes inputType
t
G.TypeDefinitionUnion UnionTypeDefinition
t -> UnionTypeDefinition -> Name
G._utdName UnionTypeDefinition
t
G.TypeDefinitionEnum EnumTypeDefinition
t -> EnumTypeDefinition -> Name
G._etdName EnumTypeDefinition
t
G.TypeDefinitionInputObject InputObjectTypeDefinition inputType
t -> InputObjectTypeDefinition inputType -> Name
forall inputType. InputObjectTypeDefinition inputType -> Name
G._iotdName InputObjectTypeDefinition inputType
t
lookupType ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe (G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition)
lookupType :: RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType (RemoteSchemaIntrospection HashMap
Name (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
types) Name
name = Name
-> HashMap
Name (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup Name
name HashMap
Name (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
types
lookupObject ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe (G.ObjectTypeDefinition RemoteSchemaInputValueDefinition)
lookupObject :: RemoteSchemaIntrospection
-> Name
-> Maybe (ObjectTypeDefinition RemoteSchemaInputValueDefinition)
lookupObject RemoteSchemaIntrospection
introspection Name
name =
RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType RemoteSchemaIntrospection
introspection Name
name Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> (TypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe (ObjectTypeDefinition RemoteSchemaInputValueDefinition))
-> Maybe (ObjectTypeDefinition RemoteSchemaInputValueDefinition)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
G.TypeDefinitionObject ObjectTypeDefinition RemoteSchemaInputValueDefinition
t | ObjectTypeDefinition RemoteSchemaInputValueDefinition -> Name
forall inputType. ObjectTypeDefinition inputType -> Name
G._otdName ObjectTypeDefinition RemoteSchemaInputValueDefinition
t Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name -> ObjectTypeDefinition RemoteSchemaInputValueDefinition
-> Maybe (ObjectTypeDefinition RemoteSchemaInputValueDefinition)
forall a. a -> Maybe a
Just ObjectTypeDefinition RemoteSchemaInputValueDefinition
t
TypeDefinition [Name] RemoteSchemaInputValueDefinition
_ -> Maybe (ObjectTypeDefinition RemoteSchemaInputValueDefinition)
forall a. Maybe a
Nothing
lookupInterface ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe (G.InterfaceTypeDefinition [G.Name] RemoteSchemaInputValueDefinition)
lookupInterface :: RemoteSchemaIntrospection
-> Name
-> Maybe
(InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupInterface RemoteSchemaIntrospection
introspection Name
name =
RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType RemoteSchemaIntrospection
introspection Name
name Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> (TypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe
(InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition))
-> Maybe
(InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
G.TypeDefinitionInterface InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition
t | InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Name
forall possibleTypes inputType.
InterfaceTypeDefinition possibleTypes inputType -> Name
G._itdName InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition
t Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name -> InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe
(InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition)
forall a. a -> Maybe a
Just InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition
t
TypeDefinition [Name] RemoteSchemaInputValueDefinition
_ -> Maybe
(InterfaceTypeDefinition [Name] RemoteSchemaInputValueDefinition)
forall a. Maybe a
Nothing
lookupScalar ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe G.ScalarTypeDefinition
lookupScalar :: RemoteSchemaIntrospection -> Name -> Maybe ScalarTypeDefinition
lookupScalar RemoteSchemaIntrospection
introspection Name
name =
RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType RemoteSchemaIntrospection
introspection Name
name Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> (TypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe ScalarTypeDefinition)
-> Maybe ScalarTypeDefinition
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
G.TypeDefinitionScalar ScalarTypeDefinition
t | ScalarTypeDefinition -> Name
G._stdName ScalarTypeDefinition
t Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name -> ScalarTypeDefinition -> Maybe ScalarTypeDefinition
forall a. a -> Maybe a
Just ScalarTypeDefinition
t
TypeDefinition [Name] RemoteSchemaInputValueDefinition
_ -> Maybe ScalarTypeDefinition
forall a. Maybe a
Nothing
lookupUnion ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe G.UnionTypeDefinition
lookupUnion :: RemoteSchemaIntrospection -> Name -> Maybe UnionTypeDefinition
lookupUnion RemoteSchemaIntrospection
introspection Name
name =
RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType RemoteSchemaIntrospection
introspection Name
name Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> (TypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe UnionTypeDefinition)
-> Maybe UnionTypeDefinition
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
G.TypeDefinitionUnion UnionTypeDefinition
t | UnionTypeDefinition -> Name
G._utdName UnionTypeDefinition
t Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name -> UnionTypeDefinition -> Maybe UnionTypeDefinition
forall a. a -> Maybe a
Just UnionTypeDefinition
t
TypeDefinition [Name] RemoteSchemaInputValueDefinition
_ -> Maybe UnionTypeDefinition
forall a. Maybe a
Nothing
lookupEnum ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe G.EnumTypeDefinition
lookupEnum :: RemoteSchemaIntrospection -> Name -> Maybe EnumTypeDefinition
lookupEnum RemoteSchemaIntrospection
introspection Name
name =
RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType RemoteSchemaIntrospection
introspection Name
name Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> (TypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe EnumTypeDefinition)
-> Maybe EnumTypeDefinition
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
G.TypeDefinitionEnum EnumTypeDefinition
t | EnumTypeDefinition -> Name
G._etdName EnumTypeDefinition
t Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name -> EnumTypeDefinition -> Maybe EnumTypeDefinition
forall a. a -> Maybe a
Just EnumTypeDefinition
t
TypeDefinition [Name] RemoteSchemaInputValueDefinition
_ -> Maybe EnumTypeDefinition
forall a. Maybe a
Nothing
lookupInputObject ::
RemoteSchemaIntrospection ->
G.Name ->
Maybe (G.InputObjectTypeDefinition RemoteSchemaInputValueDefinition)
lookupInputObject :: RemoteSchemaIntrospection
-> Name
-> Maybe
(InputObjectTypeDefinition RemoteSchemaInputValueDefinition)
lookupInputObject RemoteSchemaIntrospection
introspection Name
name =
RemoteSchemaIntrospection
-> Name
-> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupType RemoteSchemaIntrospection
introspection Name
name Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
-> (TypeDefinition [Name] RemoteSchemaInputValueDefinition
-> Maybe
(InputObjectTypeDefinition RemoteSchemaInputValueDefinition))
-> Maybe
(InputObjectTypeDefinition RemoteSchemaInputValueDefinition)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
G.TypeDefinitionInputObject InputObjectTypeDefinition RemoteSchemaInputValueDefinition
t | InputObjectTypeDefinition RemoteSchemaInputValueDefinition -> Name
forall inputType. InputObjectTypeDefinition inputType -> Name
G._iotdName InputObjectTypeDefinition RemoteSchemaInputValueDefinition
t Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name -> InputObjectTypeDefinition RemoteSchemaInputValueDefinition
-> Maybe
(InputObjectTypeDefinition RemoteSchemaInputValueDefinition)
forall a. a -> Maybe a
Just InputObjectTypeDefinition RemoteSchemaInputValueDefinition
t
TypeDefinition [Name] RemoteSchemaInputValueDefinition
_ -> Maybe (InputObjectTypeDefinition RemoteSchemaInputValueDefinition)
forall a. Maybe a
Nothing