Projects STRLCPY graphql-engine Commits 354145f2
🤬
  • server: switch to ghc 9.2 (2nd try)

    You will need the fork of 9.2.4 that we're using (for now):
    
    ```
    ghcup -c -n install ghc --force -u "https://storage.googleapis.com/graphql-engine-cdn.hasura.io/ghc-bindists/ghc-x86_64-deb10-linux-9.2.4-hasura-fix.tar.xz" 9.2.4
    ```
    
    or for m1 mac:
    
    ```
    ghcup -c -n install ghc --force -u  "https://storage.googleapis.com/graphql-engine-cdn.hasura.io/ghc-bindists/ghc-arm64-apple-darwin-9.2.4-hasura-fix.tar.xz"
    ```
    
    Samir is working on a nix build for nix folx
    
    PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6154
    GitOrigin-RevId: c11a2598a7c75e2c315e36f3d6f0b488febfccd4
  • Loading...
  • Brandon Simmons committed with hasura-bot 2 months ago
    354145f2
    1 parent a9202c42
Revision indexing in progress... (symbol navigation in revisions will be accurate after indexed)
  • ■ ■ ■ ■ ■
    cabal.project
    skipped 14 lines
    15 15  --
    16 16  -- See: https://www.haskell.org/cabal/users-guide/nix-local-build.html#configuring-builds-with-cabal-project
    17 17   
    18  -with-compiler: ghc-8.10.7
     18 +with-compiler: ghc-9.2.4
    19 19   
    20 20  -- package-level parallelism:
    21 21  jobs: $ncpus
    skipped 63 lines
    85 85   location: https://github.com/hasura/ekg-core.git
    86 86   tag: b0cdc337ca2a52e392d427916ba3e28246b396c0
    87 87   
     88 +-- TODO relax these constraints in the package
     89 +allow-newer: ekg-prometheus:bytestring
     90 +allow-newer: ekg-prometheus:inspection-testing
    88 91  source-repository-package
    89 92   type: git
    90 93   location: https://github.com/hasura/ekg-prometheus.git
    skipped 12 lines
    103 106   type: git
    104 107   location: https://github.com/hasura/text.git
    105 108   tag: ba0fd2bf256c996a6c85dbdc8590a6fcde41b8f8
    106  - 
    107  --------- GHC 9.2 SPOCK-RELATED FORKS
    108  --- NOTE: jberryman is a Spock maintainer now
    109  --- see discussion: https://hasurahq.slack.com/archives/C03263T1L9W/p1649087218167979
    110  - 
    111  --- This is an unreleased version of "Spock-core"
    112  -source-repository-package
    113  - type: git
    114  - location: https://github.com/agrafix/Spock.git
    115  - tag: efc06e4b4e91f63579d04eb15ec850cf7a5ebccf
    116  - subdir: Spock-core
    117  - 
    118  --- This is an unreleased version of "reroute-core", needed for "Spock-core"
    119  -source-repository-package
    120  - type: git
    121  - location: https://github.com/agrafix/Spock.git
    122  - tag: efc06e4b4e91f63579d04eb15ec850cf7a5ebccf
    123  - subdir: reroute
    124 109   
    125 110   
  • ■ ■ ■ ■ ■ ■
    cabal.project.freeze
    1 1  active-repositories: hackage.haskell.org:merge
    2  -constraints: any.Cabal ==3.2.1.0,
     2 +constraints: any.Cabal ==3.6.3.0,
    3 3   any.Diff ==0.4.1,
    4 4   any.HTTP ==4000.3.16,
    5 5   any.HUnit ==1.6.2.0,
    skipped 29 lines
    35 35   any.autodocodec ==0.2.0.0,
    36 36   any.autodocodec-openapi3 ==0.2.1.1,
    37 37   any.barbies ==2.0.3.1,
    38  - any.base ==4.14.3.0,
    39  - any.base-compat ==0.11.2,
    40  - any.base-compat-batteries ==0.11.2,
     38 + any.base ==4.16.3.0,
     39 + any.base-compat ==0.12.1,
     40 + any.base-compat-batteries ==0.12.1,
    41 41   any.base-orphans ==0.8.6,
    42 42   any.base16-bytestring ==1.0.2.0,
    43 43   any.base64-bytestring ==1.2.1.0,
    44 44   any.basement ==0.0.14,
    45 45   any.bifunctors ==5.5.11,
    46  - any.binary ==0.8.8.0,
     46 + any.binary ==0.8.9.0,
    47 47   any.binary-parser ==0.5.7.1,
    48 48   any.blaze-builder ==0.4.2.2,
    49 49   any.blaze-html ==0.9.1.2,
    50 50   any.blaze-markup ==0.8.2.8,
    51  - any.blaze-textual ==0.2.2.1,
    52 51   any.boring ==0.2,
    53 52   any.bsb-http-chunked ==0.0.0.4,
    54 53   any.byteorder ==1.0.4,
    55  - any.bytestring ==0.10.12.0,
     54 + any.bytestring ==0.11.3.1,
    56 55   any.bytestring-builder ==0.10.8.2.0,
    57 56   any.bytestring-lexing ==0.5.0.8,
    58 57   any.bytestring-strict-builder ==0.4.5.5,
    skipped 37 lines
    96 95   any.data-serializer ==0.3.5,
    97 96   any.data-textual ==0.3.0.3,
    98 97   any.dec ==0.0.4,
    99  - any.deepseq ==1.4.4.0,
     98 + any.deepseq ==1.4.6.1,
    100 99   any.deferred-folds ==0.9.18.1,
    101 100   any.dependent-map ==0.4.0.0,
    102 101   any.dependent-sum ==0.7.1.0,
    103  - any.directory ==1.3.6.0,
     102 + any.dependent-sum-template ==0.1.1.1,
     103 + any.directory ==1.3.6.2,
    104 104   any.distributive ==0.6.2.1,
    105 105   any.dlist ==1.0,
    106 106   any.double-conversion ==2.0.4.1,
    skipped 10 lines
    117 117   any.fail ==4.9.0.0,
    118 118   any.fast-logger ==3.1.1,
    119 119   any.file-embed ==0.0.15.0,
    120  - any.filepath ==1.4.2.1,
     120 + any.filepath ==1.4.2.2,
    121 121   any.flush-queue ==1.0.0,
    122 122   any.focus ==1.0.3,
    123 123   any.foldl ==1.4.12,
    124 124   any.formatting ==7.1.3,
    125 125   any.free ==5.1.7,
    126 126   any.generics-sop ==0.5.1.2,
    127  - any.ghc ==8.10.7,
    128  - any.ghc-boot ==8.10.7,
    129  - any.ghc-boot-th ==8.10.7,
    130  - any.ghc-heap ==8.10.7,
     127 + any.ghc ==9.2.4.20220919,
     128 + any.ghc-bignum ==1.2,
     129 + any.ghc-boot ==9.2.4.20220919,
     130 + any.ghc-boot-th ==9.2.4.20220919,
     131 + any.ghc-heap ==9.2.4.20220919,
    131 132   any.ghc-heap-view ==0.6.3,
    132  - any.ghc-prim ==0.6.1,
    133  - any.ghci ==8.10.7,
     133 + any.ghc-prim ==0.8.0,
     134 + any.ghci ==9.2.4.20220919,
    134 135   any.graphql-parser ==0.2.0.0,
    135 136   any.happy ==1.20.0,
    136 137   any.hashable ==1.3.5.0,
    skipped 26 lines
    163 164   any.indexed-traversable ==0.1.2,
    164 165   any.indexed-traversable-instances ==0.1.1,
    165 166   any.insert-ordered-containers ==0.2.5.1,
    166  - any.inspection-testing ==0.4.6.0,
    167  - any.integer-gmp ==1.0.3.0,
     167 + any.inspection-testing ==0.4.6.1,
     168 + any.integer-gmp ==1.1,
    168 169   any.integer-logarithms ==1.0.3.1,
    169 170   any.invariant ==0.5.5,
    170 171   any.iproute ==1.7.12,
    skipped 46 lines
    217 218   any.optparse-applicative ==0.16.1.0,
    218 219   any.optparse-generic ==1.4.7,
    219 220   any.parallel ==3.2.2.0,
    220  - any.parsec ==3.1.14.0 || ==3.1.15.0,
     221 + any.parsec ==3.1.15.1,
    221 222   any.parser-combinators ==1.3.0,
    222 223   any.parsers ==0.12.10,
    223 224   any.pcre-light ==0.4.1.0,
    skipped 20 lines
    244 245   any.reflection ==2.1.6,
    245 246   any.regex-base ==0.94.0.2,
    246 247   any.regex-tdfa ==1.3.1.1,
    247  - any.relude ==1.0.0.1,
    248  - any.reroute ==0.6.0.0,
     248 + any.relude ==1.1.0.0,
     249 + any.reroute ==0.7.0.0,
    249 250   any.resource-pool ==0.2.3.2,
    250 251   any.resourcet ==1.2.4.3,
    251 252   any.retry ==0.9.1.0,
    252  - any.rts ==1.0.1,
     253 + any.rts ==1.0.2,
    253 254   any.safe ==0.3.19,
    254 255   any.safe-exceptions ==0.1.7.2,
    255 256   any.scanner ==0.3.1,
    skipped 16 lines
    272 273   any.sop-core ==0.5.0.2,
    273 274   any.split ==0.2.3.4,
    274 275   any.splitmix ==0.1.0.4,
    275  - any.stm ==2.5.0.1,
     276 + any.stm ==2.5.0.2,
    276 277   any.stm-chans ==3.0.0.6,
    277 278   any.stm-containers ==1.2,
    278 279   any.stm-hamt ==1.2.0.7,
    skipped 4 lines
    283 284   any.syb ==0.7.2.1,
    284 285   any.system-filepath ==0.4.14,
    285 286   any.tagged ==0.8.6.1,
    286  - any.template-haskell ==2.16.0.0,
     287 + any.template-haskell ==2.18.0.0,
    287 288   any.terminal-size ==0.3.2.1,
    288  - any.terminfo ==0.4.1.4,
    289  - any.text ==1.2.4.1 || ==1.2.5.0,
     289 + any.terminfo ==0.4.1.5,
     290 + any.text ==1.2.5.0,
    290 291   any.text-builder ==0.6.6.3,
    291 292   any.text-conversions ==0.3.1,
    292 293   any.text-latin1 ==0.3.1,
    skipped 8 lines
    301 302   any.th-orphans ==0.13.12,
    302 303   any.th-reify-many ==0.1.10,
    303 304   any.these ==1.1.1.1,
    304  - any.time ==1.9.3,
     305 + any.these-skinny ==0.7.5,
     306 + any.time ==1.11.1.1,
    305 307   any.time-compat ==1.9.6.1,
    306 308   any.time-locale-compat ==0.1.1.5,
    307 309   any.time-manager ==0.0.0,
    skipped 46 lines
    354 356   any.xml-types ==0.3.8,
    355 357   any.yaml ==0.11.7.0,
    356 358   any.zlib ==0.6.2.3,
    357  -index-state: hackage.haskell.org 2022-07-25T05:35:55Z
     359 +index-state: hackage.haskell.org 2022-09-21T21:18:32Z
    358 360   
  • ■ ■ ■ ■ ■
    server/VERSIONS.json
    1 1  {
     2 + "ghc": "9.2.4",
    2 3   "hlint": "3.3.6",
    3 4   "hpack": "0.34.7",
    4 5   "ormolu": "0.3.1.0"
    skipped 2 lines
  • ■ ■ ■ ■ ■
    server/graphql-engine.cabal
    skipped 481 lines
    482 482   , Hasura.Backends.MSSQL.Types.Instances
    483 483   , Hasura.Backends.MSSQL.Types.Internal
    484 484   , Hasura.Backends.MSSQL.Types.Update
    485  - 
    486 485   , Hasura.Backends.Postgres.Connection
    487 486   , Hasura.Backends.Postgres.Connection.MonadTx
    488 487   , Hasura.Backends.Postgres.Connection.Settings
    skipped 856 lines
  • ■ ■ ■ ■ ■
    server/lib/schema-parsers/src/Data/GADT/Compare/Extended.hs
     1 +{-# LANGUAGE PackageImports #-}
    1 2  {-# LANGUAGE PolyKinds #-}
    2 3   
    3 4  module Data.GADT.Compare.Extended
    skipped 3 lines
    7 8   )
    8 9  where
    9 10   
    10  -import Data.GADT.Compare
     11 +import "dependent-sum" Data.GADT.Compare
    11 12   
    12 13  strengthenOrdering :: Ordering -> GOrdering a a
    13 14  strengthenOrdering LT = GLT
    skipped 10 lines
  • ■ ■ ■ ■ ■
    server/lib/schema-parsers/src/Hasura/GraphQL/Parser/Directives.hs
    skipped 45 lines
    46 46  import Hasura.GraphQL.Parser.Schema
    47 47  import Hasura.GraphQL.Parser.Variable
    48 48  import Language.GraphQL.Draft.Syntax qualified as G
    49  -import Type.Reflection (Typeable, typeRep, (:~:) (..))
     49 +import Type.Reflection (Typeable, typeRep, (:~:) (Refl))
    50 50  import Witherable (catMaybes)
     51 +import Prelude
    51 52   
    52 53  -- Disable custom prelude warnings in preparation for extracting this module into a separate package.
    53 54  {-# ANN module ("HLint: ignore Use onNothing" :: String) #-}
    skipped 237 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Data/Text/NonEmpty.hs
    skipped 15 lines
    16 16  import Database.PG.Query qualified as Q
    17 17  import Hasura.Prelude hiding (lift)
    18 18  import Language.Haskell.TH.Quote (QuasiQuoter (..))
    19  -import Language.Haskell.TH.Syntax (Lift, Q, TExp, lift)
     19 +import Language.Haskell.TH.Syntax (Code, Lift, Q, bindCode, lift)
    20 20  import Test.QuickCheck qualified as QC
    21 21   
    22 22  newtype NonEmptyText = NonEmptyText {unNonEmptyText :: Text}
    skipped 12 lines
    35 35  parseNonEmptyText :: MonadFail m => Text -> m NonEmptyText
    36 36  parseNonEmptyText text = mkNonEmptyText text `onNothing` fail "empty string not allowed"
    37 37   
    38  -nonEmptyText :: Text -> Q (TExp NonEmptyText)
    39  -nonEmptyText = parseNonEmptyText >=> \text -> [||text||]
     38 +nonEmptyText :: Text -> Code Q NonEmptyText
     39 +nonEmptyText textDirty = parseNonEmptyText textDirty `bindCode` \text -> [||text||]
    40 40   
    41 41  -- | Construct 'NonEmptyText' literals at compile-time via quasiquotation.
    42 42  nonEmptyTextQQ :: QuasiQuoter
    skipped 21 lines
  • ■ ■ ■ ■ ■
    server/src-lib/Hasura/Backends/Postgres/Instances/Schema.hs
    skipped 79 lines
    80 80  import Hasura.RQL.Types.SourceCustomization
    81 81  import Hasura.RQL.Types.Table (CustomRootField (..), RolePermInfo (..), TableConfig (..), TableCoreInfoG (..), TableCustomRootFields (..), TableInfo (..), UpdPermInfo (..), ViewInfo (..), getRolePermInfo, isMutable, tableInfoName)
    82 82  import Hasura.SQL.Backend (BackendType (Postgres), PostgresKind (Citus, Vanilla))
    83  -import Hasura.SQL.Tag (HasTag)
    84 83  import Hasura.SQL.Types
    85 84  import Language.GraphQL.Draft.Syntax qualified as G
    86 85   
    skipped 47 lines
    134 133   
    135 134  instance
    136 135   ( PostgresSchema pgKind,
    137  - Backend ('Postgres pgKind),
    138  - HasTag ('Postgres pgKind)
     136 + Backend ('Postgres pgKind)
    139 137   ) =>
    140 138   BS.BackendTableSelectSchema ('Postgres pgKind)
    141 139   where
    skipped 917 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/Base/Instances.hs
    skipped 7 lines
    8 8  import Control.Monad.Fix
    9 9  import Data.Aeson qualified as J
    10 10  import Data.Functor.Product (Product (Pair))
    11  -import "some" Data.GADT.Compare (GCompare (gcompare), GOrdering (GEQ, GGT, GLT))
     11 +import "dependent-sum" Data.GADT.Compare (GCompare (gcompare), GOrdering (GEQ, GGT, GLT))
    12 12  import Data.HashMap.Strict qualified as M
    13 13  import Data.HashSet qualified as S
    14 14  import Data.OpenApi.Declare as D
    skipped 48 lines
    63 63  --------------------------------------------------------------------------------
    64 64  -- Template Haskell
    65 65   
    66  -instance (TH.Lift k, TH.Lift v) => TH.Lift (M.HashMap k v) where
     66 +instance (Hashable k, Eq k, TH.Lift k, TH.Lift v) => TH.Lift (M.HashMap k v) where
    67 67   lift m = [|M.fromList $(TH.lift $ M.toList m)|]
    68  - liftTyped = TH.unsafeTExpCoerce . TH.lift
     68 + -- liftTyped = TH.unsafeTExpCoerce . TH.lift
     69 + liftTyped m = [|| M.fromList $$(TH.liftTyped $ M.toList m) ||]
    69 70   
    70  -instance TH.Lift a => TH.Lift (S.HashSet a) where
     71 +instance (Hashable a, Eq a, TH.Lift a) => TH.Lift (S.HashSet a) where
    71 72   lift s = [|S.fromList $(TH.lift $ S.toList s)|]
    72  - liftTyped = TH.unsafeTExpCoerce . TH.lift
     73 + -- liftTyped = TH.unsafeTExpCoerce . TH.lift
     74 + liftTyped m = [|| S.fromList $$(TH.liftTyped $ S.toList m) ||]
    73 75   
    74 76  deriving instance TH.Lift TDFA.CompOption
    75 77   
    skipped 53 lines
  • ■ ■ ■ ■
    server/src-lib/Hasura/GraphQL/ApolloFederation.hs
    skipped 72 lines
    73 73   _ -> P.parseError $ toErrorMessage "representations is expecting a list of objects only"
    74 74   
    75 75  convertToApolloFedParserFunc ::
    76  - (Monad n, MonadParse n, Backend b) =>
     76 + (MonadParse n, Backend b) =>
    77 77   SourceInfo b ->
    78 78   TableInfo b ->
    79 79   TablePermG b (UnpreparedValue b) ->
    skipped 206 lines
  • ■ ■ ■ ■ ■
    server/src-lib/Hasura/GraphQL/Execute/RemoteJoin/Types.hs
    skipped 213 lines
    214 214   
    215 215  deriving instance
    216 216   ( Backend b,
    217  - Show (ScalarValue b),
    218 217   Show (SourceConfig b),
    219 218   Show (BooleanOperators b (IR.UnpreparedValue b)),
    220 219   Show (FunctionArgumentExp b (IR.UnpreparedValue b))
    skipped 2 lines
    223 222   
    224 223  deriving instance
    225 224   ( Backend b,
    226  - Eq (ScalarValue b),
    227 225   Eq (BooleanOperators b (IR.UnpreparedValue b)),
    228  - Eq (FunctionArgumentExp b (IR.UnpreparedValue b))
     226 + Eq (FunctionArgumentExp b (IR.UnpreparedValue b)),
     227 + Eq (IR.SourceRelationshipSelection b Void IR.UnpreparedValue)
    229 228   ) =>
    230 229   Eq (RemoteSourceJoin b)
    231 230   
    skipped 66 lines
  • ■ ■ ■ ■ ■
    server/src-lib/Hasura/GraphQL/Schema/Update.hs
    skipped 216 lines
    217 217   
    218 218  incOp ::
    219 219   forall b m n r.
    220  - ( Backend b,
    221  - MonadReader r m,
     220 + ( MonadReader r m,
    222 221   MonadError QErr m,
    223 222   P.MonadParse n,
    224 223   BackendSchema b,
    skipped 126 lines
  • ■ ■ ■ ■
    server/src-lib/Hasura/Incremental/Internal/Dependency.hs
    skipped 19 lines
    20 20  import Data.CaseInsensitive (CI)
    21 21  import Data.Dependent.Map qualified as DM
    22 22  import Data.Functor.Classes (Eq1 (..), Eq2 (..))
    23  -import "some" Data.GADT.Compare
     23 +import "dependent-sum" Data.GADT.Compare
    24 24  import Data.HashMap.Strict qualified as HM
    25 25  import Data.HashMap.Strict.InsOrd qualified as OHM
    26 26  import Data.HashMap.Strict.NonEmpty (NEHashMap)
    skipped 415 lines
  • ■ ■ ■ ■
    server/src-lib/Hasura/Incremental/Select.hs
    skipped 48 lines
    49 49   default select :: Selector a ~ FieldS a => Selector a b -> a -> b
    50 50   select (FieldS (_ :: Proxy s)) = getField @s
    51 51   
    52  -instance (Eq k, Ord k, Hashable k) => Select (HashMap k v) where
     52 +instance (Ord k, Hashable k) => Select (HashMap k v) where
    53 53   type Selector (HashMap k v) = ConstS k (Maybe v)
    54 54   select (ConstS k) = M.lookup k
    55 55   
    skipped 90 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/RQL/DDL/Metadata.hs
    skipped 80 lines
    81 81   
    82 82  runClearMetadata ::
    83 83   forall m r.
    84  - ( QErrM m,
    85  - MonadIO m,
     84 + ( MonadIO m,
    86 85   CacheRWM m,
    87 86   MetadataM m,
    88 87   MonadMetadataStorageQueryAPI m,
    skipped 70 lines
    159 158   RMReplaceMetadataV2 v2args -> runReplaceMetadataV2 v2args
    160 159   
    161 160  runReplaceMetadataV1 ::
    162  - ( QErrM m,
    163  - CacheRWM m,
     161 + ( CacheRWM m,
    164 162   MetadataM m,
    165 163   MonadIO m,
    166 164   MonadMetadataStorageQueryAPI m,
    skipped 7 lines
    174 172   
    175 173  runReplaceMetadataV2 ::
    176 174   forall m r.
    177  - ( QErrM m,
    178  - CacheRWM m,
     175 + ( CacheRWM m,
    179 176   MetadataM m,
    180 177   MonadIO m,
    181 178   MonadMetadataStorageQueryAPI m,
    skipped 492 lines
  • ■ ■ ■ ■
    server/src-lib/Hasura/RQL/DDL/Relationship.hs
    skipped 46 lines
    47 47   
    48 48  runCreateRelationship ::
    49 49   forall m b a.
    50  - (MonadError QErr m, CacheRWM m, ToJSON a, MetadataM m, Backend b, BackendMetadata b) =>
     50 + (MonadError QErr m, CacheRWM m, ToJSON a, MetadataM m, BackendMetadata b) =>
    51 51   RelType ->
    52 52   WithTable b (RelDef a) ->
    53 53   m EncJSON
    skipped 310 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/RQL/DDL/Schema/Cache/Common.hs
    skipped 142 lines
    143 143   }
    144 144   deriving (Generic)
    145 145   
    146  -deriving instance (Backend b, Show (TableName b)) => Show (TablePermissionInputs b)
     146 +deriving instance (Backend b) => Show (TablePermissionInputs b)
    147 147   
    148  -deriving instance (Backend b, Eq (TableName b)) => Eq (TablePermissionInputs b)
     148 +deriving instance (Backend b) => Eq (TablePermissionInputs b)
    149 149   
    150 150  instance (Backend b) => Inc.Cacheable (TablePermissionInputs b)
    151 151   
    skipped 188 lines
  • ■ ■ ■ ■
    server/src-lib/Hasura/RQL/DDL/Schema/Function.hs
    skipped 319 lines
    320 320  -- | Changes the custom names of a function. Used in the API command 'pg_set_function_customization'.
    321 321  runSetFunctionCustomization ::
    322 322   forall b m.
    323  - (QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
     323 + (QErrM m, CacheRWM m, MetadataM m, Backend b) =>
    324 324   SetFunctionCustomization b ->
    325 325   m EncJSON
    326 326  runSetFunctionCustomization (SetFunctionCustomization source function config) = do
    skipped 7 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/RQL/DDL/Schema/Table.hs
    skipped 322 lines
    323 323   
    324 324  runSetTableCustomization ::
    325 325   forall b m.
    326  - (QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
     326 + (QErrM m, CacheRWM m, MetadataM m, Backend b) =>
    327 327   SetTableCustomization b ->
    328 328   m EncJSON
    329 329  runSetTableCustomization (SetTableCustomization source table config) = do
    skipped 333 lines
    663 663   
    664 664  runSetApolloFederationConfig ::
    665 665   forall b m.
    666  - (QErrM m, CacheRWM m, MetadataM m, Backend b, BackendMetadata b) =>
     666 + (QErrM m, CacheRWM m, MetadataM m, Backend b) =>
    667 667   SetApolloFederationConfig b ->
    668 668   m EncJSON
    669 669  runSetApolloFederationConfig (SetApolloFederationConfig source table apolloFedConfig) = do
    skipped 11 lines
  • ■ ■ ■ ■
    server/src-lib/Hasura/RQL/DML/Count.hs
    skipped 129 lines
    130 130   validateCountQWith sessVarFromCurrentSetting binRHSBuilder query
    131 131   
    132 132  countQToTx ::
    133  - (QErrM m, MonadTx m) =>
     133 + (MonadTx m) => -- QErrM m ?
    134 134   (CountQueryP1, DS.Seq Q.PrepArg) ->
    135 135   m EncJSON
    136 136  countQToTx (u, p) = do
    skipped 28 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/RQL/IR/BoolExp.hs
    skipped 220 lines
    221 221  deriving instance (Backend b) => Show (PartialSQLExp b)
    222 222   
    223 223  instance
    224  - ( Backend b,
    225  - NFData (BooleanOperators b (PartialSQLExp b))
     224 + ( Backend b
    226 225   ) =>
    227 226   NFData (PartialSQLExp b)
    228 227   
    229 228  instance
    230  - ( Backend b,
    231  - Hashable (BooleanOperators b (PartialSQLExp b))
     229 + ( Backend b
    232 230   ) =>
    233 231   Hashable (PartialSQLExp b)
    234 232   
    235 233  instance
    236  - ( Backend b,
    237  - Cacheable (BooleanOperators b (PartialSQLExp b))
     234 + ( Backend b
    238 235   ) =>
    239 236   Cacheable (PartialSQLExp b)
    240 237   
    skipped 503 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/RQL/IR/Value.hs
    skipped 29 lines
    30 30   
    31 31  deriving instance
    32 32   ( Backend b,
    33  - Eq (ColumnValue b),
    34  - Eq (ScalarValue b)
     33 + Eq (ColumnValue b)
    35 34   ) =>
    36 35   Eq (UnpreparedValue b)
    37 36   
    38 37  deriving instance
    39 38   ( Backend b,
    40  - Show (ColumnValue b),
    41  - Show (ScalarValue b)
     39 + Show (ColumnValue b)
    42 40   ) =>
    43 41   Show (UnpreparedValue b)
    44 42   
    skipped 16 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/RQL/Types/Column.hs
    skipped 124 lines
    125 125   cvValue :: ScalarValue b
    126 126   }
    127 127   
    128  -deriving instance (Backend b, Eq (ScalarValue b)) => Eq (ColumnValue b)
     128 +deriving instance (Backend b) => Eq (ColumnValue b)
    129 129   
    130  -deriving instance (Backend b, Show (ScalarValue b)) => Show (ColumnValue b)
     130 +deriving instance (Backend b) => Show (ColumnValue b)
    131 131   
    132 132  isScalarColumnWhere :: (ScalarType b -> Bool) -> ColumnType b -> Bool
    133 133  isScalarColumnWhere f = \case
    skipped 166 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/SQL/AnyBackend.hs
    skipped 156 lines
    157 157   -- the name of the type
    158 158   (mkName "AnyBackend")
    159 159   -- the type variable
    160  - [KindedTV typeVarName varKind]
     160 + [KindedTV typeVarName () varKind]
    161 161   -- the constructor for each backend
    162 162   ( \b ->
    163 163   pure $
    skipped 91 lines
    255 255   -- the expression on which we do the case switch
    256 256   [|t|]
    257 257   -- the pattern for a given backend: the backend type itself
    258  - (\(con :| args) -> pure $ ConP con [ConP a [] | a <- args])
     258 + (\(con :| args) -> pure $ ConP con [] [ConP a [] [] | a <- args])
    259 259   -- the body for a given backend: creating and wrapping the tag
    260 260   (\b -> [|$(pure $ ConE $ getBackendValueName b) $(pure $ ConE $ getBackendTagName b)|])
    261 261   -- no default case: every constructor should be handled
    skipped 19 lines
    281 281   -- the name of the constructor
    282 282   let consName = getBackendValueName b
    283 283   -- the patterrn we match: @FooValue x@
    284  - let matchPattern = ConP consName [VarP $ mkName "x"]
     284 + let matchPattern = ConP consName [] [VarP $ mkName "x"]
    285 285   -- the body of the match: @FooValue (f x)@
    286 286   matchBody <- [|$(pure $ ConE consName) (f x)|]
    287 287   pure $ Match matchPattern (NormalB matchBody) []
    skipped 26 lines
    314 314   -- the name of the constructor
    315 315   let consName = getBackendValueName b
    316 316   -- the patterrn we match: @FooValue x@
    317  - let matchPattern = ConP consName [VarP $ mkName "x"]
     317 + let matchPattern = ConP consName [] [VarP $ mkName "x"]
    318 318   -- the body of the match: @FooValue <$> f x@
    319 319   matchBody <- [|$(pure $ ConE consName) <$> f x|]
    320 320   pure $ Match matchPattern (NormalB matchBody) []
    skipped 20 lines
    341 341   $( backendCase
    342 342   [|backendTag @b|]
    343 343   -- the pattern for a backend
    344  - (\b -> pure $ ConP (getBackendTagName b) [])
     344 + (\b -> pure $ ConP (getBackendTagName b) [] [])
    345 345   -- the body for a backend
    346 346   (pure . ConE . getBackendValueName)
    347 347   -- no default case
    skipped 92 lines
    440 440   [|(e1, e2)|]
    441 441   -- the pattern for a given backend: @(FooValue a, FooValue b)@
    442 442   ( \b -> do
    443  - let valueCon n = pure $ ConP (getBackendValueName b) [VarP $ mkName n]
     443 + let valueCon n = pure $ ConP (getBackendValueName b) [] [VarP $ mkName n]
    444 444   [p|($(valueCon "a"), $(valueCon "b"))|]
    445 445   )
    446 446   -- the body for each backend: @f a b@
    skipped 21 lines
    468 468   [|(backendTag @b, exists)|]
    469 469   -- the pattern for a given backend
    470 470   ( \b -> do
    471  - let tagConstructor = pure $ ConP (getBackendTagName b) []
    472  - valConstructor = pure $ ConP (getBackendValueName b) [VarP $ mkName "a"]
     471 + let tagConstructor = pure $ ConP (getBackendTagName b) [] []
     472 + valConstructor = pure $ ConP (getBackendValueName b) [] [VarP $ mkName "a"]
    473 473   [p|($tagConstructor, $valConstructor)|]
    474 474   )
    475 475   -- the body for each backend
    skipped 92 lines
    568 568   -- name of the constructor: FooValue
    569 569   let consName = getBackendValueName b
    570 570   -- pattern of the match: @FooValue x@
    571  - let matchPattern = ConP consName [VarP $ mkName "x"]
     571 + let matchPattern = ConP consName [] [VarP $ mkName "x"]
    572 572   -- expression of the match: applying the 'BackendChoice' constructor to x
    573 573   matchBody <- [|$(pure c) x|]
    574 574   pure $ Match matchPattern (NormalB matchBody) []
    skipped 128 lines
    703 703   $( backendCase
    704 704   [|backendKind|]
    705 705   -- the pattern for a given backend
    706  - (\(con :| args) -> pure $ ConP con [ConP arg [] | arg <- args])
     706 + (\(con :| args) -> pure $ ConP con [] [ConP arg [] [] | arg <- args])
    707 707   -- the body for each backend
    708 708   ( \b -> do
    709 709   let valueCon = pure $ ConE $ getBackendValueName b
    skipped 53 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/SQL/TH.hs
    skipped 101 lines
    102 102   -- | the name of the type
    103 103   Name ->
    104 104   -- | type variables of the type if any
    105  - [TyVarBndr] ->
     105 + [TyVarBndr ()] ->
    106 106   -- | the constructor for a given backend
    107 107   (BackendConstructor -> Q Con) ->
    108 108   -- | classes to derive using the stock strategy
    skipped 24 lines
    133 133   backendCase
    134 134   [|$vE|]
    135 135   -- the pattern for a backend
    136  - (\b -> pure $ ConP (getBackendValueName b) [VarP $ mkName "x"])
     136 + (\b -> pure $ ConP (getBackendValueName b) [] [VarP $ mkName "x"])
    137 137   -- the body for a backend
    138 138   (const [|$fE x|])
    139 139   -- no default case
    skipped 2 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/SQL/Tag.hs
    skipped 25 lines
    26 26   -- the name of the type
    27 27   name
    28 28   -- the type variable
    29  - [KindedTV (mkName "b") $ ConT ''BackendType]
     29 + [KindedTV (mkName "b") () $ ConT ''BackendType]
    30 30   -- the constructor for each backend
    31 31   ( \b ->
    32 32   pure $
    skipped 39 lines
    72 72   -- the expression on which we do the case switch
    73 73   [|t|]
    74 74   -- the pattern for a given backend: just its tag, no argument
    75  - (\b -> pure $ ConP (getBackendTagName b) [])
     75 + (\b -> pure $ ConP (getBackendTagName b) [] [])
    76 76   -- the body for a given backend: the backend constructor itself
    77 77   (\b -> pure $ getBackendValue b)
    78 78   -- no default case: every constructor should be handled
    skipped 3 lines
  • ■ ■ ■ ■ ■ ■
    server/src-lib/Hasura/Server/Utils.hs
    skipped 59 lines
    60 60  import Database.PG.Query qualified as Q
    61 61  import Hasura.Base.Instances ()
    62 62  import Hasura.Prelude
    63  -import Language.Haskell.TH.Syntax (Q, TExp)
     63 +import Language.Haskell.TH.Syntax qualified as TH
    64 64  import Network.HTTP.Client qualified as HC
    65 65  import Network.HTTP.Types qualified as HTTP
    66 66  import Network.Wreq qualified as Wreq
    skipped 75 lines
    142 142  -}
    143 143   
    144 144  -- | Quotes a regex using Template Haskell so syntax errors can be reported at compile-time.
    145  -quoteRegex :: TDFA.CompOption -> TDFA.ExecOption -> String -> Q (TExp TDFA.Regex)
    146  -quoteRegex compOption execOption regexText = do
    147  - regex <- TDFA.parseRegex regexText `onLeft` (fail . show)
    148  - [||TDFA.patternToRegex regex compOption execOption||]
     145 +quoteRegex :: TDFA.CompOption -> TDFA.ExecOption -> String -> TH.Code TH.Q TDFA.Regex
     146 +quoteRegex compOption execOption regexText =
     147 + (TDFA.parseRegex regexText `onLeft` (fail . show)) `TH.bindCode` \regex ->
     148 + [||TDFA.patternToRegex regex compOption execOption||]
    149 149   
    150 150  fmapL :: (a -> a') -> Either a b -> Either a' b
    151 151  fmapL fn (Left e) = Left (fn e)
    skipped 192 lines
Please wait...
Page is in error, reload to recover