2021-05-13 16:17:40 +03:00
|
|
|
{-# LANGUAGE CPP #-}
|
2022-09-21 21:01:48 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2021-05-13 16:17:40 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
|
|
|
|
-- | This module defines all missing instances of third party libraries.
|
2021-11-04 19:08:33 +03:00
|
|
|
module Hasura.Base.Instances () where
|
2021-05-13 16:17:40 +03:00
|
|
|
|
2022-12-15 23:37:00 +03:00
|
|
|
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
|
2021-05-13 16:17:40 +03:00
|
|
|
import Data.Aeson qualified as J
|
2022-09-21 21:01:48 +03:00
|
|
|
import Data.Fixed (Fixed (..))
|
2022-02-18 08:31:12 +03:00
|
|
|
import Data.Functor.Product (Product (Pair))
|
2022-10-06 12:07:14 +03:00
|
|
|
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
|
2022-02-18 08:31:12 +03:00
|
|
|
import Data.Text qualified as T
|
2022-09-21 21:01:48 +03:00
|
|
|
import Data.Time (NominalDiffTime)
|
2021-05-13 16:17:40 +03:00
|
|
|
import Data.URL.Template qualified as UT
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
import Database.PG.Query qualified as PG
|
2021-05-13 16:17:40 +03:00
|
|
|
import Hasura.Prelude
|
2023-01-25 10:12:53 +03:00
|
|
|
import Kriti qualified
|
|
|
|
import Kriti.Parser qualified as Kriti
|
2022-09-21 21:01:48 +03:00
|
|
|
import Language.Haskell.TH.Lift qualified as TH (deriveLift)
|
2021-05-13 16:17:40 +03:00
|
|
|
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
|
2021-07-30 18:42:36 +03:00
|
|
|
|
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 #-}
|
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Deepseq
|
|
|
|
|
|
|
|
instance NFData UT.Variable
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData UT.TemplateItem
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData UT.URLTemplate
|
|
|
|
|
|
|
|
instance NFData C.StepField
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.RangeField
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.SpecificField
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.BaseField
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.CronField
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.MonthSpec
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.DayOfMonthSpec
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.DayOfWeekSpec
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.HourSpec
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
instance NFData C.MinuteSpec
|
|
|
|
|
|
|
|
instance NFData C.CronSchedule
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Template Haskell
|
|
|
|
|
|
|
|
deriving instance TH.Lift TDFA.CompOption
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
deriving instance TH.Lift TDFA.DoPa
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
deriving instance TH.Lift TDFA.ExecOption
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
deriving instance TH.Lift TDFA.Pattern
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
deriving instance TH.Lift TDFA.PatternSet
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2022-09-21 21:01:48 +03:00
|
|
|
deriving instance TH.Lift (Fixed a)
|
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
deriving instance TH.Lift TDFA.PatternSetCharacterClass
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
deriving instance TH.Lift TDFA.PatternSetCollatingElement
|
|
|
|
|
|
|
|
deriving instance TH.Lift TDFA.PatternSetEquivalenceClass
|
|
|
|
|
2022-09-21 21:01:48 +03:00
|
|
|
$(TH.deriveLift ''DiffTime)
|
|
|
|
|
|
|
|
$(TH.deriveLift ''NominalDiffTime)
|
|
|
|
|
|
|
|
deriving instance TH.Lift Milliseconds
|
|
|
|
|
|
|
|
deriving instance TH.Lift Seconds
|
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- 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
|
|
|
|
|
2022-12-15 23:37:00 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- HasCodec
|
|
|
|
|
|
|
|
instance AC.HasCodec C.CronSchedule where
|
|
|
|
codec =
|
|
|
|
AC.named "CronSchedule" $
|
|
|
|
AC.bimapCodec C.parseCronSchedule C.serializeCronSchedule $
|
|
|
|
AC.codec @Text
|
|
|
|
|
2021-05-13 16:17:40 +03:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- 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
|
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
instance PG.ToPrepArg C.CronSchedule where
|
|
|
|
toPrepVal = PG.toPrepVal . C.serializeCronSchedule
|
2021-05-13 16:17:40 +03:00
|
|
|
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
instance PG.FromCol C.CronSchedule where
|
2021-05-13 16:17:40 +03:00
|
|
|
fromCol bs =
|
Import `pg-client-hs` as `PG`
Result of executing the following commands:
```shell
# replace "as Q" imports with "as PG" (in retrospect this didn't need a regex)
git grep -lE 'as Q($|[^a-zA-Z])' -- '*.hs' | xargs sed -i -E 's/as Q($|[^a-zA-Z])/as PG\1/'
# replace " Q." with " PG."
git grep -lE ' Q\.' -- '*.hs' | xargs sed -i 's/ Q\./ PG./g'
# replace "(Q." with "(PG."
git grep -lE '\(Q\.' -- '*.hs' | xargs sed -i 's/(Q\./(PG./g'
# ditto, but for [, |, { and !
git grep -lE '\[Q\.' -- '*.hs' | xargs sed -i 's/\[Q\./\[PG./g'
git grep -l '|Q\.' -- '*.hs' | xargs sed -i 's/|Q\./|PG./g'
git grep -l '{Q\.' -- '*.hs' | xargs sed -i 's/{Q\./{PG./g'
git grep -l '!Q\.' -- '*.hs' | xargs sed -i 's/!Q\./!PG./g'
```
(Doing the `grep -l` before the `sed`, instead of `sed` on the entire codebase, reduces the number of `mtime` updates, and so reduces how many times a file gets recompiled while checking intermediate results.)
Finally, I manually removed a broken and unused `Arbitrary` instance in `Hasura.RQL.Network`. (It used an `import Test.QuickCheck.Arbitrary as Q` statement, which was erroneously caught by the first find-replace command.)
After this PR, `Q` is no longer used as an import qualifier. That was not the goal of this PR, but perhaps it's a useful fact for future efforts.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5933
GitOrigin-RevId: 8c84c59d57789111d40f5d3322c5a885dcfbf40e
2022-09-20 22:54:43 +03:00
|
|
|
case PG.fromCol bs of
|
2021-05-13 16:17:40 +03:00
|
|
|
Left err -> Left err
|
|
|
|
Right dbCron ->
|
|
|
|
case C.parseCronSchedule dbCron of
|
2022-02-18 08:31:12 +03:00
|
|
|
Left err' -> Left $ "invalid cron schedule " <> T.pack err'
|
2021-05-13 16:17:40 +03:00
|
|
|
Right cron -> Right cron
|
2023-01-25 10:12:53 +03:00
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
-- Kriti
|
|
|
|
|
|
|
|
instance NFData Kriti.AlexSourcePos
|
|
|
|
|
|
|
|
instance NFData Kriti.Span
|
|
|
|
|
|
|
|
instance NFData Kriti.Elif
|
|
|
|
|
|
|
|
instance NFData Kriti.ValueExt
|