2022-03-16 03:39:21 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
|
2019-08-14 02:34:37 +03:00
|
|
|
-- | This module (along with the various @Hasura.RQL.DDL.Schema.*@ modules) provides operations to
|
|
|
|
-- load and modify the Hasura catalog and schema cache.
|
2021-09-24 01:56:37 +03:00
|
|
|
--
|
2019-08-14 02:34:37 +03:00
|
|
|
-- * The /catalog/ refers to the set of PostgreSQL tables and views that store all schema information
|
|
|
|
-- known by Hasura. This includes any tracked Postgres tables, views, and functions, all remote
|
|
|
|
-- schemas, and any additionaly Hasura-specific information such as permissions and relationships.
|
2021-09-24 01:56:37 +03:00
|
|
|
--
|
2019-08-14 02:34:37 +03:00
|
|
|
-- Primitive functions for loading and modifying the catalog are defined in
|
|
|
|
-- "Hasura.RQL.DDL.Schema.Catalog", but most uses are wrapped by other functions to synchronize
|
|
|
|
-- catalog information with the information in the schema cache.
|
2021-09-24 01:56:37 +03:00
|
|
|
--
|
2019-08-14 02:34:37 +03:00
|
|
|
-- * The /schema cache/ is a process-global value of type 'SchemaCache' that stores an in-memory
|
|
|
|
-- representation of the data stored in the catalog. The in-memory representation is not identical
|
|
|
|
-- to the data in the catalog, since it has some post-processing applied to it in order to make it
|
|
|
|
-- easier to consume for other parts of the system, such as GraphQL schema generation. For example,
|
2020-10-22 23:42:27 +03:00
|
|
|
-- although column information is represented by 'RawColumnInfo', the schema cache contains
|
|
|
|
-- “processed” 'ColumnInfo' values, instead.
|
2021-09-24 01:56:37 +03:00
|
|
|
--
|
2019-08-14 02:34:37 +03:00
|
|
|
-- Ultimately, the catalog is the source of truth for all information contained in the schema
|
|
|
|
-- cache, but to avoid rebuilding the entire schema cache on every change to the catalog, various
|
|
|
|
-- functions incrementally update the cache when they modify the catalog.
|
|
|
|
module Hasura.RQL.DDL.Schema
|
2021-05-27 18:06:13 +03:00
|
|
|
( module M,
|
|
|
|
RunSQLRes (..),
|
|
|
|
)
|
|
|
|
where
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2019-08-14 02:34:37 +03:00
|
|
|
import Data.Aeson
|
2022-03-16 03:39:21 +03:00
|
|
|
import Data.Aeson.TH (deriveJSON)
|
2021-05-27 18:06:13 +03:00
|
|
|
import Data.Text.Encoding qualified as TE
|
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-27 18:06:13 +03:00
|
|
|
import Database.PostgreSQL.LibPQ qualified as PQ
|
2019-08-14 02:34:37 +03:00
|
|
|
import Hasura.Prelude
|
2021-05-27 18:06:13 +03:00
|
|
|
import Hasura.RQL.DDL.Schema.Cache as M
|
|
|
|
import Hasura.RQL.DDL.Schema.Catalog as M
|
|
|
|
import Hasura.RQL.DDL.Schema.Rename as M
|
|
|
|
import Hasura.RQL.DDL.Schema.Table as M
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2019-08-14 02:34:37 +03:00
|
|
|
data RunSQLRes = RunSQLRes
|
2022-08-01 12:32:04 +03:00
|
|
|
{ rrResultType :: Text,
|
|
|
|
rrResult :: Value
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
2019-08-14 02:34:37 +03:00
|
|
|
deriving (Show, Eq)
|
|
|
|
|
2021-01-19 22:14:42 +03:00
|
|
|
$(deriveJSON hasuraJSON ''RunSQLRes)
|
2019-08-14 02:34:37 +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.FromRes RunSQLRes where
|
|
|
|
fromRes (PG.ResultOkEmpty _) =
|
2019-08-14 02:34:37 +03:00
|
|
|
return $ RunSQLRes "CommandOk" Null
|
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
|
|
|
fromRes (PG.ResultOkData res) = do
|
2019-08-14 02:34:37 +03:00
|
|
|
csvRows <- resToCSV res
|
|
|
|
return $ RunSQLRes "TuplesOk" $ toJSON csvRows
|
|
|
|
where
|
2020-10-27 16:53:49 +03:00
|
|
|
resToCSV :: PQ.Result -> ExceptT Text IO [[Text]]
|
2019-08-14 02:34:37 +03:00
|
|
|
resToCSV r = do
|
|
|
|
nr <- liftIO $ PQ.ntuples r
|
|
|
|
nc <- liftIO $ PQ.nfields r
|
|
|
|
|
|
|
|
hdr <- forM [0 .. pred nc] $ \ic -> do
|
|
|
|
colNameBS <- liftIO $ PQ.fname r ic
|
|
|
|
maybe (return "unknown") decodeBS colNameBS
|
|
|
|
|
|
|
|
rows <- forM [0 .. pred nr] $ \ir ->
|
|
|
|
forM [0 .. pred nc] $ \ic -> do
|
|
|
|
cellValBS <- liftIO $ PQ.getvalue r ir ic
|
|
|
|
maybe (return "NULL") decodeBS cellValBS
|
|
|
|
|
|
|
|
return $ hdr : rows
|
|
|
|
|
2020-12-08 17:22:31 +03:00
|
|
|
decodeBS = either (throwError . tshow) return . TE.decodeUtf8'
|