graphql-engine/server/src-lib/Hasura/Base/Instances.hs
Antoine Leblanc 3a400fab3d Rewrite OpenAPI
### Description

This PR rewrites OpenAPI to be more idiomatic. Some noteworthy changes:
- we accumulate all required information during the Analyze phase, to avoid having to do a single lookup in the schema cache during the OpenAPI generation phase (we now only need the schema cache as input to run the analysis)
- we no longer build intermediary endpoint information and aggregate it, we directly build the the `PathItem` for each endpoint; additionally, that means we no longer have to assume that different methods have the same metadata
- we no longer have to first declare types, then craft references: we do everything in one step
- we now properly deal with nullability by treating "typeName" and "typeName!" as different
- we add a bunch of additional fields in the generated "schema", such as title
- we do now support enum values in both input and output positions
- checking whether the request body is required is now performed on the fly rather than by introspecting the generated schema
- the methods in the file are sorted by topic

### Controversial point

However, this PR creates some additional complexity, that we might not want to keep. The main complexity is _knot-tying_: to avoid lookups when generating the OpenAPI, it builds an actual graph of input types, which means that we need something similar to (but simpler than) `MonadSchema`, to avoid infinite recursions when analyzing the input types of a query. To do this, this PR introduces `CircularT`, a lesser `SchemaT` that aims at avoiding ever having to reinvent this particular wheel ever again.

### Remaining work

- [x] fix existing tests (they are all failing due to some of the schema changes)
- [ ] add tests to cover the new features:
  - [x] tests for `CircularT`
  - [ ] tests for enums in output schemas
- [x] extract / document `CircularT` if we wish to keep it
- [x] add more comments to `OpenAPI`
- [x] have a second look at `buildVariableSchema`
- [x] fix all missing diagnostics in `Analyze`
- [x] add a Changelog entry?

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/4654
Co-authored-by: David Overton <7734777+dmoverton@users.noreply.github.com>
GitOrigin-RevId: f4a9191f22dfcc1dccefd6a52f5c586b6ad17172
2022-06-30 12:57:09 +00:00

128 lines
3.5 KiB
Haskell

{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- | This module defines all missing instances of third party libraries.
module Hasura.Base.Instances () where
import Control.Monad.Fix
import Data.Aeson qualified as J
import Data.Functor.Product (Product (Pair))
import Data.GADT.Compare (GCompare (gcompare), GOrdering (GEQ, GGT, GLT))
import Data.HashMap.Strict qualified as M
import Data.HashSet qualified as S
import Data.OpenApi.Declare as D
import Data.Text qualified as T
import Data.URL.Template qualified as UT
import Database.PG.Query qualified as Q
import Hasura.Prelude
import Language.Haskell.TH.Syntax qualified as TH
import System.Cron.Parser qualified as C
import System.Cron.Types qualified as C
import Text.Regex.TDFA qualified as TDFA
import Text.Regex.TDFA.Pattern qualified as TDFA
--------------------------------------------------------------------------------
-- MonadFix
instance (Monoid d, MonadFix m) => MonadFix (DeclareT d m) where
mfix f = DeclareT $ \s -> mfix $ \ ~(_, a) -> runDeclareT (f a) s
{-# INLINE mfix #-}
--------------------------------------------------------------------------------
-- Deepseq
instance NFData UT.Variable
instance NFData UT.TemplateItem
instance NFData UT.URLTemplate
instance NFData C.StepField
instance NFData C.RangeField
instance NFData C.SpecificField
instance NFData C.BaseField
instance NFData C.CronField
instance NFData C.MonthSpec
instance NFData C.DayOfMonthSpec
instance NFData C.DayOfWeekSpec
instance NFData C.HourSpec
instance NFData C.MinuteSpec
instance NFData C.CronSchedule
--------------------------------------------------------------------------------
-- Template Haskell
instance (TH.Lift k, TH.Lift v) => TH.Lift (M.HashMap k v) where
lift m = [|M.fromList $(TH.lift $ M.toList m)|]
liftTyped = TH.unsafeTExpCoerce . TH.lift
instance TH.Lift a => TH.Lift (S.HashSet a) where
lift s = [|S.fromList $(TH.lift $ S.toList s)|]
liftTyped = TH.unsafeTExpCoerce . TH.lift
deriving instance TH.Lift TDFA.CompOption
deriving instance TH.Lift TDFA.DoPa
deriving instance TH.Lift TDFA.ExecOption
deriving instance TH.Lift TDFA.Pattern
deriving instance TH.Lift TDFA.PatternSet
deriving instance TH.Lift TDFA.PatternSetCharacterClass
deriving instance TH.Lift TDFA.PatternSetCollatingElement
deriving instance TH.Lift TDFA.PatternSetEquivalenceClass
--------------------------------------------------------------------------------
-- GADT
instance (GCompare f, GCompare g) => GCompare (Product f g) where
Pair a1 a2 `gcompare` Pair b1 b2 = case gcompare a1 b1 of
GLT -> GLT
GEQ -> case gcompare a2 b2 of
GLT -> GLT
GEQ -> GEQ
GGT -> GGT
GGT -> GGT
--------------------------------------------------------------------------------
-- JSON
instance J.FromJSON C.CronSchedule where
parseJSON = J.withText "CronSchedule" $ \t ->
onLeft (C.parseCronSchedule t) fail
instance J.ToJSON C.CronSchedule where
toJSON = J.String . C.serializeCronSchedule
instance J.ToJSONKey Void
--------------------------------------------------------------------------------
-- Postgres
instance Q.ToPrepArg C.CronSchedule where
toPrepVal = Q.toPrepVal . C.serializeCronSchedule
instance Q.FromCol C.CronSchedule where
fromCol bs =
case Q.fromCol bs of
Left err -> Left err
Right dbCron ->
case C.parseCronSchedule dbCron of
Left err' -> Left $ "invalid cron schedule " <> T.pack err'
Right cron -> Right cron