server: add analyzeGraphqlQuery

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3288
GitOrigin-RevId: a5fd39acc8039f2e6ec5090adfc984ac09281d6b
This commit is contained in:
paritosh-08 2022-01-21 11:09:08 +05:30 committed by hasura-bot
parent 1a0627d6fa
commit 00558666b1
6 changed files with 360 additions and 129 deletions

View File

@ -629,6 +629,7 @@ library
, Hasura.RQL.IR.Update
, Hasura.RQL.IR.Root
, Hasura.RQL.IR
, Hasura.GraphQL.Analyse
, Hasura.GraphQL.Context
, Hasura.GraphQL.Execute
, Hasura.GraphQL.Execute.Action

View File

@ -0,0 +1,222 @@
module Hasura.GraphQL.Analyse
( Analysis (..),
FieldAnalysis (..),
FieldDef (..),
analyzeGraphqlQuery,
)
where
import Data.HashMap.Strict qualified as Map
import Data.HashMap.Strict.InsOrd qualified as OMap
import Hasura.Prelude hiding (get, put)
import Hasura.RQL.Types.RemoteSchema
( RemoteSchemaInputValueDefinition (RemoteSchemaInputValueDefinition, _rsitdDefinition),
RemoteSchemaIntrospection (RemoteSchemaIntrospection),
)
import Language.GraphQL.Draft.Syntax (ExecutableDefinition, GType, Name, TypeDefinition)
import Language.GraphQL.Draft.Syntax qualified as G
-- | Analyse and FieldAnalysis are almost similar, except, Analyse will have a bool field (in future)
-- to indicate whether the GQL query is valid or not
data Analysis var = Analysis
{ -- | ordered hashmap from the fields to it's definition and analysis
_aFields :: InsOrdHashMap FieldName (FieldDef, Maybe (FieldAnalysis var)),
-- | map of all the variables, their type and default value (if there is any)
_aVars :: HashMap VarName (GType, Maybe (G.Value Void)),
_aErrs :: [Text]
}
deriving (Show)
data FieldAnalysis var = FieldAnalysis
{ _fFields :: InsOrdHashMap FieldName (FieldDef, Maybe (FieldAnalysis var)),
_fVars :: HashMap VarName (GType, Maybe (G.Value var)),
_fErrs :: [Text]
}
deriving (Show)
instance Monoid (FieldAnalysis v) where
mempty = FieldAnalysis mempty mempty []
instance Semigroup (FieldAnalysis v) where
(<>) fa1 fa2 = FieldAnalysis unionFields (_fVars fa1 <> _fVars fa2) (_fErrs fa1 <> _fErrs fa2)
where
unionFields = foldl' (safeInsertInFieldMap) (_fFields fa1) (OMap.toList (_fFields fa2))
instance Monoid (Analysis v) where
mempty = Analysis mempty mempty []
instance Semigroup (Analysis v) where
(<>) fa1 fa2 = Analysis unionFields (_aVars fa1 <> _aVars fa2) (_aErrs fa1 <> _aErrs fa2)
where
unionFields = foldl' (safeInsertInFieldMap) (_aFields fa1) (OMap.toList (_aFields fa2))
-- | FieldDef is analogous to `GType` from the `Language.GraphQL.Draft.Syntax` module
data FieldDef = FieldInfo G.Nullability (TypeDefinition [Name] RemoteSchemaInputValueDefinition) | FieldList G.Nullability FieldDef deriving (Show)
type FieldName = Name
type VarName = Name
-- | inserts in field map, if there is already a key, then take a union of the fields inside
-- i.e. for the following graphql query:
-- query MyQuery {
-- test {
-- a
-- b
-- }
-- test {
-- b
-- c
-- }
-- }
-- The final field map of `test` will have a, b and c
safeInsertInFieldMap ::
(Eq k, Hashable k, Semigroup a1) =>
InsOrdHashMap k (a2, Maybe a1) ->
(k, (a2, Maybe a1)) ->
InsOrdHashMap k (a2, Maybe a1)
safeInsertInFieldMap m (k, v) =
OMap.insertWith (\(fdef, (f1)) (_, (f2)) -> (fdef, f1 <> f2)) k v m
analyzeGraphqlQuery :: ExecutableDefinition Name -> RemoteSchemaIntrospection -> Maybe (Analysis Name)
analyzeGraphqlQuery (G.ExecutableDefinitionOperation (G.OperationDefinitionTyped td)) sc = do
let t = (G._todType td,) <$> G._todSelectionSet td
varDefs = G._todVariableDefinitions td
varMap = foldr (\G.VariableDefinition {..} m -> Map.insert _vdName (_vdType, _vdDefaultValue) m) mempty varDefs
(fieldMap, errs) = getFieldsMap sc t
pure Analysis {_aFields = fieldMap, _aVars = varMap, _aErrs = errs}
analyzeGraphqlQuery _ _ = Nothing
getFieldsMap ::
RemoteSchemaIntrospection ->
[(G.OperationType, G.Selection frag var)] ->
(InsOrdHashMap Name (FieldDef, Maybe (FieldAnalysis var)), [Text])
getFieldsMap rs ss =
let fields = mapMaybe (\(o, s) -> (o,) <$> field s) ss
(ps, errs) =
foldl'
( \(m, e) (o, f) -> case lookupRoot rs (o, f) of
Left x0 -> (safeInsertInFieldMap m (G._fName f, x0), e)
Right txts -> (m, e <> txts)
)
(OMap.empty, [])
fields
in (ps, errs)
lookupRoot ::
RemoteSchemaIntrospection ->
(G.OperationType, G.Field frag var) ->
Either (FieldDef, Maybe (FieldAnalysis var)) [Text]
lookupRoot rs (ot, f) = do
let rootFieldName = getRootFieldNameFromOpType ot
fieldName = G._fName f
fieldTypeM = do
operationDefinitionSum <- lookupRS rs rootFieldName
operationDefinitionObject <- asObjectTypeDefinition operationDefinitionSum
fieldDefinition <- find ((== fieldName) . G._fldName) $ G._otdFieldsDefinition operationDefinitionObject
pure $ G._fldType fieldDefinition
case fieldTypeM of
Nothing -> Right $ ["Couldn't find field " <> G.unName fieldName <> " in root field " <> G.unName rootFieldName]
Just fieldType -> lookupDefinition rs fieldType f
lookupDefinition ::
RemoteSchemaIntrospection ->
GType ->
G.Field frag var ->
Either (FieldDef, Maybe (FieldAnalysis var)) [Text]
lookupDefinition rs t f = do
typeToSchemaM t \n ->
case lookupRS rs n of
Nothing -> Right ["Cannot find type definition for " <> G.unName n <> " in field " <> G.unName (G._fName f)]
Just tDef -> Left $ getDefinition rs tDef (G._fSelectionSet f)
field :: G.Selection frag var -> Maybe (G.Field frag var)
field (G.SelectionField f) = Just f
field _ = Nothing
infixl 7 &&&&
(&&&&) :: Applicative f => (t -> f a1) -> (t -> f a2) -> t -> f (a1, a2)
f &&&& g = \a -> (,) <$> f a <*> g a
getRootFieldNameFromOpType :: G.OperationType -> G.Name
getRootFieldNameFromOpType G.OperationTypeQuery = $$(G.litName "query_root")
getRootFieldNameFromOpType G.OperationTypeMutation = $$(G.litName "mutation_root")
getRootFieldNameFromOpType G.OperationTypeSubscription = $$(G.litName "subscription_root")
asObjectTypeDefinition :: G.TypeDefinition possibleTypes inputType -> Maybe (G.ObjectTypeDefinition inputType)
asObjectTypeDefinition (G.TypeDefinitionObject o) = Just o
asObjectTypeDefinition _ = Nothing
lookupRS :: RemoteSchemaIntrospection -> G.Name -> Maybe (TypeDefinition [Name] RemoteSchemaInputValueDefinition)
lookupRS (RemoteSchemaIntrospection rsDefs) n = Map.lookup n rsDefs
typeToSchemaM ::
GType ->
(Name -> Either (TypeDefinition [Name] RemoteSchemaInputValueDefinition, Maybe (FieldAnalysis var)) [Text]) ->
Either (FieldDef, Maybe (FieldAnalysis var)) [Text]
typeToSchemaM (G.TypeNamed n tName) k = case k tName of
Right x -> Right x
Left (t, x) -> Left (FieldInfo n t, x)
typeToSchemaM (G.TypeList n t) k = case typeToSchemaM t k of
Right x -> Right x
Left (t', x) -> Left (FieldList n t', x)
getDefinition ::
RemoteSchemaIntrospection ->
TypeDefinition [Name] RemoteSchemaInputValueDefinition ->
G.SelectionSet frag var ->
(TypeDefinition [Name] RemoteSchemaInputValueDefinition, Maybe (FieldAnalysis var))
getDefinition rs td sels =
(td,) $ case td of
(G.TypeDefinitionObject otd) -> do
ps <- traverse (\sel -> fmap (mkFieldAnalysis rs sel) (lookupFieldBySelection sel (G._otdFieldsDefinition otd))) sels
pure $ fold $ catMaybes ps
_ -> Nothing
itrListWith :: GType -> (Name -> p) -> p
itrListWith (G.TypeNamed _ tName) k = k tName
itrListWith (G.TypeList _ t) k = itrListWith t k
getFieldVars :: G.FieldDefinition RemoteSchemaInputValueDefinition -> HashMap Name (G.Value var) -> [(VarName, (GType, Maybe (G.Value var)))]
getFieldVars fDef' agMap =
map
( \RemoteSchemaInputValueDefinition {..} ->
(G._ivdName _rsitdDefinition, (G._ivdType _rsitdDefinition, Map.lookup (G._ivdName _rsitdDefinition) agMap))
)
(G._fldArgumentsDefinition fDef')
mkFieldAnalysis ::
RemoteSchemaIntrospection ->
G.Selection frag var ->
G.FieldDefinition RemoteSchemaInputValueDefinition ->
Maybe (FieldAnalysis var)
-- TODO: Handle `SelectionFragmentSpread` and `SelectionInlineFragment` as well
mkFieldAnalysis _ (G.SelectionFragmentSpread _) _ = Nothing
mkFieldAnalysis _ (G.SelectionInlineFragment _) _ = Nothing
mkFieldAnalysis rs (G.SelectionField sel) fd = do
let ag = G._fArguments sel
ft = G._fldType fd
fn = G._fldName fd
(fFds, fVrs, fErrs) = itrListWith ft \n ->
case lookupRS rs n of
Nothing -> (mempty, mempty, ["Couldn't find definition for type " <> G.unName n <> " in field " <> G.unName fn <> " selected by " <> G.unName (G._fName sel)])
Just tDef ->
let (def, fAn) = getDefinition rs tDef (G._fSelectionSet sel)
in case ft of
G.TypeNamed n' _ ->
(OMap.singleton fn (FieldInfo n' def, fAn), Map.fromList (getFieldVars fd ag), [])
G.TypeList n' _ ->
(OMap.singleton fn (FieldList n' $ FieldInfo n' def, fAn), Map.fromList (getFieldVars fd ag), [])
pure
FieldAnalysis
{ _fFields = fFds,
_fVars = fVrs,
_fErrs = fErrs
}
lookupFieldBySelection :: G.Selection frag0 var0 -> [G.FieldDefinition RemoteSchemaInputValueDefinition] -> Maybe (G.FieldDefinition RemoteSchemaInputValueDefinition)
lookupFieldBySelection (G.SelectionField f) = find \d -> G._fName f == G._fldName d
lookupFieldBySelection _ = const Nothing

View File

@ -1,3 +1,4 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
-- |
@ -28,6 +29,7 @@ import Data.Set qualified as Set
import Data.Text qualified as T
import Data.Text.Extended (commaSeparated)
import Data.Text.NonEmpty
import Hasura.GraphQL.Analyse (Analysis (Analysis, _aFields, _aVars), FieldAnalysis (FieldAnalysis, _fFields), FieldDef (FieldInfo, FieldList), analyzeGraphqlQuery)
import Hasura.GraphQL.Context
import Hasura.GraphQL.Namespace (mkUnNamespacedRootFieldAlias)
import Hasura.GraphQL.Parser.Schema (Variable)
@ -130,56 +132,24 @@ Example stepthrough initiated by call to getSelectionSchema:
-}
mdSelectionFields :: EndpointMetadata GQLQueryWithText -> [(G.OperationType, G.Selection G.FragmentSpread G.Name)]
mdSelectionFields = definitionSelections <=< mdDefinitions -- Workaround for safety, just take 1.
where
-- FIXME: There should only be one definition associated. Find a way to signal an error here otherwise.
mdDefinitions :: EndpointMetadata GQLQueryWithText -> [G.ExecutableDefinition G.Name]
mdDefinitions = G.getExecutableDefinitions . unGQLQuery . getGQLQuery . _edQuery . _ceDefinition
-- FIXME: There should only be one definition associated. Find a way to signal an error here otherwise.
mdDefinitions :: EndpointMetadata GQLQueryWithText -> [G.ExecutableDefinition G.Name]
mdDefinitions = G.getExecutableDefinitions . unGQLQuery . getGQLQuery . _edQuery . _ceDefinition
-- definitionSelections :: G.ExecutableDefinition x -> G.SelectionSet G.FragmentSpread x
definitionSelections :: G.ExecutableDefinition G.Name -> [(G.OperationType, G.Selection G.FragmentSpread G.Name)]
definitionSelections (G.ExecutableDefinitionOperation (G.OperationDefinitionTyped td)) = (G._todType td,) <$> G._todSelectionSet td
definitionSelections _ = []
mkResponse :: [Text] -> String -> Maybe RemoteSchemaIntrospection -> EndpointMetadata GQLQueryWithText -> Declare (Definitions Schema) (Maybe Response)
mkResponse :: [Text] -> String -> Maybe RemoteSchemaIntrospection -> Analysis G.Name -> Declare (Definitions Schema) (Maybe Response)
mkResponse _ _ Nothing _ = pure Nothing
mkResponse epMethods epUrl (Just rs) md = do
fs <- getSelectionSchema rs (mdSelectionFields md)
mkResponse epMethods epUrl (Just rs) Analysis {..} = do
fs <- getSelectionSchema rs (OMap.toList _aFields)
pure $
Just $
mempty
& content .~ OMap.singleton ("application" // "json") (mempty & schema ?~ Inline fs)
& description .~ "Responses for " <> commaSeparated epMethods <> " " <> T.pack epUrl
getSelectionSchema :: RemoteSchemaIntrospection -> [(G.OperationType, G.Selection a b)] -> Declare (Definitions Schema) Schema
getSelectionSchema rs ss = do
let fields = mapMaybe (\(o, s) -> (o,) <$> field s) ss
ps <- traverse (pure . G.unName . G._fName . snd &&&& lookupRoot rs) fields
pure $ mempty & properties .~ OMap.fromList ps
lookupRoot :: RemoteSchemaIntrospection -> (G.OperationType, G.Field a b) -> Declare (Definitions Schema) (Referenced Schema)
lookupRoot rs (ot, f) = do
let rootFieldName = getRootFieldNameFromOpType ot
fieldName = G._fName f
fieldTypeM = do
operationDefinitionSum <- lookupRS rs rootFieldName
operationDefinitionObject <- asObjectTypeDefinition operationDefinitionSum
fieldDefinition <- find ((== fieldName) . G._fldName) $ G._otdFieldsDefinition operationDefinitionObject
pure $ G._fldType fieldDefinition
case fieldTypeM of
Nothing -> pure $ Inline $ mempty & description ?~ "Couldn't find field " <> G.unName fieldName <> " in root field " <> G.unName rootFieldName
Just fieldType -> lookupDefinition rs fieldType f
lookupDefinition :: RemoteSchemaIntrospection -> G.GType -> G.Field a b -> Declare (Definitions Schema) (Referenced Schema)
lookupDefinition rs t f = do
result <- typeToSchemaM t \n -> do
case lookupRS rs n of
Nothing -> pure $ mempty & description ?~ "Couldn't find definition for type " <> G.unName n <> " in field " <> G.unName (G._fName f)
Just tDef -> getDefinitionSchema rs n tDef (G._fSelectionSet f)
pure $ Inline result
getSelectionSchema :: RemoteSchemaIntrospection -> [(G.Name, (FieldDef, Maybe (FieldAnalysis var)))] -> Declare (Definitions Schema) Schema
getSelectionSchema rs fields = do
ps <- traverse (pure . G.unName . fst &&&& (\(fN, (td, fA)) -> getDefinitionSchema rs fN td fA {- (\(fN,(td,fA)) -> pure $ (G.unName fN,) $ getDefinitionSchema rs td fA) -})) fields
pure $ mempty & properties .~ OMap.fromList (map (second Inline) ps)
-- | A helper function to set the pattern field in Schema
-- Why not lens `pattern`? hlint doesn't like the name `pattern`
@ -190,57 +160,39 @@ setPattern p s = s {_schemaPattern = p}
getDefinitionSchema ::
RemoteSchemaIntrospection ->
G.Name ->
G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition ->
[G.Selection frag0 var0] ->
FieldDef ->
Maybe (FieldAnalysis var) ->
Declare (Definitions Schema) Schema
getDefinitionSchema rs tn td sels =
case td of
(G.TypeDefinitionInterface _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionInterface: " <> G.unName tn
(G.TypeDefinitionUnion _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionUnion: " <> G.unName tn
(G.TypeDefinitionEnum _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionEnum: " <> G.unName tn
(G.TypeDefinitionInputObject _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionInputObject: " <> G.unName tn
(G.TypeDefinitionObject otd) -> do
ps <- traverse (\sel -> getDefinitionSchemaObject rs (lookupFieldBySelection sel (G._otdFieldsDefinition otd)) sel) sels
pure $
mempty
& properties .~ OMap.fromList (catMaybes ps)
& type_ ?~ OpenApiObject
(G.TypeDefinitionScalar std) -> do
let (refType, patt) = referenceType True (T.toLower $ G.unName $ G._stdName std)
pure $
mempty
& title ?~ G.unName (G._stdName std)
& description .~ (G.unDescription <$> G._stdDescription std)
& type_ .~ refType
& setPattern patt
getDefinitionSchema rs tn fd fA =
typeToSchemaM
fd
( \case
(G.TypeDefinitionInterface _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionInterface: " <> G.unName tn
(G.TypeDefinitionUnion _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionUnion: " <> G.unName tn
(G.TypeDefinitionEnum _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionEnum: " <> G.unName tn
(G.TypeDefinitionInputObject _) -> pure $ mempty & description ?~ "Unsupported field type TypeDefinitionInputObject: " <> G.unName tn
(G.TypeDefinitionObject _) ->
case fA of
Nothing -> pure $ mempty & description ?~ "Field analysis not found"
Just FieldAnalysis {..} -> do
ps <- traverse (pure . G.unName . fst &&&& (\(fN, (td', fA')) -> getDefinitionSchema rs fN td' fA')) (OMap.toList _fFields)
pure $
mempty
& properties .~ OMap.fromList (map (second Inline) ps)
& type_ ?~ OpenApiObject
(G.TypeDefinitionScalar std) -> do
let (refType, patt) = referenceType True (T.toLower $ G.unName $ G._stdName std)
pure $
mempty
& title ?~ G.unName (G._stdName std)
& description .~ (G.unDescription <$> G._stdDescription std)
& type_ .~ refType
& setPattern patt
)
lookupFieldBySelection :: G.Selection frag0 var0 -> [G.FieldDefinition RemoteSchemaInputValueDefinition] -> Maybe (G.FieldDefinition RemoteSchemaInputValueDefinition)
lookupFieldBySelection (G.SelectionField f) = find \d -> G._fName f == G._fldName d
lookupFieldBySelection _ = const Nothing
getDefinitionSchemaObject ::
RemoteSchemaIntrospection ->
Maybe (G.FieldDefinition RemoteSchemaInputValueDefinition) ->
G.Selection frag0 var0 ->
Declare (Definitions Schema) (Maybe (Text, Referenced Schema))
getDefinitionSchemaObject _ Nothing _ = pure Nothing
getDefinitionSchemaObject _ _ (G.SelectionFragmentSpread _) = pure Nothing
getDefinitionSchemaObject _ _ (G.SelectionInlineFragment _) = pure Nothing
getDefinitionSchemaObject rs (Just fd) (G.SelectionField sel) = do
let sn = G._fName sel
ft = G._fldType fd
result <- typeToSchemaM ft \n -> do
let fn = G._fldName fd
case lookupRS rs n of
Nothing -> pure $ mempty & description ?~ "Couldn't find definition for type " <> G.unName n <> " in field " <> G.unName fn <> " selected by " <> G.unName sn
Just tDef -> getDefinitionSchema rs n tDef (G._fSelectionSet sel)
pure $ Just (G.unName sn, Inline result)
typeToSchemaM :: Monad m => G.GType -> (G.Name -> m Schema) -> m Schema
typeToSchemaM (G.TypeNamed _nullability tName) k = k tName
typeToSchemaM (G.TypeList n t) k = do
typeToSchemaM :: Monad m => FieldDef -> (G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition -> m Schema) -> m Schema
typeToSchemaM (FieldInfo _nullability tName) k = k tName
typeToSchemaM (FieldList n t) k = do
t' <- typeToSchemaM t k
pure $
mempty
@ -248,44 +200,19 @@ typeToSchemaM (G.TypeList n t) k = do
& type_ ?~ OpenApiArray
& items ?~ OpenApiItemsObject (Inline t') -- TODO: Why do we assume objects here?
lookupRS :: RemoteSchemaIntrospection -> G.Name -> Maybe (G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition)
lookupRS (RemoteSchemaIntrospection rsDefs) n = Map.lookup n rsDefs
field :: G.Selection frag var -> Maybe (G.Field frag var)
field (G.SelectionField f) = Just f
field _ = Nothing
infixl 7 &&&&
(&&&&) :: Applicative f => (t -> f a1) -> (t -> f a2) -> t -> f (a1, a2)
f &&&& g = \a -> (,) <$> f a <*> g a
-- TODO: Move these literals somewhere else
getRootFieldNameFromOpType :: G.OperationType -> G.Name
getRootFieldNameFromOpType G.OperationTypeQuery = $$(G.litName "query_root")
getRootFieldNameFromOpType G.OperationTypeMutation = $$(G.litName "mutation_root")
getRootFieldNameFromOpType G.OperationTypeSubscription = $$(G.litName "subscription_root")
asObjectTypeDefinition :: G.TypeDefinition possibleTypes inputType -> Maybe (G.ObjectTypeDefinition inputType)
asObjectTypeDefinition (G.TypeDefinitionObject o) = Just o
asObjectTypeDefinition _ = Nothing
-- * URL / Query Params and Request Body Functions
getVarList :: EndpointMetadata GQLQueryWithText -> [G.VariableDefinition]
getVarList e = vars =<< varLists
where
varLists = G.getExecutableDefinitions . unGQLQuery . getGQLQuery . _edQuery . _ceDefinition $ e
vars x = case x of
G.ExecutableDefinitionOperation (G.OperationDefinitionTyped (G.TypedOperationDefinition _ _ vds _ _)) -> vds
_ -> []
-- There could be an additional partitioning scheme besides referentiality to support more types in Params
getParams :: EndpointMetadata GQLQueryWithText -> [Referenced Param]
getParams d = varDetails =<< getVarList d
getParams :: Analysis G.Name -> EndpointUrl -> [Referenced Param]
getParams Analysis {..} eURL = varDetails =<< Map.toList _aVars
where
pathVars = map T.tail $ concat $ splitPath pure (const []) (_ceUrl d) -- NOTE: URL Variable name ':' prefix is removed for `elem` lookup.
varDetails G.VariableDefinition {..} =
pathVars = map T.tail $ concat $ splitPath pure (const []) eURL -- NOTE: URL Variable name ':' prefix is removed for `elem` lookup.
varDetails (_vdName, (_vdType, _vdDefaultValue)) =
let vName = G.unName _vdName
isRequired = not $ G.isNullable _vdType
in case getType _vdType of
@ -311,15 +238,16 @@ getType gt@(G.TypeNamed _ na) = case referenceType True t of
t = T.toLower $ G.unName na
getType t = Left t -- Non scalar types are deferred to reference types for processing using introspection
mkProperties :: Maybe RemoteSchemaIntrospection -> [G.VariableDefinition] -> Declare (Definitions Schema) (InsOrdHashMap Text (Referenced Schema))
mkProperties sd ds = OMap.fromList <$> traverse (mkProperty sdMap) ds
mkProperties :: Maybe RemoteSchemaIntrospection -> Analysis G.Name -> Declare (Definitions Schema) (InsOrdHashMap Text (Referenced Schema))
mkProperties sd Analysis {..} = OMap.fromList <$> traverse (mkProperty sdMap) ds
where
ds = Map.toList _aVars
sdMap = case sd of
Nothing -> OMap.empty
Just (RemoteSchemaIntrospection sd') -> OMap.fromList $ map (first G.unName) $ Map.toList sd'
mkProperty :: OMap.InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> G.VariableDefinition -> Declare (Definitions Schema) (Text, Referenced Schema)
mkProperty sd G.VariableDefinition {..} = do
mkProperty :: InsOrdHashMap Text (G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition) -> (G.Name, (G.GType, Maybe (G.Value Void))) -> Declare (Definitions Schema) (Text, Referenced Schema)
mkProperty sd (_vdName, (_vdType, _vdDefaultValue)) = do
d <- case getType _vdType of
Left t -> handleRefType sd t
Right (vdType, patt) ->
@ -349,7 +277,7 @@ handleRefType sd = \case
& items ?~ OpenApiItemsObject st
-- TODO: No reference types should be nullable and only references to reference types
--
declareReference :: G.Nullability -> Text -> OMap.InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> Declare (Definitions Schema) ()
declareReference nullability n ts = do
isAvailable <- referenceAvailable n
@ -509,12 +437,15 @@ getURL d =
extractEndpointInfo :: Maybe RemoteSchemaIntrospection -> EndpointMethod -> EndpointMetadata GQLQueryWithText -> Declare (Definitions Schema) EndpointData
extractEndpointInfo sd method d = do
_edProperties <- mkProperties sd (getVarList d)
_edResponse <- mkResponse _edMethod _edUrl sd d
_edProperties <- mkProperties sd _analysis
_edResponse <- mkResponse _edMethod _edUrl sd _analysis
pure EndpointData {..}
where
_eDef = mdDefinitions d
-- mdDefinition returns a list, but there should only be one definition associated, so it is safe to fold
_analysis = fromMaybe mempty (fold $ mapMaybe (\e -> fmap (analyzeGraphqlQuery e) sd) _eDef)
_edUrl = T.unpack . getURL $ d
_edVarList = getParams d
_edVarList = getParams _analysis (_ceUrl d)
_edDescription = getComment d
_edName = unNonEmptyText $ unEndpointName $ _ceName d
_edMethod = [unEndpointMethod method] -- NOTE: Methods are grouped with into matching endpoints - Name used for grouping.

View File

@ -0,0 +1,72 @@
- description: Try to add a POST rest endpoint with default argument
url: /v1/query
status: 200
response:
message: success
query:
type: create_rest_endpoint
args:
url: with_duplicate_field_name
name: with_duplicate_field_name
methods:
- POST
definition:
query:
collection_name: test_collection
query_name: query_with_duplicate_field_name
- description: Call openapi json endpoint
url: /api/swagger/json
method: GET
status: 200
query:
response:
openapi: 3.0.0
info:
version: ''
title: Rest Endpoints
description: This OpenAPI specification is automatically generated by Hasura.
paths:
/api/rest/with_duplicate_field_name:
post:
summary: with_duplicate_field_name
description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\
query { test_table { first_name } test_table { last_name } }\n```"
parameters:
- schema:
type: string
in: header
name: x-hasura-admin-secret
description: Your x-hasura-admin-secret will be used for authentication
of the API request.
responses:
'200':
content:
application/json:
schema:
properties:
test_table:
items:
type: object
properties:
first_name:
title: String
type: string
last_name:
title: String
type: string
type: array
nullable: false
description: Responses for POST /api/rest/with_duplicate_field_name
components: {}
- description: Try to remove the endpoint
url: /v1/query
status: 200
response:
message: success
query:
type: drop_rest_endpoint
args:
name: with_duplicate_field_name

View File

@ -68,4 +68,6 @@ args:
- name: mutation_complex_args
query: "mutation QQ($new_object: test_table_set_input!, $first_name: String!) { update_test_table(where: {first_name: {_eq: $first_name}}, _set: $new_object) { affected_rows } }"
- name: mutation_recursive_arg
query: "mutation MyMutation($object: test_table_recurse_insert_input!) { insert_test_table_recurse_one(object: $object) { id } }"
query: "mutation MyMutation($object: test_table_recurse_insert_input!) { insert_test_table_recurse_one(object: $object) { id } }"
- name: query_with_duplicate_field_name
query: "query { test_table { first_name } test_table { last_name } }"

View File

@ -43,3 +43,6 @@ class TestOpenAPISpec:
def test_endpoint_with_recursive_arg(self, hge_ctx, transport):
check_query_f(hge_ctx, self.dir() + '/openapi_post_endpoint_test_recursive_arg.yaml', transport)
def test_duplicate_field_name(self, hge_ctx, transport):
check_query_f(hge_ctx, self.dir() + '/openapi_get_endpoint_test_duplicate_field_name.yaml', transport)