mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
feature(server): add SQLServer logical models
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/8388 GitOrigin-RevId: cbf813d1114cb03816003ba73788d33ac37f1473
This commit is contained in:
parent
78a129fdd0
commit
2d9c8299c2
@ -153,8 +153,6 @@ test-logical-models:
|
||||
GRAPHQL_ENGINE=$(GRAPHQL_ENGINE_PATH) \
|
||||
cabal run api-tests:exe:api-tests
|
||||
|
||||
|
||||
|
||||
.PHONY: py-tests
|
||||
## py-tests: run the python-based test suite
|
||||
py-tests:
|
||||
|
@ -138,6 +138,7 @@ library
|
||||
Test.Databases.Postgres.UniqueConstraintsSpec
|
||||
Test.Databases.SQLServer.DefaultValues.OnConflictSpec
|
||||
Test.Databases.SQLServer.InsertVarcharColumnSpec
|
||||
Test.Databases.SQLServer.LogicalModelsSpec
|
||||
Test.Databases.SQLServer.VarcharLiteralsSpec
|
||||
Test.EventTriggers.EventTriggersSpecialCharactersSpec
|
||||
Test.EventTriggers.MSSQL.EventTriggerDropSourceCleanupSpec
|
||||
|
@ -281,3 +281,47 @@ tests = do
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Runs a simple query using distinct_on and order_by" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
|
||||
queryWithDuplicates :: Text
|
||||
queryWithDuplicates = "SELECT * FROM (VALUES ('hello', 'world'), ('hello', 'friend')) as t(\"one\", \"two\")"
|
||||
|
||||
helloWorldLogicalModelWithDuplicates :: Schema.LogicalModel
|
||||
helloWorldLogicalModelWithDuplicates =
|
||||
(Schema.logicalModel "hello_world_function" queryWithDuplicates)
|
||||
{ Schema.logicalModelColumns =
|
||||
[ Schema.logicalModelColumn "one" Schema.TStr,
|
||||
Schema.logicalModelColumn "two" Schema.TStr
|
||||
]
|
||||
}
|
||||
|
||||
Schema.trackLogicalModel source helloWorldLogicalModelWithDuplicates testEnvironment
|
||||
|
||||
let expected =
|
||||
[yaml|
|
||||
data:
|
||||
hello_world_function:
|
||||
- one: "hello"
|
||||
two: "world"
|
||||
|]
|
||||
|
||||
actual :: IO Value
|
||||
actual =
|
||||
GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query {
|
||||
hello_world_function (
|
||||
distinct_on: [one]
|
||||
order_by: [{one:asc}]
|
||||
){
|
||||
one
|
||||
two
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
@ -0,0 +1,264 @@
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
|
||||
-- | Access to the SQL
|
||||
module Test.Databases.SQLServer.LogicalModelsSpec (spec) where
|
||||
|
||||
import Data.Aeson (Value)
|
||||
import Data.List.NonEmpty qualified as NE
|
||||
import Data.Time.Calendar.OrdinalDate
|
||||
import Data.Time.Clock
|
||||
import Harness.Backend.Sqlserver qualified as Sqlserver
|
||||
import Harness.GraphqlEngine qualified as GraphqlEngine
|
||||
import Harness.Quoter.Graphql
|
||||
import Harness.Quoter.Yaml (yaml)
|
||||
import Harness.Test.BackendType qualified as BackendType
|
||||
import Harness.Test.Fixture qualified as Fixture
|
||||
import Harness.Test.Schema (Table (..), table)
|
||||
import Harness.Test.Schema qualified as Schema
|
||||
import Harness.TestEnvironment (GlobalTestEnvironment, TestEnvironment, getBackendTypeConfig, options)
|
||||
import Harness.Yaml (shouldAtLeastBe, shouldReturnYaml)
|
||||
import Hasura.Prelude
|
||||
import Test.Hspec (SpecWith, describe, it)
|
||||
|
||||
-- ** Preamble
|
||||
|
||||
featureFlagForLogicalModels :: String
|
||||
featureFlagForLogicalModels = "HASURA_FF_LOGICAL_MODEL_INTERFACE"
|
||||
|
||||
spec :: SpecWith GlobalTestEnvironment
|
||||
spec =
|
||||
Fixture.hgeWithEnv [(featureFlagForLogicalModels, "True")] $
|
||||
Fixture.runClean -- re-run fixture setup on every test
|
||||
( NE.fromList
|
||||
[ (Fixture.fixture $ Fixture.Backend Sqlserver.backendTypeMetadata)
|
||||
{ Fixture.setupTeardown = \(testEnvironment, _) ->
|
||||
[ Sqlserver.setupTablesAction schema testEnvironment
|
||||
]
|
||||
}
|
||||
]
|
||||
)
|
||||
tests
|
||||
|
||||
-- ** Setup and teardown
|
||||
|
||||
schema :: [Schema.Table]
|
||||
schema =
|
||||
[ (table "article")
|
||||
{ tableColumns =
|
||||
[ Schema.column "id" Schema.TInt,
|
||||
Schema.column "title" Schema.TStr,
|
||||
Schema.column "content" Schema.TStr,
|
||||
Schema.column "date" Schema.TUTCTime
|
||||
],
|
||||
tableData =
|
||||
[ [ Schema.VInt 1,
|
||||
Schema.VStr "Dogs",
|
||||
Schema.VStr "I like to eat dog food I am a dogs I like to eat dog food I am a dogs I like to eat dog food I am a dogs",
|
||||
Schema.VUTCTime (UTCTime (fromOrdinalDate 2000 1) 0)
|
||||
]
|
||||
]
|
||||
}
|
||||
]
|
||||
|
||||
tests :: SpecWith TestEnvironment
|
||||
tests = do
|
||||
let articleQuery :: Schema.SchemaName -> Text
|
||||
articleQuery schemaName =
|
||||
"select id, title,(substring(content, 1, {{length}}) + (case when len(content) < {{length}} then '' else '...' end)) as excerpt,date from [" <> Schema.unSchemaName schemaName <> "].[article]"
|
||||
|
||||
articleWithExcerptLogicalModel :: Text -> Schema.SchemaName -> Schema.LogicalModel
|
||||
articleWithExcerptLogicalModel name schemaName =
|
||||
(Schema.logicalModel name (articleQuery schemaName))
|
||||
{ Schema.logicalModelColumns =
|
||||
[ Schema.logicalModelColumn "id" Schema.TInt,
|
||||
Schema.logicalModelColumn "title" Schema.TStr,
|
||||
Schema.logicalModelColumn "excerpt" Schema.TStr,
|
||||
Schema.logicalModelColumn "date" Schema.TUTCTime
|
||||
],
|
||||
Schema.logicalModelArguments =
|
||||
[ Schema.logicalModelColumn "length" Schema.TInt
|
||||
]
|
||||
}
|
||||
|
||||
describe "Testing Logical Models" $ do
|
||||
it "Runs a simple query that takes one parameter and uses it multiple times" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
schemaName = Schema.getSchemaName testEnvironment
|
||||
|
||||
Schema.trackLogicalModel source (articleWithExcerptLogicalModel "article_with_excerpt" schemaName) testEnvironment
|
||||
|
||||
let actual :: IO Value
|
||||
actual =
|
||||
GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query {
|
||||
article_with_excerpt(args: { length: 34 }) {
|
||||
id
|
||||
title
|
||||
date
|
||||
excerpt
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
[yaml|
|
||||
data:
|
||||
article_with_excerpt:
|
||||
- id: 1
|
||||
title: "Dogs"
|
||||
date: "00:00:00"
|
||||
excerpt: "I like to eat dog food I am a dogs..."
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Uses two queries with the same argument names and ensure they don't mess with one another" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
schemaName = Schema.getSchemaName testEnvironment
|
||||
|
||||
Schema.trackLogicalModel
|
||||
source
|
||||
(articleWithExcerptLogicalModel "article_with_excerpt_1" schemaName)
|
||||
testEnvironment
|
||||
|
||||
Schema.trackLogicalModel
|
||||
source
|
||||
(articleWithExcerptLogicalModel "article_with_excerpt_2" schemaName)
|
||||
testEnvironment
|
||||
|
||||
let actual :: IO Value
|
||||
actual =
|
||||
GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query {
|
||||
article_with_excerpt_1(args: { length: 34 }) {
|
||||
excerpt
|
||||
}
|
||||
article_with_excerpt_2(args: { length: 13 }) {
|
||||
excerpt
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
[yaml|
|
||||
data:
|
||||
article_with_excerpt_1:
|
||||
- excerpt: "I like to eat dog food I am a dogs..."
|
||||
article_with_excerpt_2:
|
||||
- excerpt: "I like to eat..."
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Uses the same one parameter query multiple times" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
schemaName = Schema.getSchemaName testEnvironment
|
||||
|
||||
Schema.trackLogicalModel source (articleWithExcerptLogicalModel "article_with_excerpt" schemaName) testEnvironment
|
||||
|
||||
let actual :: IO Value
|
||||
actual =
|
||||
GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query {
|
||||
first: article_with_excerpt(args: { length: 34 }) {
|
||||
excerpt
|
||||
}
|
||||
second: article_with_excerpt(args: { length: 13 }) {
|
||||
excerpt
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
expected =
|
||||
[yaml|
|
||||
data:
|
||||
first:
|
||||
- excerpt: "I like to eat dog food I am a dogs..."
|
||||
second:
|
||||
- excerpt: "I like to eat..."
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Uses a one parameter query, passing it a GraphQL variable" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
schemaName = Schema.getSchemaName testEnvironment
|
||||
|
||||
Schema.trackLogicalModel source (articleWithExcerptLogicalModel "article_with_excerpt" schemaName) testEnvironment
|
||||
|
||||
let variables =
|
||||
[yaml|
|
||||
length: 34
|
||||
|]
|
||||
|
||||
actual :: IO Value
|
||||
actual =
|
||||
GraphqlEngine.postGraphqlWithVariables
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query MyQuery($length: Int!) {
|
||||
article_with_excerpt(args: { length: $length }) {
|
||||
excerpt
|
||||
}
|
||||
}
|
||||
|]
|
||||
variables
|
||||
|
||||
expected =
|
||||
[yaml|
|
||||
data:
|
||||
article_with_excerpt:
|
||||
- excerpt: "I like to eat dog food I am a dogs..."
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Runs a query that uses a built-in Stored Procedure" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
|
||||
goodQuery = "EXEC sp_databases"
|
||||
|
||||
useStoredProcedure :: Schema.LogicalModel
|
||||
useStoredProcedure =
|
||||
(Schema.logicalModel "use_stored_procedure" goodQuery)
|
||||
{ Schema.logicalModelColumns =
|
||||
[ Schema.logicalModelColumn "database_name" Schema.TStr,
|
||||
Schema.logicalModelColumn "database_size" Schema.TInt,
|
||||
Schema.logicalModelColumn "remarks" Schema.TStr
|
||||
]
|
||||
}
|
||||
|
||||
Schema.trackLogicalModel source useStoredProcedure testEnvironment
|
||||
|
||||
-- making an assumption here that an SQLServer instance will always have
|
||||
-- a `master` database
|
||||
let expected =
|
||||
[yaml|
|
||||
data:
|
||||
use_stored_procedure:
|
||||
- database_name: "master"
|
||||
|]
|
||||
|
||||
actual <-
|
||||
GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query {
|
||||
use_stored_procedure {
|
||||
database_name
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
actual `shouldAtLeastBe` expected
|
@ -8,6 +8,7 @@ import Data.List.NonEmpty qualified as NE
|
||||
import Harness.Backend.Citus qualified as Citus
|
||||
import Harness.Backend.Cockroach qualified as Cockroach
|
||||
import Harness.Backend.Postgres qualified as Postgres
|
||||
import Harness.Backend.Sqlserver qualified as Sqlserver
|
||||
import Harness.GraphqlEngine qualified as GraphqlEngine
|
||||
import Harness.Quoter.Graphql
|
||||
import Harness.Quoter.Yaml (interpolateYaml, yaml)
|
||||
@ -44,6 +45,11 @@ spec =
|
||||
{ Fixture.setupTeardown = \(testEnvironment, _) ->
|
||||
[ Citus.setupTablesAction schema testEnvironment
|
||||
]
|
||||
},
|
||||
(Fixture.fixture $ Fixture.Backend Sqlserver.backendTypeMetadata)
|
||||
{ Fixture.setupTeardown = \(testEnvironment, _) ->
|
||||
[ Sqlserver.setupTablesAction schema testEnvironment
|
||||
]
|
||||
}
|
||||
]
|
||||
)
|
||||
@ -252,50 +258,6 @@ tests = do
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Runs a simple query using distinct_on and order_by" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
source = BackendType.backendSourceName backendTypeMetadata
|
||||
|
||||
queryWithDuplicates :: Text
|
||||
queryWithDuplicates = "SELECT * FROM (VALUES ('hello', 'world'), ('hello', 'friend')) as t(\"one\", \"two\")"
|
||||
|
||||
helloWorldLogicalModelWithDuplicates :: Schema.LogicalModel
|
||||
helloWorldLogicalModelWithDuplicates =
|
||||
(Schema.logicalModel "hello_world_function" queryWithDuplicates)
|
||||
{ Schema.logicalModelColumns =
|
||||
[ Schema.logicalModelColumn "one" Schema.TStr,
|
||||
Schema.logicalModelColumn "two" Schema.TStr
|
||||
]
|
||||
}
|
||||
|
||||
Schema.trackLogicalModel source helloWorldLogicalModelWithDuplicates testEnvironment
|
||||
|
||||
let expected =
|
||||
[yaml|
|
||||
data:
|
||||
hello_world_function:
|
||||
- one: "hello"
|
||||
two: "world"
|
||||
|]
|
||||
|
||||
actual :: IO Value
|
||||
actual =
|
||||
GraphqlEngine.postGraphql
|
||||
testEnvironment
|
||||
[graphql|
|
||||
query {
|
||||
hello_world_function (
|
||||
distinct_on: [one]
|
||||
order_by: [{one:asc}]
|
||||
){
|
||||
one
|
||||
two
|
||||
}
|
||||
}
|
||||
|]
|
||||
|
||||
shouldReturnYaml (options testEnvironment) actual expected
|
||||
|
||||
it "Runs a simple query that takes no parameters" $ \testEnvironment -> do
|
||||
let backendTypeMetadata = fromMaybe (error "Unknown backend") $ getBackendTypeConfig testEnvironment
|
||||
sourceName = BackendType.backendSourceName backendTypeMetadata
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# HLINT ignore "Use onNothing" #-}
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{-# HLINT ignore "Use onNothing" #-}
|
||||
{-# LANGUAGE TemplateHaskellQuotes #-}
|
||||
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
|
||||
|
||||
|
@ -156,9 +156,9 @@ createTable testEnvironment Schema.Table {tableName, tableColumns, tablePrimaryK
|
||||
|
||||
scalarType :: HasCallStack => Schema.ScalarType -> Text
|
||||
scalarType = \case
|
||||
Schema.TInt -> "integer"
|
||||
Schema.TInt -> "int"
|
||||
Schema.TStr -> "nvarchar(127)"
|
||||
Schema.TUTCTime -> "timestamp"
|
||||
Schema.TUTCTime -> "time"
|
||||
Schema.TBool -> "bit"
|
||||
Schema.TGeography -> "geography"
|
||||
Schema.TCustomType txt -> Schema.getBackendScalarType txt bstMssql
|
||||
|
@ -73,13 +73,15 @@ buildDeleteTx deleteOperation stringifyNum queryTags = do
|
||||
toQueryFlat $
|
||||
TQ.fromSelectIntoTempTable $
|
||||
TSQL.toSelectIntoTempTable tempTableNameDeleted (_adTable deleteOperation) (_adAllCols deleteOperation) RemoveConstraints
|
||||
|
||||
-- Create a temp table
|
||||
Tx.unitQueryE defaultMSSQLTxErrorHandler (createInsertedTempTableQuery `withQueryTags` queryTags)
|
||||
let deleteQuery = TQ.fromDelete <$> TSQL.fromDelete deleteOperation
|
||||
deleteQueryValidated <- toQueryFlat <$> runFromIr deleteQuery
|
||||
deleteQueryValidated <- toQueryFlat . qwdQuery <$> runFromIr deleteQuery
|
||||
|
||||
-- Execute DELETE statement
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (deleteQueryValidated `withQueryTags` queryTags)
|
||||
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _adOutput deleteOperation
|
||||
mutationOutputSelect <- qwdQuery <$> runFromIr (mkMutationOutputSelect stringifyNum withAlias $ _adOutput deleteOperation)
|
||||
|
||||
let withSelect =
|
||||
emptySelect
|
||||
@ -88,8 +90,10 @@ buildDeleteTx deleteOperation stringifyNum queryTags = do
|
||||
}
|
||||
finalMutationOutputSelect = mutationOutputSelect {selectWith = Just $ With $ pure $ Aliased withSelect withAlias}
|
||||
mutationOutputSelectQuery = toQueryFlat $ TQ.fromSelect finalMutationOutputSelect
|
||||
|
||||
-- Execute SELECT query and fetch mutation response
|
||||
result <- encJFromText <$> Tx.singleRowQueryE defaultMSSQLTxErrorHandler (mutationOutputSelectQuery `withQueryTags` queryTags)
|
||||
|
||||
-- delete the temporary table
|
||||
let dropDeletedTempTableQuery = toQueryFlat $ dropTempTableQuery tempTableNameDeleted
|
||||
Tx.unitQueryE defaultMSSQLTxErrorHandler (dropDeletedTempTableQuery `withQueryTags` queryTags)
|
||||
|
@ -227,7 +227,7 @@ buildUpsertTx tableName insert ifMatched queryTags = do
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (insertValuesIntoTempTableQuery `withQueryTags` queryTags)
|
||||
|
||||
-- Run the MERGE query and store the mutated rows in #inserted temporary table
|
||||
merge <- runFromIr (toMerge tableName (_aiInsertObject $ _aiData insert) allTableColumns ifMatched)
|
||||
merge <- qwdQuery <$> runFromIr (toMerge tableName (_aiInsertObject $ _aiData insert) allTableColumns ifMatched)
|
||||
let mergeQuery = toQueryFlat $ TQ.fromMerge merge
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (mergeQuery `withQueryTags` queryTags)
|
||||
|
||||
@ -244,11 +244,11 @@ buildInsertResponseTx ::
|
||||
Tx.TxET QErr m (Text, Int)
|
||||
buildInsertResponseTx stringifyNum withAlias insert queryTags = do
|
||||
-- Generate a SQL SELECT statement which outputs the mutation response using the #inserted
|
||||
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert
|
||||
mutationOutputSelect <- qwdQuery <$> runFromIr (mkMutationOutputSelect stringifyNum withAlias $ _aiOutput insert)
|
||||
|
||||
-- The check constraint is translated to boolean expression
|
||||
let checkCondition = fst $ _aiCheckCondition $ _aiData insert
|
||||
checkBoolExp <- runFromIr $ runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias)
|
||||
checkBoolExp <- qwdQuery <$> runFromIr (runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
||||
|
||||
let withSelect =
|
||||
emptySelect
|
||||
|
@ -82,13 +82,15 @@ buildUpdateTx updateOperation stringifyNum queryTags = do
|
||||
-- Create a temp table
|
||||
Tx.unitQueryE defaultMSSQLTxErrorHandler (createInsertedTempTableQuery `withQueryTags` queryTags)
|
||||
let updateQuery = TQ.fromUpdate <$> TSQL.fromUpdate updateOperation
|
||||
updateQueryValidated <- toQueryFlat <$> runFromIr updateQuery
|
||||
updateQueryValidated <- toQueryFlat . qwdQuery <$> runFromIr updateQuery
|
||||
|
||||
-- Execute UPDATE statement
|
||||
Tx.unitQueryE mutationMSSQLTxErrorHandler (updateQueryValidated `withQueryTags` queryTags)
|
||||
mutationOutputSelect <- runFromIr $ mkMutationOutputSelect stringifyNum withAlias $ _auOutput updateOperation
|
||||
mutationOutputSelect <- qwdQuery <$> runFromIr (mkMutationOutputSelect stringifyNum withAlias $ _auOutput updateOperation)
|
||||
let checkCondition = _auCheck updateOperation
|
||||
|
||||
-- The check constraint is translated to boolean expression
|
||||
checkBoolExp <- runFromIr $ runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias)
|
||||
checkBoolExp <- qwdQuery <$> runFromIr (runReaderT (fromGBoolExp checkCondition) (EntityAlias withAlias))
|
||||
|
||||
let withSelect =
|
||||
emptySelect
|
||||
|
@ -12,6 +12,8 @@ module Hasura.Backends.MSSQL.FromIr
|
||||
FromIr,
|
||||
runFromIr,
|
||||
Error (..),
|
||||
tellBefore,
|
||||
tellAfter,
|
||||
|
||||
-- * Name generation
|
||||
NameTemplate (..),
|
||||
@ -21,6 +23,7 @@ where
|
||||
|
||||
import Control.Monad.Validate
|
||||
import Control.Monad.Validate qualified as V
|
||||
import Control.Monad.Writer.Strict
|
||||
import Data.Map.Strict (Map)
|
||||
import Data.Map.Strict qualified as M
|
||||
import Data.Text qualified as T
|
||||
@ -31,6 +34,28 @@ import Hasura.Prelude
|
||||
import Hasura.RQL.IR qualified as IR
|
||||
import Hasura.SQL.Backend
|
||||
|
||||
-- | Allow the query process to emit extra setup / teardown steps
|
||||
data IRWriter = IRWriter
|
||||
{ irwBefore :: [TempTableDDL],
|
||||
irwAfter :: [TempTableDDL]
|
||||
}
|
||||
|
||||
instance Semigroup IRWriter where
|
||||
(IRWriter a b) <> (IRWriter a' b') = IRWriter (a <> a') (b' <> b)
|
||||
|
||||
instance Monoid IRWriter where
|
||||
mempty = IRWriter mempty mempty
|
||||
|
||||
-- | add a step to be run before the main query
|
||||
tellBefore :: TempTableDDL -> FromIr ()
|
||||
tellBefore step =
|
||||
tell (IRWriter {irwBefore = [step], irwAfter = mempty})
|
||||
|
||||
-- | add a step to be run after the main query
|
||||
tellAfter :: TempTableDDL -> FromIr ()
|
||||
tellAfter step =
|
||||
tell (IRWriter {irwBefore = mempty, irwAfter = [step]})
|
||||
|
||||
-- | The central Monad used throughout for all conversion functions.
|
||||
--
|
||||
-- It has the following features:
|
||||
@ -43,20 +68,29 @@ import Hasura.SQL.Backend
|
||||
-- translation process needing to be bothered about potential name shadowing.
|
||||
-- See 'generateAlias'.
|
||||
newtype FromIr a = FromIr
|
||||
{ unFromIr :: StateT (Map Text Int) (Validate (NonEmpty Error)) a
|
||||
{ unFromIr ::
|
||||
StateT
|
||||
(Map Text Int)
|
||||
(WriterT IRWriter (Validate (NonEmpty Error)))
|
||||
a
|
||||
}
|
||||
deriving (Functor, Applicative, Monad, MonadValidate (NonEmpty Error))
|
||||
deriving (Functor, Applicative, Monad, MonadValidate (NonEmpty Error), MonadWriter IRWriter)
|
||||
|
||||
-- | Run a 'FromIr' action, throwing errors that have been collected using the
|
||||
-- supplied action.
|
||||
runFromIr :: MonadError QErr m => FromIr a -> m a
|
||||
runFromIr = flip onLeft (throw500 . tshow) . V.runValidate . flip evalStateT mempty . unFromIr
|
||||
runFromIr :: MonadError QErr m => FromIr a -> m (QueryWithDDL a)
|
||||
runFromIr =
|
||||
fmap (\(result, IRWriter before after) -> QueryWithDDL before result after)
|
||||
. flip onLeft (throw500 . tshow)
|
||||
. V.runValidate
|
||||
. runWriterT
|
||||
. flip evalStateT mempty
|
||||
. unFromIr
|
||||
|
||||
-- | Errors that may happen during translation.
|
||||
data Error
|
||||
= UnsupportedOpExpG (IR.OpExpG 'MSSQL Expression)
|
||||
| FunctionNotSupported
|
||||
| LogicalModelNotSupported
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- | Hints about the type of entity that 'generateAlias' is producing an alias
|
||||
|
@ -14,10 +14,12 @@ import Control.Applicative (getConst)
|
||||
import Control.Monad.Validate
|
||||
import Data.Aeson.Extended qualified as J
|
||||
import Data.HashMap.Strict qualified as HM
|
||||
import Data.HashMap.Strict.InsOrd qualified as InsOrd
|
||||
import Data.List.NonEmpty qualified as NE
|
||||
import Data.Map.Strict (Map)
|
||||
import Data.Map.Strict qualified as M
|
||||
import Data.Proxy
|
||||
import Data.Text.Extended qualified as T
|
||||
import Data.Text.NonEmpty (mkNonEmptyTextUnsafe)
|
||||
import Database.ODBC.SQLServer qualified as ODBC
|
||||
import Hasura.Backends.MSSQL.FromIr
|
||||
@ -25,11 +27,16 @@ import Hasura.Backends.MSSQL.FromIr
|
||||
FromIr,
|
||||
NameTemplate (..),
|
||||
generateAlias,
|
||||
tellAfter,
|
||||
tellBefore,
|
||||
)
|
||||
import Hasura.Backends.MSSQL.FromIr.Constants
|
||||
import Hasura.Backends.MSSQL.FromIr.Expression
|
||||
import Hasura.Backends.MSSQL.Instances.Types ()
|
||||
import Hasura.Backends.MSSQL.Types.Internal as TSQL
|
||||
import Hasura.CustomReturnType (CustomReturnType (..))
|
||||
import Hasura.LogicalModel.IR qualified as IR
|
||||
import Hasura.LogicalModel.Types (LogicalModelName (..), NullableScalarType (..))
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.IR qualified as IR
|
||||
import Hasura.RQL.Types.Column qualified as IR
|
||||
@ -202,7 +209,7 @@ fromSelectRows annSelectG = do
|
||||
IR.FromTable qualifiedObject -> fromQualifiedTable qualifiedObject
|
||||
IR.FromIdentifier identifier -> pure $ FromIdentifier $ IR.unFIIdentifier identifier
|
||||
IR.FromFunction {} -> refute $ pure FunctionNotSupported
|
||||
IR.FromLogicalModel {} -> refute $ pure LogicalModelNotSupported
|
||||
IR.FromLogicalModel logicalModel -> fromLogicalModel logicalModel
|
||||
Args
|
||||
{ argsOrderBy,
|
||||
argsWhere,
|
||||
@ -220,6 +227,7 @@ fromSelectRows annSelectG = do
|
||||
filterExpression <-
|
||||
runReaderT (fromGBoolExp permFilter) (fromAlias selectFrom)
|
||||
let selectProjections = map fieldSourceProjections fieldSources
|
||||
|
||||
pure $
|
||||
emptySelect
|
||||
{ selectOrderBy = argsOrderBy,
|
||||
@ -323,6 +331,35 @@ mkAggregateSelect Args {..} foreignKeyConditions filterExpression selectFrom agg
|
||||
| (index, (fieldName, projections)) <- aggregates
|
||||
]
|
||||
|
||||
fromLogicalModel :: IR.LogicalModel 'MSSQL Expression -> FromIr TSQL.From
|
||||
fromLogicalModel logicalModel = do
|
||||
let logicalModelName = IR.lmRootFieldName logicalModel
|
||||
logicalModelSql = IR.lmInterpolatedQuery logicalModel
|
||||
logicalModelReturnType = IR.lmReturnType logicalModel
|
||||
|
||||
rawTempTableName = T.toTxt (getLogicalModelName logicalModelName)
|
||||
aliasedTempTableName = Aliased (TempTableName rawTempTableName) rawTempTableName
|
||||
|
||||
let columns =
|
||||
( \(name, ty) ->
|
||||
UnifiedColumn
|
||||
{ name = name,
|
||||
type' = (nstType ty)
|
||||
}
|
||||
)
|
||||
<$> InsOrd.toList (crtColumns logicalModelReturnType)
|
||||
|
||||
-- \| add create temp table to "the environment"
|
||||
tellBefore (CreateTemp (TempTableName rawTempTableName) columns)
|
||||
|
||||
-- \| add insert into temp table
|
||||
tellBefore (InsertTemp (TempTableName rawTempTableName) logicalModelSql)
|
||||
|
||||
-- \| when we're done, drop the temp table
|
||||
tellAfter (DropTemp (TempTableName rawTempTableName))
|
||||
|
||||
pure $ TSQL.FromTempTable aliasedTempTableName
|
||||
|
||||
fromSelectAggregate ::
|
||||
Maybe (EntityAlias, HashMap ColumnName ColumnName) ->
|
||||
IR.AnnSelectG 'MSSQL (IR.TableAggregateFieldG 'MSSQL Void) Expression ->
|
||||
@ -341,7 +378,7 @@ fromSelectAggregate
|
||||
IR.FromTable qualifiedObject -> fromQualifiedTable qualifiedObject
|
||||
IR.FromIdentifier identifier -> pure $ FromIdentifier $ IR.unFIIdentifier identifier
|
||||
IR.FromFunction {} -> refute $ pure FunctionNotSupported
|
||||
IR.FromLogicalModel {} -> refute $ pure LogicalModelNotSupported
|
||||
IR.FromLogicalModel logicalModel -> fromLogicalModel logicalModel
|
||||
-- Below: When we're actually a RHS of a query (of CROSS APPLY),
|
||||
-- then we'll have a LHS table that we're joining on. So we get the
|
||||
-- conditions expressions from the field mappings. The LHS table is
|
||||
|
@ -97,16 +97,22 @@ msDBQueryPlan ::
|
||||
m (DBStepInfo 'MSSQL)
|
||||
msDBQueryPlan userInfo _env sourceName sourceConfig qrf _ _ = do
|
||||
let sessionVariables = _uiSession userInfo
|
||||
statement <- planQuery sessionVariables qrf
|
||||
(QueryWithDDL {qwdBeforeSteps, qwdAfterSteps, qwdQuery = statement}) <- planQuery sessionVariables qrf
|
||||
queryTags <- ask
|
||||
|
||||
-- Append Query tags comment to the select statement
|
||||
let printer = fromSelect statement `withQueryTagsPrinter` queryTags
|
||||
queryString = ODBC.renderQuery (toQueryPretty printer)
|
||||
|
||||
pure $ DBStepInfo @'MSSQL sourceName sourceConfig (Just queryString) (runSelectQuery printer) ()
|
||||
pure $ DBStepInfo @'MSSQL sourceName sourceConfig (Just queryString) (runSelectQuery printer qwdBeforeSteps qwdAfterSteps) ()
|
||||
where
|
||||
runSelectQuery queryPrinter = OnBaseMonad do
|
||||
let queryTx = encJFromText <$> Tx.singleRowQueryE defaultMSSQLTxErrorHandler (toQueryFlat queryPrinter)
|
||||
runSelectQuery queryPrinter beforeSteps afterSteps = OnBaseMonad do
|
||||
let queryTx = do
|
||||
let executeStep = Tx.unitQueryE defaultMSSQLTxErrorHandler . toQueryFlat . TQ.fromTempTableDDL
|
||||
traverse_ executeStep beforeSteps
|
||||
result <- encJFromText <$> Tx.singleRowQueryE defaultMSSQLTxErrorHandler (toQueryFlat queryPrinter)
|
||||
traverse_ executeStep afterSteps
|
||||
pure result
|
||||
mssqlRunReadOnly (_mscExecCtx sourceConfig) (fmap withNoStatistics queryTx)
|
||||
|
||||
runShowplan ::
|
||||
@ -133,7 +139,7 @@ msDBQueryExplain ::
|
||||
m (AB.AnyBackend DBStepInfo)
|
||||
msDBQueryExplain fieldName userInfo sourceName sourceConfig qrf _ _ = do
|
||||
let sessionVariables = _uiSession userInfo
|
||||
statement <- planQuery sessionVariables qrf
|
||||
statement <- qwdQuery <$> planQuery sessionVariables qrf
|
||||
let query = toQueryPretty (fromSelect statement)
|
||||
queryString = ODBC.renderQuery query
|
||||
odbcQuery = OnBaseMonad $
|
||||
|
@ -35,6 +35,7 @@ import Hasura.GraphQL.Schema.Parser
|
||||
import Hasura.GraphQL.Schema.Parser qualified as P
|
||||
import Hasura.GraphQL.Schema.Select
|
||||
import Hasura.GraphQL.Schema.Update qualified as SU
|
||||
import Hasura.LogicalModel.Schema qualified as LogicalModels
|
||||
import Hasura.Name qualified as Name
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.IR
|
||||
@ -59,6 +60,7 @@ instance BackendSchema 'MSSQL where
|
||||
buildTableInsertMutationFields = GSB.buildTableInsertMutationFields backendInsertParser
|
||||
buildTableDeleteMutationFields = GSB.buildTableDeleteMutationFields
|
||||
buildTableUpdateMutationFields = GSB.buildSingleBatchTableUpdateMutationFields id
|
||||
buildLogicalModelRootFields = LogicalModels.defaultBuildLogicalModelRootFields
|
||||
|
||||
buildFunctionQueryFields _ _ _ _ = pure []
|
||||
buildFunctionRelayQueryFields _ _ _ _ _ = pure []
|
||||
@ -98,6 +100,10 @@ instance BackendTableSelectSchema 'MSSQL where
|
||||
selectTableAggregate = defaultSelectTableAggregate
|
||||
tableSelectionSet = defaultTableSelectionSet
|
||||
|
||||
instance BackendCustomTypeSelectSchema 'MSSQL where
|
||||
logicalModelArguments = defaultLogicalModelArgs
|
||||
logicalModelSelectionSet = defaultLogicalModelSelectionSet
|
||||
|
||||
instance BackendUpdateOperatorsSchema 'MSSQL where
|
||||
type UpdateOperators 'MSSQL = UpdateOperator
|
||||
|
||||
|
@ -52,7 +52,7 @@ planQuery ::
|
||||
MonadError QErr m =>
|
||||
SessionVariables ->
|
||||
QueryDB 'MSSQL Void (UnpreparedValue 'MSSQL) ->
|
||||
m Select
|
||||
m (QueryWithDDL Select)
|
||||
planQuery sessionVariables queryDB = do
|
||||
rootField <- traverse (prepareValueQuery sessionVariables) queryDB
|
||||
runIrWrappingRoot $ fromQueryRootField rootField
|
||||
@ -78,17 +78,19 @@ planSourceRelationship
|
||||
traverseSourceRelationshipSelection
|
||||
(fmap Const . prepareValueQuery sessionVariables)
|
||||
sourceRelationshipRaw
|
||||
runIrWrappingRoot $
|
||||
fromSourceRelationship
|
||||
lhs
|
||||
lhsSchema
|
||||
argumentId
|
||||
(relationshipName, sourceRelationship)
|
||||
qwdQuery
|
||||
<$> runIrWrappingRoot
|
||||
( fromSourceRelationship
|
||||
lhs
|
||||
lhsSchema
|
||||
argumentId
|
||||
(relationshipName, sourceRelationship)
|
||||
)
|
||||
|
||||
runIrWrappingRoot ::
|
||||
MonadError QErr m =>
|
||||
FromIr Select ->
|
||||
m Select
|
||||
m (QueryWithDDL Select)
|
||||
runIrWrappingRoot selectAction =
|
||||
runFromIr selectAction `onLeft` (throwError . overrideQErrStatus HTTP.status400 NotSupported)
|
||||
|
||||
@ -136,7 +138,7 @@ planSubscription unpreparedMap sessionVariables = do
|
||||
unpreparedMap
|
||||
)
|
||||
emptyPrepareState
|
||||
selectMap <- runFromIr (traverse fromQueryRootField rootFieldMap)
|
||||
selectMap <- qwdQuery <$> runFromIr (traverse fromQueryRootField rootFieldMap)
|
||||
pure (collapseMap selectMap, prepareState)
|
||||
|
||||
-- Plan a query without prepare/exec.
|
||||
|
@ -16,6 +16,7 @@ module Hasura.Backends.MSSQL.ToQuery
|
||||
toQueryPretty,
|
||||
fromInsert,
|
||||
fromMerge,
|
||||
fromTempTableDDL,
|
||||
fromSetIdentityInsert,
|
||||
fromDelete,
|
||||
fromUpdate,
|
||||
@ -39,6 +40,8 @@ import Data.Text.Lazy qualified as L
|
||||
import Data.Text.Lazy.Builder qualified as L
|
||||
import Database.ODBC.SQLServer
|
||||
import Hasura.Backends.MSSQL.Types
|
||||
import Hasura.Backends.MSSQL.Types qualified as MSSQL
|
||||
import Hasura.LogicalModel.Metadata (InterpolatedItem (..), InterpolatedQuery (..))
|
||||
import Hasura.Prelude hiding (GT, LT)
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
@ -436,6 +439,32 @@ fromUpdateSet setColumns =
|
||||
UpdateSet p -> " = " <+> p
|
||||
UpdateInc p -> " += " <+> p
|
||||
|
||||
fromTempTableDDL :: MSSQL.TempTableDDL -> Printer
|
||||
fromTempTableDDL = \case
|
||||
CreateTemp tempTableName tempColumns ->
|
||||
"CREATE TABLE "
|
||||
<+> fromTempTableName tempTableName
|
||||
<+> " ( "
|
||||
<+> columns
|
||||
<+> " ) "
|
||||
where
|
||||
columns =
|
||||
SepByPrinter
|
||||
("," <+> NewlinePrinter)
|
||||
(map columnNameAndType tempColumns)
|
||||
columnNameAndType (UnifiedColumn name ty) =
|
||||
fromColumnName name
|
||||
<+> " "
|
||||
<+> fromString (T.unpack (scalarTypeDBName DataLengthMax ty))
|
||||
InsertTemp tempTableName interpolatedQuery ->
|
||||
"INSERT INTO "
|
||||
<+> fromTempTableName tempTableName
|
||||
<+> " "
|
||||
<+> renderInterpolatedQuery interpolatedQuery
|
||||
DropTemp tempTableName ->
|
||||
"DROP TABLE "
|
||||
<+> fromTempTableName tempTableName
|
||||
|
||||
-- | Converts `SelectIntoTempTable`.
|
||||
--
|
||||
-- > SelectIntoTempTable (TempTableName "deleted") [UnifiedColumn "id" IntegerType, UnifiedColumn "name" TextType] (TableName "table" "schema")
|
||||
@ -533,9 +562,20 @@ fromWith :: With -> Printer
|
||||
fromWith (With withSelects) =
|
||||
"WITH " <+> SepByPrinter ", " (map fromAliasedSelect (toList withSelects)) <+> NewlinePrinter
|
||||
where
|
||||
fromAliasedSelect Aliased {..} =
|
||||
fromAliasedSelect (Aliased {..}) =
|
||||
fromNameText aliasedAlias <+> " AS " <+> "( " <+> fromSelect aliasedThing <+> " )"
|
||||
|
||||
renderInterpolatedQuery :: InterpolatedQuery Expression -> Printer
|
||||
renderInterpolatedQuery = foldr (<+>) "" . renderedParts
|
||||
where
|
||||
renderedParts :: InterpolatedQuery Expression -> [Printer]
|
||||
renderedParts (InterpolatedQuery parts) =
|
||||
( \case
|
||||
IIText t -> fromRawUnescapedText t
|
||||
IIVariable v -> fromExpression v
|
||||
)
|
||||
<$> parts
|
||||
|
||||
fromJoinSource :: JoinSource -> Printer
|
||||
fromJoinSource =
|
||||
\case
|
||||
|
@ -61,12 +61,14 @@ module Hasura.Backends.MSSQL.Types.Internal
|
||||
Deleted (..),
|
||||
Output (..),
|
||||
Projection (..),
|
||||
QueryWithDDL (..),
|
||||
Reselect (..),
|
||||
Root (..),
|
||||
ScalarType (..),
|
||||
SchemaName (..),
|
||||
Select (..),
|
||||
SetIdentityInsert (..),
|
||||
TempTableDDL (..),
|
||||
TempTableName (..),
|
||||
SomeTableName (..),
|
||||
TempTable (..),
|
||||
@ -104,11 +106,13 @@ module Hasura.Backends.MSSQL.Types.Internal
|
||||
where
|
||||
|
||||
import Data.Aeson qualified as J
|
||||
import Data.Text qualified as T
|
||||
import Data.Text.Casing (GQLNameIdentifier)
|
||||
import Data.Text.Casing qualified as C
|
||||
import Database.ODBC.SQLServer qualified as ODBC
|
||||
import Hasura.Base.Error
|
||||
import Hasura.GraphQL.Parser.Name qualified as GName
|
||||
import Hasura.LogicalModel.Metadata (InterpolatedQuery)
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.Types.Backend (SupportedNamingCase (..))
|
||||
import Hasura.SQL.Backend
|
||||
@ -377,6 +381,23 @@ newtype Where
|
||||
newtype With
|
||||
= With (NonEmpty (Aliased Select))
|
||||
|
||||
-- | Extra query steps that can be emitted from the main
|
||||
-- query to do things like setup temp tables
|
||||
data TempTableDDL
|
||||
= -- | create a temp table
|
||||
CreateTemp
|
||||
{ stcTempTableName :: TempTableName,
|
||||
stcColumns :: [UnifiedColumn]
|
||||
}
|
||||
| -- | insert output of a statement into a temp table
|
||||
InsertTemp
|
||||
{ stiTempTableName :: TempTableName,
|
||||
stiExpression :: InterpolatedQuery Expression
|
||||
}
|
||||
| -- | Drop a temp table
|
||||
DropTemp
|
||||
{stdTempTableName :: TempTableName}
|
||||
|
||||
data Top
|
||||
= NoTop
|
||||
| Top Int
|
||||
@ -521,6 +542,13 @@ newtype ConstraintName = ConstraintName {constraintNameText :: Text}
|
||||
|
||||
newtype FunctionName = FunctionName {functionNameText :: Text}
|
||||
|
||||
-- | type for a query generated from IR along with any DDL actions
|
||||
data QueryWithDDL a = QueryWithDDL
|
||||
{ qwdBeforeSteps :: [TempTableDDL],
|
||||
qwdQuery :: a,
|
||||
qwdAfterSteps :: [TempTableDDL]
|
||||
}
|
||||
|
||||
-- | Derived from the odbc package.
|
||||
data ScalarType
|
||||
= CharType
|
||||
@ -632,7 +660,11 @@ parseScalarType = \case
|
||||
"uniqueidentifier" -> GuidType
|
||||
"geography" -> GeographyType
|
||||
"geometry" -> GeometryType
|
||||
t -> UnknownType t
|
||||
t ->
|
||||
-- if the type is something like `varchar(127)`, try stripping off the data length
|
||||
if T.isInfixOf "(" t
|
||||
then parseScalarType (T.takeWhile (\c -> c /= '(') t)
|
||||
else UnknownType t
|
||||
|
||||
parseScalarValue :: ScalarType -> J.Value -> Either QErr Value
|
||||
parseScalarValue scalarType jValue = case scalarType of
|
||||
|
@ -4,6 +4,7 @@ module Hasura.LogicalModel.IR
|
||||
)
|
||||
where
|
||||
|
||||
import Hasura.CustomReturnType
|
||||
import Hasura.LogicalModel.Metadata
|
||||
import Hasura.Prelude
|
||||
import Hasura.RQL.Types.Backend
|
||||
@ -16,7 +17,9 @@ data LogicalModel b field = LogicalModel
|
||||
-- | The raw sql to use in the query
|
||||
lmInterpolatedQuery :: InterpolatedQuery field,
|
||||
-- | The arguments passed to the query, if any.
|
||||
lmArgs :: HashMap LogicalModelArgumentName (ColumnValue b)
|
||||
lmArgs :: HashMap LogicalModelArgumentName (ColumnValue b),
|
||||
-- | The return type of the logical model
|
||||
lmReturnType :: CustomReturnType b
|
||||
}
|
||||
deriving (Functor, Foldable, Traversable)
|
||||
|
||||
|
@ -120,7 +120,8 @@ defaultBuildLogicalModelRootFields logicalModel@LogicalModelInfo {..} = runMaybe
|
||||
LogicalModel
|
||||
{ lmRootFieldName = _lmiRootFieldName,
|
||||
lmArgs,
|
||||
lmInterpolatedQuery = interpolatedQuery lmArgs
|
||||
lmInterpolatedQuery = interpolatedQuery lmArgs,
|
||||
lmReturnType = _lmiReturns
|
||||
},
|
||||
IR._asnPerm =
|
||||
if roleName == adminRoleName
|
||||
|
Loading…
Reference in New Issue
Block a user