From 02aef27a7532f678bc90638a53fc978b3c9fae69 Mon Sep 17 00:00:00 2001 From: David Overton Date: Wed, 22 Dec 2021 19:30:15 +1100 Subject: [PATCH] Add request body to OpenAPI PR-URL: https://github.com/hasura/graphql-engine-mono/pull/2632 Co-authored-by: Lyndon Maydwell <92299+sordina@users.noreply.github.com> Co-authored-by: paritosh-08 <85472423+paritosh-08@users.noreply.github.com> GitOrigin-RevId: 067e182effaed255ff047abeee309d65a9fb191c --- CHANGELOG.md | 2 + server/graphql-engine.cabal | 1 + server/src-lib/Hasura/GraphQL/RemoteServer.hs | 5 + server/src-lib/Hasura/Server/OpenAPI.hs | 627 +++++++++++++++--- .../queries/openapi/openapi_empty.yaml | 4 +- ...penapi_endpoint_with_multiple_methods.yaml | 443 +++++++++---- ...openapi_get_endpoint_test_complex_arg.yaml | 106 +++ ...penapi_get_endpoint_test_complex_args.yaml | 105 +++ .../openapi_get_endpoint_test_simple.yaml | 46 +- .../openapi_multiple_endpoints_same_path.yaml | 163 +++-- .../openapi_multiple_endpoints_test.yaml | 249 ++++--- ...napi_post_endpoint_test_recursive_arg.yaml | 104 +++ .../openapi_post_endpoint_test_with_args.yaml | 87 ++- ...napi_post_endpoint_test_with_args_url.yaml | 89 ++- ...i_post_endpoint_test_with_default_arg.yaml | 75 ++- server/tests-py/queries/openapi/setup.yaml | 29 + server/tests-py/queries/openapi/teardown.yaml | 2 +- server/tests-py/test_openapi.py | 8 + 18 files changed, 1671 insertions(+), 474 deletions(-) create mode 100644 server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_arg.yaml create mode 100644 server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_args.yaml create mode 100644 server/tests-py/queries/openapi/openapi_post_endpoint_test_recursive_arg.yaml diff --git a/CHANGELOG.md b/CHANGELOG.md index 00d5f1ad6fd..3fb44b2053f 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -3,6 +3,8 @@ ## Next release (Add highlights/major features below) +- server: add request and response bodies to OpenAPI specification of REST endpoints + ### Bug fixes and improvements (Add entries below in the order of server, console, cli, docs, others) diff --git a/server/graphql-engine.cabal b/server/graphql-engine.cabal index 648cb957a33..bf9eb8a8f1a 100644 --- a/server/graphql-engine.cabal +++ b/server/graphql-engine.cabal @@ -146,6 +146,7 @@ library , hashable-time , http-client-tls , http-conduit + , http-media , http-types , kan-extensions , kriti-lang diff --git a/server/src-lib/Hasura/GraphQL/RemoteServer.hs b/server/src-lib/Hasura/GraphQL/RemoteServer.hs index 93dbe4813fe..a86958ab00e 100644 --- a/server/src-lib/Hasura/GraphQL/RemoteServer.hs +++ b/server/src-lib/Hasura/GraphQL/RemoteServer.hs @@ -1,8 +1,10 @@ module Hasura.GraphQL.RemoteServer ( fetchRemoteSchema, IntrospectionResult, + parseIntrospectionResult, execRemoteGQ, identityCustomizer, + introspectionQuery, -- The following exports are needed for unit tests getCustomizer, validateSchemaCustomizationsDistinct, @@ -136,6 +138,9 @@ validateSchemaCustomizationsDistinct remoteSchemaCustomizer (RemoteSchemaIntrosp <> dquoteList dups _ -> pure () +parseIntrospectionResult :: J.Value -> Maybe IntrospectionResult +parseIntrospectionResult = fmap fromIntrospection . J.parseMaybe J.parseJSON + -- | Make an introspection query to the remote graphql server for the data we -- need to present and stitch the remote schema. This powers add_remote_schema, -- and also is called by schema cache rebuilding code in "Hasura.RQL.DDL.Schema.Cache". diff --git a/server/src-lib/Hasura/Server/OpenAPI.hs b/server/src-lib/Hasura/Server/OpenAPI.hs index 868477e41c3..df0c136f398 100644 --- a/server/src-lib/Hasura/Server/OpenAPI.hs +++ b/server/src-lib/Hasura/Server/OpenAPI.hs @@ -1,30 +1,276 @@ {-# LANGUAGE OverloadedStrings #-} +-- | +-- Module : Hasura.Server.OpenAPI +-- Description : Builds an OpenAPI specification for the REST endpoints from a SchemaCache via the `declareOpenApiSpec` function. +-- +-- The implementation currently iterates over the endpoints building up `EndpointData` for each then exposes this as an OpenAPI Schema. +-- +-- Most functions are in the `Declare` monad so that they can add new component definitions on the fly that can be referenced. +-- This is especially useful for the params and request body documentation. +-- +-- The response body recurses over the SelectionSet Fields associated with an endpoint and looks up types by name in +-- a `RemoteSchemaIntrospection` result generated from the `SchemaCache`. +-- +-- Response bodies are mostly delcared inline, since the associated query will likely be unique and determine the fields +-- contained in the response. module Hasura.Server.OpenAPI (serveJSON) where import Control.Lens -import Data.Aeson (Value, toJSON) -import Data.HashMap.Strict qualified as M -import Data.HashMap.Strict.InsOrd qualified as MI -import Data.List.NonEmpty qualified as LNE +import Data.Aeson qualified as J +import Data.Aeson.Ordered qualified as JO +import Data.HashMap.Strict qualified as Map +import Data.HashMap.Strict.InsOrd qualified as OMap +import Data.List.NonEmpty qualified as NE import Data.OpenApi import Data.OpenApi.Declare -import Data.Set.Internal qualified as S +import Data.Set qualified as Set import Data.Text qualified as T -import Data.Text.NonEmpty qualified as TNE +import Data.Text.Extended (commaSeparated) +import Data.Text.NonEmpty +import Hasura.GraphQL.Context +import Hasura.GraphQL.Namespace (mkUnNamespacedRootFieldAlias) +import Hasura.GraphQL.Parser.Schema (Variable) +import Hasura.GraphQL.RemoteServer (introspectionQuery, parseIntrospectionResult) +import Hasura.GraphQL.Transport.HTTP.Protocol import Hasura.Prelude hiding (get, put) +import Hasura.RQL.IR.Root import Hasura.RQL.Types.Endpoint import Hasura.RQL.Types.QueryCollection +import Hasura.RQL.Types.RemoteSchema import Hasura.RQL.Types.SchemaCache +import Hasura.Session (adminRoleName) import Language.GraphQL.Draft.Syntax qualified as G +import Network.HTTP.Media.MediaType ((//)) data EndpointData = EndpointData { _edUrl :: String, _edMethod :: [Text], _edVarList :: [Referenced Param], + _edProperties :: InsOrdHashMap Text (Referenced Schema), + _edResponse :: Maybe Response, _edDescription :: Text, -- contains API comments and graphql query _edName :: Text } + deriving (Show) + +-- * Response Body Related Functions. + +{- + +Example stepthrough initiated by call to getSelectionSchema: + + * Endpoint insert_foo + * getExecutableDefinitions -> List (Normally 1 entry) + * ExecutableDefinitionOperation -> OperationDefinitionTyped -> TypedOperationDefinition (_todType = OperationTypeMutation) + * _todSelectionSet -> + [SelectionField + (Field{ _fName = Name{unName = "insert_foo"}, + _fSelectionSet + = [SelectionField + (Field{ _fName = Name{unName = "returning"}, + _fSelectionSet + = [..., SelectionField + (Field{ _fName = Name{unName = "id"}, + _fSelectionSet = []}), + * Lookup introspection schema, Under mutation_root (inferred from operationtype = OperationTypeMutation) + RemoteSchemaIntrospection + (fromList + [..., (Name{unName = "mutation_root"}, + TypeDefinitionObject + (ObjectTypeDefinition{_otdDescription = + Just (Description{unDescription = "mutation root"}), + _otdName = Name{unName = "mutation_root"}, + _otdImplementsInterfaces = [], _otdDirectives = [], + _otdFieldsDefinition = + [..., FieldDefinition{_fldDescription = Just (Description{unDescription = "insert data into the table: \"foo\""}), + _fldName = Name{unName = "insert_foo"}, + _fldType = TypeNamed (Nullability{unNullability = True}) (Name{unName = "foo_mutation_response"}), + * Find that type for insert_foo field in mutation_root is named type "foo_mutation_response" + * Look up "foo_mutation_response" in introspection schema: + (Name{unName = "foo_mutation_response"}, + TypeDefinitionObject + (ObjectTypeDefinition{_otdDescription = Just (Description{unDescription = "response of any mutation on the table \"foo\""}), + _otdName = Name{unName = "foo_mutation_response"}, + _otdFieldsDefinition = + [..., FieldDefinition{_fldDescription = + Just + (Description{unDescription = + "data from the rows affected by the mutation"}), + _fldName = Name{unName = "returning"}, + _fldArgumentsDefinition = [], + _fldType = + TypeList (Nullability{unNullability = False}) + (TypeNamed + (Nullability{unNullability = False}) + (Name{unName = "foo"})), + _fldDirectives = []}]})), + * Find first referenced sub-field "returning" + * It has type (TypeNamed (Name{unName = "foo"})), + * Look up "foo" in Introspection Schema: ..., + (Name{unName = "foo"}, + TypeDefinitionObject + (ObjectTypeDefinition{_otdDescription = Just (Description{unDescription = "columns and relationships of \"foo\""}), + _otdName = Name{unName = "foo"}, _otdImplementsInterfaces = [], + _otdFieldsDefinition = + [ ..., FieldDefinition{_fldDescription = Nothing, + _fldName = Name{unName = "id"}, + _fldType = TypeNamed (Nullability{unNullability = False}) (Name{unName = "uuid"}), + * Lookup first sub-sub field by SelectionSet field name "id" + * See that it has type: TypeNamed (Name{unName = "uuid"}) + * See that there are no sub-sub-sub fields + * declare type uuid by looking up its definition + (Name{unName = "uuid"}, + TypeDefinitionScalar + (ScalarTypeDefinition{_stdDescription = Nothing, + _stdName = Name{unName = "uuid"}, _stdDirectives = []})), + * reference type name from components in output + + ... Proceed with other sub-fields and fields + +-} + +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 + + -- 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 _ _ Nothing _ = pure Nothing +mkResponse epMethods epUrl (Just rs) md = do + fs <- getSelectionSchema rs (mdSelectionFields md) + 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 + +-- | A helper function to set the pattern field in Schema +-- Why not lens `pattern`? hlint doesn't like the name `pattern` +-- https://github.com/ndmitchell/hlint/issues/607 +setPattern :: Maybe Pattern -> Schema -> Schema +setPattern p s = s {_schemaPattern = p} + +getDefinitionSchema :: + RemoteSchemaIntrospection -> + G.Name -> + G.TypeDefinition [G.Name] RemoteSchemaInputValueDefinition -> + [G.Selection frag0 var0] -> + 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 + +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 + t' <- typeToSchemaM t k + pure $ + mempty + & nullable ?~ G.unNullability n + & 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 @@ -34,35 +280,186 @@ getVarList e = vars =<< varLists G.ExecutableDefinitionOperation (G.OperationDefinitionTyped (G.TypedOperationDefinition _ _ vds _ _)) -> vds _ -> [] -getVariableDefinitions :: EndpointMetadata GQLQueryWithText -> [Referenced Param] -getVariableDefinitions d = fmap varDetails varList +-- 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 where - pathVars = map T.tail $ lefts $ splitPath Left Right (_ceUrl d) -- NOTE: URL Variable name ':' prefix is removed for `elem` lookup. - varList = getVarList d - varDetails a = - let vName = (G.unName . G._vdName $ a) - in Inline $ - mkParam - vName - Nothing - Nothing - (if vName `elem` pathVars then ParamPath else ParamQuery) - Nothing - (getDefaultVar a) - ( case G._vdType a of - G.TypeNamed _ na -> case G.unName na of - "Int" -> Just OpenApiInteger - "String" -> Just OpenApiString - "json" -> Just OpenApiObject - _ -> Nothing - G.TypeList _ _ -> Nothing - ) + pathVars = map T.tail $ concat $ splitPath pure (const []) (_ceUrl d) -- NOTE: URL Variable name ':' prefix is removed for `elem` lookup. + varDetails G.VariableDefinition {..} = + let vName = G.unName _vdName + isRequired = not $ G.isNullable _vdType + in case getType _vdType of + Left _foo -> [] -- Complex types are not allowed as params + Right (vdType, patt) -> + pure $ + Inline $ + mkParam + vName + (if isRequired then Just $ "_\"" <> vName <> "\" is required (enter it either in parameters or request body)_" else Nothing) + Nothing + (if vName `elem` pathVars then ParamPath else ParamQuery) + Nothing + (gqlToJsonValue <$> _vdDefaultValue) + (Just vdType) + patt + +getType :: G.GType -> Either G.GType (OpenApiType, Maybe Pattern) +getType gt@(G.TypeNamed _ na) = case referenceType True t of + (Nothing, _) -> Left gt + (Just typ, patt) -> Right (typ, patt) + where + 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 + where + 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 + d <- case getType _vdType of + Left t -> handleRefType sd t + Right (vdType, patt) -> + pure $ + Inline $ + mempty + & nullable ?~ G.isNullable _vdType + & type_ ?~ vdType + & default_ .~ fmap gqlToJsonValue _vdDefaultValue + & setPattern patt + + pure (G.unName _vdName, d) + +handleRefType :: OMap.InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> G.GType -> Declare (Definitions Schema) (Referenced Schema) +handleRefType sd = \case + G.TypeNamed nullability nameWrapper -> do + let n = G.unName nameWrapper + declareReference nullability n sd + pure $ Ref $ Reference n + G.TypeList nullability subType -> do + st <- handleRefType sd subType + pure $ + Inline $ + mempty + & nullable ?~ (G.unNullability nullability && G.isNullable subType) + & type_ ?~ OpenApiArray + & 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 + unless isAvailable do + for_ (OMap.lookup n ts) \t -> do + let properties' = getPropertyReferences ts (typeProperties t) + + result <- + declare $ + OMap.singleton n $ + let (refType, patt) = referenceType (null properties') (T.toLower n) + in mempty + & nullable ?~ G.unNullability nullability + & description .~ typeDescription t + & properties .~ properties' + & type_ .~ refType + & setPattern patt + void $ processProperties ts (typeProperties t) + pure result + +referenceAvailable :: Text -> DeclareT (Definitions Schema) Identity Bool +referenceAvailable n = OMap.member n <$> look + +getPropertyReferences :: InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> Maybe [RemoteSchemaInputValueDefinition] -> InsOrdHashMap Text (Referenced Schema) +getPropertyReferences _ Nothing = mempty +getPropertyReferences sd (Just ds) = + let ds' = fmap (processProperty' sd) ds + in OMap.fromList ds' + +processProperty' :: InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> RemoteSchemaInputValueDefinition -> (Text, Referenced Schema) +processProperty' sd (RemoteSchemaInputValueDefinition d _preset) = + let n = G._ivdName d + t = G._ivdType d + rt = handleRefType' sd t + in (G.unName n, rt) + +handleRefType' :: OMap.InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> G.GType -> Referenced Schema +handleRefType' sd = \case + G.TypeNamed _nullability nameWrapper -> + let n = G.unName nameWrapper + in Ref $ Reference n + G.TypeList nullability subType -> + let st = handleRefType' sd subType + in Inline $ + mempty + & nullable ?~ (G.unNullability nullability && G.isNullable subType) + & type_ ?~ OpenApiArray + & items ?~ OpenApiItemsObject st + +typeDescription :: G.TypeDefinition possibleTypes inputType -> Maybe Text +typeDescription = \case + (G.TypeDefinitionScalar o) -> G.unDescription <$> G._stdDescription o + (G.TypeDefinitionObject o) -> G.unDescription <$> G._otdDescription o + (G.TypeDefinitionInterface o) -> G.unDescription <$> G._itdDescription o + (G.TypeDefinitionUnion o) -> G.unDescription <$> G._utdDescription o + (G.TypeDefinitionEnum o) -> G.unDescription <$> G._etdDescription o + (G.TypeDefinitionInputObject o) -> G.unDescription <$> G._iotdDescription o + +typeName :: G.TypeDefinition possibleTypes inputType -> Text +typeName = \case + (G.TypeDefinitionScalar o) -> G.unName (G._stdName o) + (G.TypeDefinitionObject o) -> G.unName (G._otdName o) + (G.TypeDefinitionInterface o) -> G.unName (G._itdName o) + (G.TypeDefinitionUnion o) -> G.unName (G._utdName o) + (G.TypeDefinitionEnum o) -> G.unName (G._etdName o) + (G.TypeDefinitionInputObject o) -> G.unName (G._iotdName o) + +typeProperties :: G.TypeDefinition possibleTypes RemoteSchemaInputValueDefinition -> Maybe [RemoteSchemaInputValueDefinition] +typeProperties = \case + (G.TypeDefinitionScalar _) -> Nothing + (G.TypeDefinitionInterface _) -> Nothing + (G.TypeDefinitionUnion _) -> Nothing + (G.TypeDefinitionEnum _) -> Nothing + (G.TypeDefinitionInputObject o) -> Just $ G._iotdValueDefinitions o + (G.TypeDefinitionObject _) -> Nothing + +-- TODO: Can we reuse something from rest module to handle this? +-- TODO: referenceType could be improved, instead of using Bool (to indicate if it is object or scalar), +-- we can do something better +referenceType :: Bool -> Text -> (Maybe OpenApiType, Maybe Pattern) +referenceType False = const (Just OpenApiObject, Nothing) +referenceType True = \case + "int" -> (Just OpenApiInteger, Nothing) + "float" -> (Just OpenApiNumber, Nothing) + "double" -> (Just OpenApiNumber, Nothing) + "uuid" -> (Just OpenApiString, Just "[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}") + "bool" -> (Just OpenApiBoolean, Nothing) + "boolean" -> (Just OpenApiBoolean, Nothing) + "string" -> (Just OpenApiString, Nothing) + "id" -> (Just OpenApiString, Nothing) + _ -> (Nothing, Nothing) + +processProperties :: InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> Maybe [RemoteSchemaInputValueDefinition] -> DeclareT (Definitions Schema) Identity (InsOrdHashMap Text (Referenced Schema)) +processProperties _ Nothing = pure mempty +processProperties sd (Just ds) = do + ds' <- traverse (processProperty sd) ds + pure $ OMap.fromList ds' + +processProperty :: InsOrdHashMap Text (G.TypeDefinition a RemoteSchemaInputValueDefinition) -> RemoteSchemaInputValueDefinition -> DeclareT (Definitions Schema) Identity (Text, Referenced Schema) +processProperty sd (RemoteSchemaInputValueDefinition d _preset) = do + let n = G._ivdName d + t = G._ivdType d + rt <- handleRefType sd t + pure (G.unName n, rt) getGQLQueryFromTrie :: EndpointMetadata GQLQueryWithText -> Text getGQLQueryFromTrie = getGQLQueryText . _edQuery . _ceDefinition -mkParam :: Text -> Maybe Text -> Maybe Bool -> ParamLocation -> Maybe Bool -> Maybe Value -> Maybe OpenApiType -> Param -mkParam nameP desc req loc allowEmpty def varType = +mkParam :: Text -> Maybe Text -> Maybe Bool -> ParamLocation -> Maybe Bool -> Maybe J.Value -> Maybe OpenApiType -> Maybe Pattern -> Param +mkParam nameP desc req loc allowEmpty def varType patt = mempty & name .~ nameP & description .~ desc @@ -74,19 +471,21 @@ mkParam nameP desc req loc allowEmpty def varType = ( mempty & default_ .~ def & type_ .~ varType + & setPattern patt ) -getDefaultVar :: G.VariableDefinition -> Maybe Value -getDefaultVar var = case G._vdDefaultValue var of - Nothing -> Nothing - Just va -> case va of - G.VNull -> Nothing - G.VInt n -> Just $ toJSON n - G.VFloat sci -> Just $ toJSON sci - G.VString txt -> Just $ toJSON txt - G.VBoolean b -> Just $ toJSON b - G.VEnum ev -> Just $ toJSON ev - _ -> Nothing +gqlToJsonValue :: G.Value Void -> J.Value +gqlToJsonValue = \case + G.VNull -> J.Null + G.VInt n -> J.toJSON n + G.VFloat sci -> J.toJSON sci + G.VString txt -> J.toJSON txt + G.VBoolean b -> J.toJSON b + G.VEnum ev -> J.toJSON ev + G.VList lst -> J.toJSON $ gqlToJsonValue <$> lst + G.VObject obj -> J.toJSON $ gqlToJsonValue <$> obj + +-- * Top level schema construction getComment :: EndpointMetadata GQLQueryWithText -> Text getComment d = comment @@ -101,49 +500,110 @@ getURL d = "/api/rest/" -- The url will be of the format /:/: ... always, so we can -- split and take the first element (it should never fail) - <> fst (T.breakOn "/" (TNE.unNonEmptyText . unEndpointUrl . _ceUrl $ d)) + <> fst (T.breakOn "/" (unNonEmptyText . unEndpointUrl . _ceUrl $ d)) <> foldl ( \b a -> b <> "/{" <> a <> "}" ) "" (map T.tail $ lefts $ splitPath Left Right (_ceUrl d)) -extractEndpointInfo :: EndpointMethod -> EndpointMetadata GQLQueryWithText -> EndpointData -extractEndpointInfo method d = - let _edUrl = T.unpack . getURL $ d - _edVarList = getVariableDefinitions d - _edDescription = getComment d - _edName = TNE.unNonEmptyText $ unEndpointName $ _ceName d - in EndpointData - { _edMethod = [unEndpointMethod method], -- NOTE: Methods are grouped with into matching endpoints - Name used for grouping. - .. - } - -getEndpointsData :: SchemaCache -> [EndpointData] -getEndpointsData sc = map squashEndpointGroup endpointsGrouped +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 + pure EndpointData {..} where - endpointTrie = scEndpoints sc - methodMaps = leaves endpointTrie - endpointsWithMethods = concatMap (\(m, s) -> map (m,) (S.toList s)) $ concatMap (M.toList . _unMultiMap) methodMaps - endpointsWithInfo = map (uncurry extractEndpointInfo) endpointsWithMethods - endpointsGrouped = LNE.groupBy (\a b -> _edName a == _edName b) endpointsWithInfo + _edUrl = T.unpack . getURL $ d + _edVarList = getParams d + _edDescription = getComment d + _edName = unNonEmptyText $ unEndpointName $ _ceName d + _edMethod = [unEndpointMethod method] -- NOTE: Methods are grouped with into matching endpoints - Name used for grouping. + +getEndpointsData :: Maybe RemoteSchemaIntrospection -> SchemaCache -> Declare (Definitions Schema) [EndpointData] +getEndpointsData sd sc = do + let endpointTrie = scEndpoints sc + methodMaps = leaves endpointTrie + endpointsWithMethods = concatMap (\(m, s) -> map (m,) (Set.toList s)) $ concatMap (Map.toList . _unMultiMap) methodMaps + + endpointsWithInfo <- traverse (uncurry (extractEndpointInfo sd)) endpointsWithMethods + + let endpointsGrouped = NE.groupBy (\a b -> _edName a == _edName b) endpointsWithInfo + + pure $ map squashEndpointGroup endpointsGrouped squashEndpointGroup :: NonEmpty EndpointData -> EndpointData -squashEndpointGroup g = (LNE.head g) {_edMethod = concatMap _edMethod g} +squashEndpointGroup g = (NE.head g) {_edMethod = concatMap _edMethod g} + +getSchemaIntrospection :: SchemaCache -> Maybe RemoteSchemaIntrospection +getSchemaIntrospection SchemaCache {..} = do + RoleContext {..} <- Map.lookup adminRoleName scGQLContext + fieldMap <- either (const Nothing) Just $ gqlQueryParser _rctxDefault $ fmap (fmap nameToVariable) $ G._todSelectionSet $ _grQuery introspectionQuery + RFRaw v <- OMap.lookup (mkUnNamespacedRootFieldAlias $$(G.litName "__schema")) fieldMap + fmap irDoc $ parseIntrospectionResult $ J.object [("data", J.object [("__schema", JO.fromOrdered v)])] + where + -- This value isn't used but we give it a type to be more clear about what is being ignored + nameToVariable :: G.Name -> Variable + nameToVariable = undefined serveJSON :: SchemaCache -> OpenApi serveJSON sc = spec & components . schemas .~ defs where (defs, spec) = runDeclare (declareOpenApiSpec sc) mempty +-- | If all variables are scalar or optional then the entire request body can be marked as optional +isRequestBodyRequired :: EndpointData -> Bool +isRequestBodyRequired ed = not $ all isNotRequired (_edProperties ed) + where + -- The use of isNotRequired here won't work with list types since they are inline, but contain references + isNotRequired (Inline Schema {..}) = isScalarType _schemaType || (Just True == _schemaNullable) + isNotRequired (Ref _) = False -- Not all `Ref` are non nullable, imagine two endpoints using the same Ref one being nullable and other not + isScalarType :: Maybe OpenApiType -> Bool + isScalarType Nothing = False + isScalarType (Just t) = case t of + OpenApiString -> True + OpenApiNumber -> True + OpenApiInteger -> True + OpenApiBoolean -> True + OpenApiArray -> False + OpenApiNull -> False + OpenApiObject -> False + +-- * Entry point + declareOpenApiSpec :: SchemaCache -> Declare (Definitions Schema) OpenApi declareOpenApiSpec sc = do - let mkOperation :: EndpointData -> Operation + let _schemaIntrospection = getSchemaIntrospection sc + warnings = case _schemaIntrospection of + Nothing -> "\n\n⚠️ Schema introspection failed" + _ -> "" + + mkRequestBody :: EndpointData -> RequestBody + mkRequestBody ed = + mempty + & description ?~ "Query parameters can also be provided in the request body as a JSON object" + & required ?~ isRequestBodyRequired ed + & content + .~ OMap.singleton + ("application" // "json") + ( mempty + & schema + ?~ Inline + ( mempty + & type_ ?~ OpenApiObject + & properties .~ _edProperties ed + ) + ) + + mkOperation :: EndpointData -> Operation mkOperation ed = mempty & description ?~ _edDescription ed & summary ?~ _edName ed - & parameters .~ (Inline xHasuraAS : _edVarList ed) + & parameters .~ (Inline xHasuraAdminSecret : _edVarList ed) + & requestBody .~ toMaybe (not (null (_edProperties ed))) (Inline (mkRequestBody ed)) + & responses .~ Responses Nothing (maybe mempty (OMap.singleton 200 . Inline) (_edResponse ed)) + where + toMaybe b a = if b then Just a else Nothing getOPName :: EndpointData -> Text -> Maybe Operation getOPName ed methodType = @@ -151,8 +611,8 @@ declareOpenApiSpec sc = do then Just $ mkOperation ed else Nothing - xHasuraAS :: Param - xHasuraAS = + xHasuraAdminSecret :: Param + xHasuraAdminSecret = mkParam "x-hasura-admin-secret" (Just "Your x-hasura-admin-secret will be used for authentication of the API request.") @@ -161,20 +621,37 @@ declareOpenApiSpec sc = do Nothing Nothing (Just OpenApiString) + Nothing generatePathItem :: EndpointData -> PathItem generatePathItem ed = - mempty - & get .~ getOPName ed "GET" - & post .~ getOPName ed "POST" - & put .~ getOPName ed "PUT" - & delete .~ getOPName ed "DELETE" - & patch .~ getOPName ed "PATCH" + let pathData = + mempty + & get .~ getOPName ed "GET" + & post .~ getOPName ed "POST" + & put .~ getOPName ed "PUT" + & delete .~ getOPName ed "DELETE" + & patch .~ getOPName ed "PATCH" + completePathData = + if pathData == mempty + then + mempty + & post + ?~ mkOperation + ed + { _edDescription = + "⚠️ Method(" + <> tshow (_edMethod ed) + <> ") not supported, defaulting to POST\n\n" + <> _edDescription ed + } + else pathData + in completePathData - endpointLst = getEndpointsData sc + endpointLst <- getEndpointsData _schemaIntrospection sc - mkOpenAPISchema :: [EndpointData] -> InsOrdHashMap FilePath PathItem - mkOpenAPISchema edLst = foldl (\hm ed -> MI.insertWith (<>) (_edUrl ed) (generatePathItem ed) hm) mempty edLst + let mkOpenAPISchema :: [EndpointData] -> InsOrdHashMap FilePath PathItem + mkOpenAPISchema edLst = foldl (\hm ed -> OMap.insertWith (<>) (_edUrl ed) (generatePathItem ed) hm) mempty edLst openAPIPaths = mkOpenAPISchema endpointLst @@ -182,4 +659,4 @@ declareOpenApiSpec sc = do mempty & paths .~ openAPIPaths & info . title .~ "Rest Endpoints" - & info . description ?~ "These OpenAPI specifications are automatically generated by Hasura." + & info . description ?~ "This OpenAPI specification is automatically generated by Hasura." <> warnings diff --git a/server/tests-py/queries/openapi/openapi_empty.yaml b/server/tests-py/queries/openapi/openapi_empty.yaml index ef8fcec026e..0ecb2c10068 100644 --- a/server/tests-py/queries/openapi/openapi_empty.yaml +++ b/server/tests-py/queries/openapi/openapi_empty.yaml @@ -8,5 +8,5 @@ response: info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. - components: {} \ No newline at end of file + description: This OpenAPI specification is automatically generated by Hasura. + components: {} diff --git a/server/tests-py/queries/openapi/openapi_endpoint_with_multiple_methods.yaml b/server/tests-py/queries/openapi/openapi_endpoint_with_multiple_methods.yaml index 35c1fbecd6a..54a1c50562d 100644 --- a/server/tests-py/queries/openapi/openapi_endpoint_with_multiple_methods.yaml +++ b/server/tests-py/queries/openapi/openapi_endpoint_with_multiple_methods.yaml @@ -9,11 +9,11 @@ url: multi_method_endpoint name: multi_method_endpoint methods: - - GET - - POST - - PUT - - DELETE - - PATCH + - GET + - POST + - PUT + - DELETE + - PATCH definition: query: collection_name: test_collection @@ -30,166 +30,315 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: /api/rest/multi_method_endpoint: get: summary: multi_method_endpoint - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/multi_method_endpoint put: summary: multi_method_endpoint - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/multi_method_endpoint post: summary: multi_method_endpoint - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/multi_method_endpoint delete: summary: multi_method_endpoint - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/multi_method_endpoint patch: summary: multi_method_endpoint - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/multi_method_endpoint components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_arg.yaml b/server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_arg.yaml new file mode 100644 index 00000000000..818c5167317 --- /dev/null +++ b/server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_arg.yaml @@ -0,0 +1,106 @@ +- description: Try to add a GET rest endpoint with no argument + url: /v1/query + status: 200 + response: + message: success + query: + type: create_rest_endpoint + args: + url: complex_arg + name: complex_arg + methods: + - POST + definition: + query: + collection_name: test_collection + query_name: mutation_complex_arg + + +- 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/complex_arg: + post: + summary: complex_arg + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($objects: [test_table_insert_input!]!) { insert_test_table( objects:\ + \ $objects) { returning { id } } }\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. + requestBody: + required: true + content: + application/json: + schema: + type: object + properties: + objects: + items: + $ref: "#/components/schemas/test_table_insert_input" + type: array + nullable: false + description: Query parameters can also be provided in the request body as + a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + description: Responses for POST /api/rest/complex_arg + components: + schemas: + String: + type: string + nullable: true + uuid: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + type: string + nullable: true + test_table_insert_input: + type: object + description: input type for inserting data into table "test_table" + nullable: false + properties: + first_name: + "$ref": "#/components/schemas/String" + last_name: + "$ref": "#/components/schemas/String" + id: + "$ref": "#/components/schemas/uuid" +- description: Try to remove the endpoint + url: /v1/query + status: 200 + response: + message: success + query: + type: drop_rest_endpoint + args: + name: complex_arg diff --git a/server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_args.yaml b/server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_args.yaml new file mode 100644 index 00000000000..67b258ab730 --- /dev/null +++ b/server/tests-py/queries/openapi/openapi_get_endpoint_test_complex_args.yaml @@ -0,0 +1,105 @@ +- description: Try to add a GET rest endpoint with no argument + url: /v1/query + status: 200 + response: + message: success + query: + type: create_rest_endpoint + args: + url: complex_args + name: complex_args + methods: + - POST + definition: + query: + collection_name: test_collection + query_name: mutation_complex_args + +- 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/complex_args: + post: + summary: complex_args + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + 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 } }\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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or + request body)_ + requestBody: + required: true + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + new_object: + $ref: '#/components/schemas/test_table_set_input' + description: Query parameters can also be provided in the request body as + a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + update_test_table: + type: object + properties: + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/complex_args + components: + schemas: + String: + type: string + nullable: true + uuid: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + type: string + nullable: true + test_table_set_input: + type: object + description: input type for updating data in table "test_table" + nullable: false + properties: + first_name: + $ref: '#/components/schemas/String' + last_name: + $ref: '#/components/schemas/String' + id: + $ref: '#/components/schemas/uuid' +- description: Try to remove the endpoint + url: /v1/query + status: 200 + response: + message: success + query: + type: drop_rest_endpoint + args: + name: complex_args diff --git a/server/tests-py/queries/openapi/openapi_get_endpoint_test_simple.yaml b/server/tests-py/queries/openapi/openapi_get_endpoint_test_simple.yaml index 095ed770e69..86950289e9d 100644 --- a/server/tests-py/queries/openapi/openapi_get_endpoint_test_simple.yaml +++ b/server/tests-py/queries/openapi/openapi_get_endpoint_test_simple.yaml @@ -9,7 +9,7 @@ url: simple name: simple methods: - - GET + - GET definition: query: collection_name: test_collection @@ -26,28 +26,40 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: /api/rest/simple: get: summary: simple - description: |- - *** - The GraphQl query for this endpoint is: - ``` graphql - query { test_table { first_name last_name } } - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query { test_table { first_name 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. + - 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 GET /api/rest/simple components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/openapi_multiple_endpoints_same_path.yaml b/server/tests-py/queries/openapi/openapi_multiple_endpoints_same_path.yaml index 99e8e60bba3..1c5d5a4f478 100644 --- a/server/tests-py/queries/openapi/openapi_multiple_endpoints_same_path.yaml +++ b/server/tests-py/queries/openapi/openapi_multiple_endpoints_same_path.yaml @@ -9,7 +9,7 @@ url: my_endpoint_url name: with_default_arg methods: - - GET + - GET definition: query: collection_name: test_collection @@ -26,7 +26,7 @@ url: my_endpoint_url name: mutation_with_args methods: - - POST + - POST definition: query: collection_name: test_collection @@ -42,69 +42,120 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: /api/rest/my_endpoint_url: get: summary: with_default_arg - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - query ($first_name:String="Foo") { test_table(where: {first_name: { _eq: - $first_name } }) { first_name last_name } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query ($first_name:String=\"Foo\") { test_table(where: {first_name: {\ + \ _eq: $first_name } }) { first_name 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. - - schema: - default: Foo - type: string - in: query - name: first_name + - 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. + - schema: + default: Foo + type: string + in: query + name: first_name + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + default: Foo + type: string + nullable: true + description: Query parameters can also be provided in the request body + as a JSON object + 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 GET /api/rest/my_endpoint_url post: summary: mutation_with_args - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/my_endpoint_url components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/openapi_multiple_endpoints_test.yaml b/server/tests-py/queries/openapi/openapi_multiple_endpoints_test.yaml index 3ede65d32f4..2d0d9315741 100644 --- a/server/tests-py/queries/openapi/openapi_multiple_endpoints_test.yaml +++ b/server/tests-py/queries/openapi/openapi_multiple_endpoints_test.yaml @@ -9,7 +9,7 @@ url: with_args_url/:first_name/:last_name name: with_args_url methods: - - POST + - POST definition: query: collection_name: test_collection @@ -26,7 +26,7 @@ url: with_default_arg name: with_default_arg methods: - - POST + - POST definition: query: collection_name: test_collection @@ -43,7 +43,7 @@ url: mutation_with_args name: mutation_with_args methods: - - POST + - POST definition: query: collection_name: test_collection @@ -59,102 +59,179 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: /api/rest/mutation_with_args: post: summary: mutation_with_args - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - mutation ($first_name: String!, $last_name: String!) { - insert_test_table( objects: {first_name: $first_name, last_name: - $last_name }) { returning { id } affected_rows } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation ($first_name: String!, $last_name: String!) { insert_test_table(\ + \ objects: {first_name: $first_name, last_name: $last_name }) { returning\ + \ { id } affected_rows } }\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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table: + type: object + properties: + returning: + items: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + type: array + nullable: false + affected_rows: + title: Int + type: integer + description: Responses for POST /api/rest/mutation_with_args /api/rest/with_default_arg: post: summary: with_default_arg - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - query ($first_name:String="Foo") { test_table(where: {first_name: { _eq: - $first_name } }) { first_name last_name } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query ($first_name:String=\"Foo\") { test_table(where: {first_name: {\ + \ _eq: $first_name } }) { first_name 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. - - schema: - default: Foo - type: string - in: query - name: first_name - '/api/rest/with_args_url/{first_name}/{last_name}': + - 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. + - schema: + default: Foo + type: string + in: query + name: first_name + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + default: Foo + type: string + nullable: true + description: Query parameters can also be provided in the request body + as a JSON object + 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_default_arg + /api/rest/with_args_url/{first_name}/{last_name}: post: summary: with_args_url - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - query ($first_name: String!, $last_name:String!) { test_table(where: - {first_name: { _eq: $first_name } last_name: { _eq: $last_name }}) { - first_name last_name } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query ($first_name: String!, $last_name:String!) { test_table(where: {first_name:\ + \ { _eq: $first_name } last_name: { _eq: $last_name }}) { first_name 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. - - schema: - type: string - in: path - name: first_name - - schema: - type: string - in: path - name: last_name + - 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. + - schema: + type: string + in: path + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: path + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + 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_args_url/{first_name}/{last_name} components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/openapi_post_endpoint_test_recursive_arg.yaml b/server/tests-py/queries/openapi/openapi_post_endpoint_test_recursive_arg.yaml new file mode 100644 index 00000000000..7f246855b89 --- /dev/null +++ b/server/tests-py/queries/openapi/openapi_post_endpoint_test_recursive_arg.yaml @@ -0,0 +1,104 @@ +- description: Try to add a POST rest endpoint with arguments + url: /v1/query + status: 200 + response: + message: success + query: + type: create_rest_endpoint + args: + url: recurse_arg + name: recurse_arg + methods: + - POST + definition: + query: + collection_name: test_collection + query_name: mutation_recursive_arg + + +- 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/recurse_arg: + post: + summary: recurse_arg + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + mutation MyMutation($object: test_table_recurse_insert_input!) { insert_test_table_recurse_one(object:\ + \ $object) { id } }\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. + requestBody: + required: true + content: + application/json: + schema: + type: object + properties: + object: + $ref: '#/components/schemas/test_table_recurse_insert_input' + description: Query parameters can also be provided in the request body as + a JSON object + responses: + '200': + content: + application/json: + schema: + properties: + insert_test_table_recurse_one: + type: object + properties: + id: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + title: uuid + type: string + description: Responses for POST /api/rest/recurse_arg + components: + schemas: + test_table_recurse_insert_input: + type: object + description: input type for inserting data into table "test_table_recurse" + nullable: false + properties: + random_data: + $ref: '#/components/schemas/String' + id: + $ref: '#/components/schemas/uuid' + recurse_rel: + $ref: '#/components/schemas/test_table_recurse_obj_rel_insert_input' + uuid: + pattern: '[a-f0-9]{8}-[a-f0-9]{4}-4[a-f0-9]{3}-[89aAbB][a-f0-9]{3}-[a-f0-9]{12}' + type: string + nullable: true + String: + type: string + nullable: true + test_table_recurse_obj_rel_insert_input: + type: object + description: input type for inserting object relation for remote table "test_table_recurse" + nullable: true + properties: + data: + $ref: '#/components/schemas/test_table_recurse_insert_input' +- description: Try to remove the endpoint + url: /v1/query + status: 200 + response: + message: success + query: + type: drop_rest_endpoint + args: + name: recurse_arg diff --git a/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args.yaml b/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args.yaml index cbe7316b8a0..89973ea6b55 100644 --- a/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args.yaml +++ b/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args.yaml @@ -9,7 +9,7 @@ url: with_args name: with_args methods: - - POST + - POST definition: query: collection_name: test_collection @@ -26,42 +26,67 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: /api/rest/with_args: post: summary: with_args - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - query ($first_name: String!, $last_name:String!) { test_table(where: - {first_name: { _eq: $first_name } last_name: { _eq: $last_name }}) { - first_name last_name } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query ($first_name: String!, $last_name:String!) { test_table(where: {first_name:\ + \ { _eq: $first_name } last_name: { _eq: $last_name }}) { first_name 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. - - schema: - type: string - in: query - name: first_name - - schema: - type: string - in: query - name: last_name + - 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. + - schema: + type: string + in: query + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: query + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + 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_args components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args_url.yaml b/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args_url.yaml index 9f10a18d1b5..30e26692a35 100644 --- a/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args_url.yaml +++ b/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_args_url.yaml @@ -9,7 +9,7 @@ url: with_args_url/:first_name/:last_name name: with_args_url methods: - - POST + - POST definition: query: collection_name: test_collection @@ -26,42 +26,67 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: - '/api/rest/with_args_url/{first_name}/{last_name}': + /api/rest/with_args_url/{first_name}/{last_name}: post: summary: with_args_url - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - query ($first_name: String!, $last_name:String!) { test_table(where: - {first_name: { _eq: $first_name } last_name: { _eq: $last_name }}) { - first_name last_name } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query ($first_name: String!, $last_name:String!) { test_table(where: {first_name:\ + \ { _eq: $first_name } last_name: { _eq: $last_name }}) { first_name 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. - - schema: - type: string - in: path - name: first_name - - schema: - type: string - in: path - name: last_name + - 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. + - schema: + type: string + in: path + name: first_name + description: _"first_name" is required (enter it either in parameters or request body)_ + - schema: + type: string + in: path + name: last_name + description: _"last_name" is required (enter it either in parameters or request body)_ + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + type: string + nullable: false + last_name: + type: string + nullable: false + description: Query parameters can also be provided in the request body + as a JSON object + 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_args_url/{first_name}/{last_name} components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_default_arg.yaml b/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_default_arg.yaml index 6a3a58f3391..d9a9d1a0769 100644 --- a/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_default_arg.yaml +++ b/server/tests-py/queries/openapi/openapi_post_endpoint_test_with_default_arg.yaml @@ -9,7 +9,7 @@ url: with_default_arg name: with_default_arg methods: - - POST + - POST definition: query: collection_name: test_collection @@ -26,38 +26,59 @@ info: version: '' title: Rest Endpoints - description: These OpenAPI specifications are automatically generated by Hasura. + description: This OpenAPI specification is automatically generated by Hasura. paths: /api/rest/with_default_arg: post: summary: with_default_arg - description: >- - *** - - The GraphQl query for this endpoint is: - - ``` graphql - - query ($first_name:String="Foo") { test_table(where: {first_name: { _eq: - $first_name } }) { first_name last_name } } - - ``` - responses: {} + description: "***\nThe GraphQl query for this endpoint is:\n``` graphql\n\ + query ($first_name:String=\"Foo\") { test_table(where: {first_name: {\ + \ _eq: $first_name } }) { first_name 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. - - schema: - default: Foo - type: string - in: query - name: first_name + - 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. + - schema: + default: Foo + type: string + in: query + name: first_name + requestBody: + required: false + content: + application/json: + schema: + type: object + properties: + first_name: + default: Foo + type: string + nullable: true + description: Query parameters can also be provided in the request body + as a JSON object + 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_default_arg components: {} - - description: Try to remove the endpoint url: /v1/query status: 200 diff --git a/server/tests-py/queries/openapi/setup.yaml b/server/tests-py/queries/openapi/setup.yaml index ab86d9bed5b..19461a26732 100644 --- a/server/tests-py/queries/openapi/setup.yaml +++ b/server/tests-py/queries/openapi/setup.yaml @@ -23,6 +23,29 @@ args: ('Baz', 'Qux'), ('X%20Y', 'Test'); +- type: run_sql + args: + sql: | + create table test_table_recurse( + random_data text, + id UUID NOT NULL DEFAULT gen_random_uuid() + ); + +- type: track_table + args: + schema: public + name: test_table_recurse + +- type: create_object_relationship + args: + table: test_table_recurse + name: recurse_rel + using: + manual_configuration: + remote_table: test_table_recurse + column_mapping: + id : id + - type: create_query_collection args: name: test_collection @@ -40,3 +63,9 @@ args: query: "query ($first_name:String=\"Foo\") { test_table(where: {first_name: { _eq: $first_name } }) { first_name last_name } }" - name: mutation_with_args query: "mutation ($first_name: String!, $last_name: String!) { insert_test_table( objects: {first_name: $first_name, last_name: $last_name }) { returning { id } affected_rows } }" + - name: mutation_complex_arg + query: "mutation ($objects: [test_table_insert_input!]!) { insert_test_table( objects: $objects) { returning { id } } }" + - 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 } }" \ No newline at end of file diff --git a/server/tests-py/queries/openapi/teardown.yaml b/server/tests-py/queries/openapi/teardown.yaml index 85bb52b8761..338b3a948aa 100644 --- a/server/tests-py/queries/openapi/teardown.yaml +++ b/server/tests-py/queries/openapi/teardown.yaml @@ -7,4 +7,4 @@ args: - type: run_sql args: sql: | - drop table test_table + drop table test_table, test_table_recurse; diff --git a/server/tests-py/test_openapi.py b/server/tests-py/test_openapi.py index f4472dbc3f6..7c1c042348c 100644 --- a/server/tests-py/test_openapi.py +++ b/server/tests-py/test_openapi.py @@ -35,3 +35,11 @@ class TestOpenAPISpec: def test_multiple_endpoints_same_path(self, hge_ctx, transport): check_query_f(hge_ctx, self.dir() + '/openapi_multiple_endpoints_same_path.yaml', transport) + def test_endpoint_with_complex_arg(self, hge_ctx, transport): + check_query_f(hge_ctx, self.dir() + '/openapi_get_endpoint_test_complex_arg.yaml', transport) + + def test_endpoint_with_complex_args(self, hge_ctx, transport): + check_query_f(hge_ctx, self.dir() + '/openapi_get_endpoint_test_complex_args.yaml', transport) + + 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)