graphql-engine/server/src-lib/Hasura/Base/Instances.hs

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

154 lines
4.0 KiB
Haskell
Raw Normal View History

{-# 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 Autodocodec qualified as AC
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 15:55:56 +03:00
import Control.Monad.Fix
import Data.Aeson qualified as J
import Data.Fixed (Fixed (..))
Updates cabal freeze file #### TODO - [x] fix `hashable >= 1.3.1` serialization ordering issue [^1] - `test_graphql_mutations.py::TestGraphQLMutateEnums` was failing - [x] fix `unordered-containers` serialization ordering issue [^2] - `test_graphql_queries.py` was failing on Citus - [ ] verify that no new failures have been introduced - [ ] open issues to fix the above - identify test cases that "leak" implementation details by depending on `hashable` instance ordering - bump `hashable >= 1.3.1` and update test cases with new ordering OR modify them so that ordering is stable - bump `unordered-containers >= 0.2.15.0` and update test cases with new ordering OR modify them so that ordering is stable - one of the test cases was failing on string equality comparison for a generated Citus query - we probably don't want to _actually_ do this unless there are _very specific_ guarantees we want to make about generated query structure --- Just what it says on the tin. https://github.com/hasura/graphql-engine-mono/pull/3538 updated the freeze file a few weeks ago, but it looks like the index state hadn't been updated since December so a lot of stuff that had newer versions didn't get updated. --- EDIT: I should add, the motivation for doing this in the first place is that `hspec > 2.8.4` now supports specifying filtering spec trees based on patterns provided by the `HSPEC_MATCH` environment variable. For example, one could have a script that executes the following: ``` HSPEC_MATCH="PostgreSQL" \ ghcid \ --command \ 'cabal repl graphql-engine:test:tests-hspec \ --repl-option -O0 \ --repl-option -fobject-code' \ --test "main" ``` ...which will loop on typechecking the `tests-hspec` component, and then as soon as it passes (i.e. no warnings or errors) will run _only_ the `PostgreSQL` sub-components. [^1]: `hashable >= 1.3.1.0` [updated its default salts](https://github.com/haskell-unordered-containers/hashable/pull/196), which [broke serialization ordering](https://github.com/haskell/aeson/issues/837) [^2]: `unordered-containers >= 0.2.16.0` [introduced changes to some of its internal functions](https://hackage.haskell.org/package/unordered-containers-0.2.16.0/changelog) which seem like they could have affected serialization stability PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3672 GitOrigin-RevId: bbd1d48c73db4021913f0b5345b7315a8d6525d3
2022-02-18 08:31:12 +03:00
import Data.Functor.Product (Product (Pair))
import "dependent-sum" Data.GADT.Compare (GCompare (gcompare), GOrdering (GEQ, GGT, GLT))
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 15:55:56 +03:00
import Data.OpenApi.Declare as D
Updates cabal freeze file #### TODO - [x] fix `hashable >= 1.3.1` serialization ordering issue [^1] - `test_graphql_mutations.py::TestGraphQLMutateEnums` was failing - [x] fix `unordered-containers` serialization ordering issue [^2] - `test_graphql_queries.py` was failing on Citus - [ ] verify that no new failures have been introduced - [ ] open issues to fix the above - identify test cases that "leak" implementation details by depending on `hashable` instance ordering - bump `hashable >= 1.3.1` and update test cases with new ordering OR modify them so that ordering is stable - bump `unordered-containers >= 0.2.15.0` and update test cases with new ordering OR modify them so that ordering is stable - one of the test cases was failing on string equality comparison for a generated Citus query - we probably don't want to _actually_ do this unless there are _very specific_ guarantees we want to make about generated query structure --- Just what it says on the tin. https://github.com/hasura/graphql-engine-mono/pull/3538 updated the freeze file a few weeks ago, but it looks like the index state hadn't been updated since December so a lot of stuff that had newer versions didn't get updated. --- EDIT: I should add, the motivation for doing this in the first place is that `hspec > 2.8.4` now supports specifying filtering spec trees based on patterns provided by the `HSPEC_MATCH` environment variable. For example, one could have a script that executes the following: ``` HSPEC_MATCH="PostgreSQL" \ ghcid \ --command \ 'cabal repl graphql-engine:test:tests-hspec \ --repl-option -O0 \ --repl-option -fobject-code' \ --test "main" ``` ...which will loop on typechecking the `tests-hspec` component, and then as soon as it passes (i.e. no warnings or errors) will run _only_ the `PostgreSQL` sub-components. [^1]: `hashable >= 1.3.1.0` [updated its default salts](https://github.com/haskell-unordered-containers/hashable/pull/196), which [broke serialization ordering](https://github.com/haskell/aeson/issues/837) [^2]: `unordered-containers >= 0.2.16.0` [introduced changes to some of its internal functions](https://hackage.haskell.org/package/unordered-containers-0.2.16.0/changelog) which seem like they could have affected serialization stability PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3672 GitOrigin-RevId: bbd1d48c73db4021913f0b5345b7315a8d6525d3
2022-02-18 08:31:12 +03:00
import Data.Text qualified as T
import Data.Time (NominalDiffTime)
import Data.URL.Template qualified as UT
import Database.PG.Query qualified as PG
import Hasura.Prelude
import Kriti qualified
import Kriti.Parser qualified as Kriti
import Language.Haskell.TH.Lift qualified as TH (deriveLift)
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
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 15:55:56 +03:00
--------------------------------------------------------------------------------
-- 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
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 (Fixed a)
deriving instance TH.Lift TDFA.PatternSetCharacterClass
deriving instance TH.Lift TDFA.PatternSetCollatingElement
deriving instance TH.Lift TDFA.PatternSetEquivalenceClass
$(TH.deriveLift ''DiffTime)
$(TH.deriveLift ''NominalDiffTime)
deriving instance TH.Lift Milliseconds
deriving instance TH.Lift Seconds
--------------------------------------------------------------------------------
-- 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
--------------------------------------------------------------------------------
-- HasCodec
instance AC.HasCodec C.CronSchedule where
codec =
AC.named "CronSchedule" $
AC.bimapCodec C.parseCronSchedule C.serializeCronSchedule $
AC.codec @Text
--------------------------------------------------------------------------------
-- 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 PG.ToPrepArg C.CronSchedule where
toPrepVal = PG.toPrepVal . C.serializeCronSchedule
instance PG.FromCol C.CronSchedule where
fromCol bs =
case PG.fromCol bs of
Left err -> Left err
Right dbCron ->
case C.parseCronSchedule dbCron of
Updates cabal freeze file #### TODO - [x] fix `hashable >= 1.3.1` serialization ordering issue [^1] - `test_graphql_mutations.py::TestGraphQLMutateEnums` was failing - [x] fix `unordered-containers` serialization ordering issue [^2] - `test_graphql_queries.py` was failing on Citus - [ ] verify that no new failures have been introduced - [ ] open issues to fix the above - identify test cases that "leak" implementation details by depending on `hashable` instance ordering - bump `hashable >= 1.3.1` and update test cases with new ordering OR modify them so that ordering is stable - bump `unordered-containers >= 0.2.15.0` and update test cases with new ordering OR modify them so that ordering is stable - one of the test cases was failing on string equality comparison for a generated Citus query - we probably don't want to _actually_ do this unless there are _very specific_ guarantees we want to make about generated query structure --- Just what it says on the tin. https://github.com/hasura/graphql-engine-mono/pull/3538 updated the freeze file a few weeks ago, but it looks like the index state hadn't been updated since December so a lot of stuff that had newer versions didn't get updated. --- EDIT: I should add, the motivation for doing this in the first place is that `hspec > 2.8.4` now supports specifying filtering spec trees based on patterns provided by the `HSPEC_MATCH` environment variable. For example, one could have a script that executes the following: ``` HSPEC_MATCH="PostgreSQL" \ ghcid \ --command \ 'cabal repl graphql-engine:test:tests-hspec \ --repl-option -O0 \ --repl-option -fobject-code' \ --test "main" ``` ...which will loop on typechecking the `tests-hspec` component, and then as soon as it passes (i.e. no warnings or errors) will run _only_ the `PostgreSQL` sub-components. [^1]: `hashable >= 1.3.1.0` [updated its default salts](https://github.com/haskell-unordered-containers/hashable/pull/196), which [broke serialization ordering](https://github.com/haskell/aeson/issues/837) [^2]: `unordered-containers >= 0.2.16.0` [introduced changes to some of its internal functions](https://hackage.haskell.org/package/unordered-containers-0.2.16.0/changelog) which seem like they could have affected serialization stability PR-URL: https://github.com/hasura/graphql-engine-mono/pull/3672 GitOrigin-RevId: bbd1d48c73db4021913f0b5345b7315a8d6525d3
2022-02-18 08:31:12 +03:00
Left err' -> Left $ "invalid cron schedule " <> T.pack err'
Right cron -> Right cron
--------------------------------------------------------------------------------
-- Kriti
instance NFData Kriti.AlexSourcePos
instance NFData Kriti.Span
instance NFData Kriti.Elif
instance NFData Kriti.ValueExt