Plc/feature/mssql logging variables

GitOrigin-RevId: b67a09cbc5bb8b21857c25a0827800ca1826fa1c
This commit is contained in:
Philip Lykke Carlsen 2021-05-21 13:37:34 +02:00 committed by hasura-bot
parent e093399305
commit 8cc358b023
6 changed files with 249 additions and 97 deletions

View File

@ -1,11 +1,19 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hasura.Backends.MSSQL.Instances.Execute (MultiplexedQuery'(..), multiplexRootReselect) where
module Hasura.Backends.MSSQL.Instances.Execute
(
MultiplexedQuery'(..),
PreparedQuery'(..),
multiplexRootReselect,
queryEnvJson
)
where
import Hasura.Prelude
import qualified Data.Aeson.Extended as J
import qualified Data.Environment as Env
import qualified Data.HashSet as Set
import qualified Data.List.NonEmpty as NE
import qualified Data.Text.Extended as T
import qualified Database.ODBC.SQLServer as ODBC
@ -32,7 +40,7 @@ import Hasura.Session
instance BackendExecute 'MSSQL where
type PreparedQuery 'MSSQL = Text
type PreparedQuery 'MSSQL = PreparedQuery'
type MultiplexedQuery 'MSSQL = MultiplexedQuery'
type ExecutionMonad 'MSSQL = ExceptT QErr IO
getRemoteJoins = const []
@ -44,6 +52,25 @@ instance BackendExecute 'MSSQL where
mkLiveQueryExplain = msDBLiveQueryExplain
-- Prepared query
data PreparedQuery' = PreparedQuery'
{ pqQueryString :: Text
, pqGraphQlEnv :: PrepareState
, pqSession :: SessionVariables
}
-- | Render as a JSON object the variables that have been collected from an RQL
-- expression.
queryEnvJson :: PrepareState -> SessionVariables -> J.Value
queryEnvJson (PrepareState posArgs namedArgs requiredSessionVars) sessionVars =
let sessionVarValues = filterSessionVariables (\k _ -> Set.member k requiredSessionVars) sessionVars
in J.object
[ "session" J..= sessionVarValues
, "namedArguments" J..= toTxtEncodedVal namedArgs
, "positionalArguments" J..= toTxtEncodedVal posArgs
]
-- multiplexed query
newtype MultiplexedQuery' = MultiplexedQuery' Reselect
@ -66,14 +93,69 @@ msDBQueryPlan
-> QueryDB 'MSSQL (UnpreparedValue 'MSSQL)
-> m ExecutionStep
msDBQueryPlan _env _manager _reqHeaders userInfo sourceName sourceConfig qrf = do
select <- fromSelect <$> planNoPlan userInfo qrf
let queryString = ODBC.renderQuery $ toQueryPretty select
let sessionVariables = _uiSession userInfo
(statement, queryEnv) <- planQuery sessionVariables qrf
let selectWithEnv = joinEnv statement sessionVariables queryEnv
printer = fromSelect selectWithEnv
queryString = ODBC.renderQuery $ toQueryPretty printer
pool = _mscConnectionPool sourceConfig
odbcQuery = encJFromText <$> runJSONPathQuery pool (toQueryFlat select)
odbcQuery = encJFromText <$> runJSONPathQuery pool (toQueryFlat printer)
pure
$ ExecStepDB []
. AB.mkAnyBackend
$ DBStepInfo @'MSSQL sourceName sourceConfig (Just queryString) odbcQuery
$ DBStepInfo @'MSSQL sourceName sourceConfig (Just $ PreparedQuery' queryString queryEnv sessionVariables) odbcQuery
joinEnv :: Select -> SessionVariables -> PrepareState -> Select
joinEnv querySelect sessionVars prepState =
querySelect
-- We *prepend* the variables of 'prepState' to the list of joins to make
-- them available in the @where@ clause as well as subsequent queries nested
-- in @join@ clauses.
{ selectJoins = [prepJoin] <> selectJoins querySelect }
where
prepJoin :: Join
prepJoin = Join
{ joinSource = JoinSelect $ (select
(
FromOpenJson
Aliased
{ aliasedThing =
OpenJson
{ openJsonExpression =
ValueExpression (ODBC.TextValue $ lbsToTxt $ J.encode $ queryEnvJson prepState sessionVars)
, openJsonWith =
NE.fromList
[ JsonField "session" Nothing
, JsonField "namedArguments" Nothing
, JsonField "positionalArguments" Nothing
]
}
, aliasedAlias = rowAlias
}
)) {selectProjections = [ StarProjection ]
}
,joinJoinAlias =
JoinAlias
{ joinAliasEntity = rowAlias
, joinAliasField = Nothing
}
}
select :: From -> Select
select from =
Select
{ selectFrom = from
, selectTop = NoTop
, selectProjections = []
, selectJoins = []
, selectWhere = Where []
, selectOrderBy = Nothing
, selectFor = NoFor
, selectOffset = Nothing
}
runShowplan
:: ODBC.Query -> ODBC.Connection -> IO [Text]
@ -94,11 +176,13 @@ msDBQueryExplain
-> QueryDB 'MSSQL (UnpreparedValue 'MSSQL)
-> m (AB.AnyBackend DBStepInfo)
msDBQueryExplain fieldName userInfo sourceName sourceConfig qrf = do
select <- fromSelect <$> planNoPlan userInfo qrf
let query = toQueryPretty select
queryString = ODBC.renderQuery $ query
pool = _mscConnectionPool sourceConfig
odbcQuery =
let sessionVariables = _uiSession userInfo
(statement, queryEnv) <- planQuery sessionVariables qrf
let selectWithEnv = joinEnv statement sessionVariables queryEnv
query = toQueryPretty (fromSelect selectWithEnv)
queryString = ODBC.renderQuery $ query
pool = _mscConnectionPool sourceConfig
odbcQuery =
withMSSQLPool
pool
(\conn -> do
@ -210,7 +294,6 @@ msDBMutationPlan
msDBMutationPlan _env _manager _reqHeaders _userInfo _stringifyNum _sourceName _sourceConfig _mrf =
throw500 "mutations are not supported in MSSQL; this should be unreachable"
-- subscription
msDBSubscriptionPlan
@ -223,17 +306,24 @@ msDBSubscriptionPlan
-> InsOrdHashMap G.Name (QueryDB 'MSSQL (UnpreparedValue 'MSSQL))
-> m (LiveQueryPlan 'MSSQL (MultiplexedQuery 'MSSQL))
msDBSubscriptionPlan UserInfo {_uiSession, _uiRole} _sourceName sourceConfig rootFields = do
(reselect, prepareState) <- planMultiplex rootFields _uiSession
let PrepareState{sessionVariables, namedArguments, positionalArguments} = prepareState
(reselect, prepareState) <- planSubscription rootFields _uiSession
let cohortVariables = prepareStateCohortVariables _uiSession prepareState
parameterizedPlan = ParameterizedLiveQueryPlan _uiRole $ MultiplexedQuery' reselect
pure
$ LiveQueryPlan parameterizedPlan sourceConfig cohortVariables
prepareStateCohortVariables :: SessionVariables -> PrepareState -> CohortVariables
prepareStateCohortVariables session prepState =
let PrepareState{sessionVariables, namedArguments, positionalArguments} = prepState
-- TODO: call MSSQL validateVariables
-- (see https://github.com/hasura/graphql-engine-mono/issues/1210)
-- We need to ensure that the values provided for variables are correct according to MSSQL.
-- Without this check an invalid value for a variable for one instance of the subscription will
-- take down the entire multiplexed query.
let cohortVariables = mkCohortVariables
in mkCohortVariables
sessionVariables
_uiSession
session
(toTxtEncodedVal namedArguments)
(toTxtEncodedVal positionalArguments)
let parameterizedPlan = ParameterizedLiveQueryPlan _uiRole $ MultiplexedQuery' reselect
pure
$ LiveQueryPlan parameterizedPlan sourceConfig cohortVariables

View File

@ -58,7 +58,7 @@ runQuery
-> L.Logger L.Hasura
-> SourceConfig 'MSSQL
-> ExceptT QErr IO EncJSON
-> Maybe Text
-> Maybe (PreparedQuery 'MSSQL)
-> m (DiffTime, EncJSON)
-- ^ Also return the time spent in the PG query; for telemetry.
runQuery reqId query fieldName _userInfo logger _sourceConfig tx genSql = do
@ -88,7 +88,7 @@ runMutation
-> L.Logger L.Hasura
-> SourceConfig 'MSSQL
-> ExceptT QErr IO EncJSON
-> Maybe Text
-> Maybe (PreparedQuery 'MSSQL)
-> m (DiffTime, EncJSON)
-- ^ Also return 'Mutation' when the operation was a mutation, and the time
-- spent in the PG query; for telemetry.
@ -131,10 +131,12 @@ run action = do
mkQueryLog
:: GQLReqUnparsed
-> G.Name
-> Maybe Text
-> Maybe (PreparedQuery 'MSSQL)
-> RequestId
-> QueryLog
mkQueryLog gqlQuery fieldName preparedSql requestId =
QueryLog gqlQuery ((fieldName,) <$> generatedQuery) requestId QueryLogKindDatabase
where
generatedQuery = preparedSql <&> \qs -> GeneratedQuery qs J.Null
generatedQuery =
preparedSql <&> \PreparedQuery'{pqQueryString, pqGraphQlEnv, pqSession}
-> GeneratedQuery pqQueryString (J.toJSON $ queryEnvJson pqGraphQlEnv pqSession)

View File

@ -2,14 +2,14 @@
module Hasura.Backends.MSSQL.Plan where
-- TODO: Re-add the export list after cleaning up the module
-- ( planNoPlan
-- , planNoPlanMap
-- , planMultiplex
-- ( planQuery
-- , planSubscription
-- ) where
import Hasura.Prelude hiding (first)
import qualified Data.Aeson as J
import Data.ByteString.Lazy (toStrict)
import qualified Data.HashMap.Strict as HM
import qualified Data.HashMap.Strict.InsOrd as OMap
import qualified Data.HashSet as Set
@ -18,7 +18,6 @@ import qualified Database.ODBC.SQLServer as ODBC
import qualified Language.GraphQL.Draft.Syntax as G
import Control.Monad.Validate
import Data.ByteString.Lazy (toStrict)
import Data.Text.Extended
import qualified Hasura.GraphQL.Parser as GraphQL
@ -40,17 +39,17 @@ type SubscriptionRootFieldMSSQL v = RootField (QDB v) Void Void {-(RQL.AnnAction
-- --------------------------------------------------------------------------------
-- -- Top-level planner
planNoPlan
planQuery
:: MonadError QErr m
=> UserInfo
=> SessionVariables
-> QueryDB 'MSSQL (GraphQL.UnpreparedValue 'MSSQL)
-> m Select
planNoPlan userInfo queryDB = do
rootField <- traverseQueryDB (prepareValueNoPlan (_uiSession userInfo)) queryDB
-> m (Select, PrepareState)
planQuery sessionVariables queryDB = do
let (rootField, env) = flip runState emptyPrepareState $ traverseQueryDB (prepareValueQuery (getSessionVariablesSet $ sessionVariables)) queryDB
select <-
runValidate (TSQL.runFromIr (TSQL.fromRootField rootField))
`onLeft` (throw400 NotSupported . tshow)
pure
pure $ (,env)
select
{ selectFor =
case selectFor select of
@ -68,16 +67,16 @@ planNoPlan userInfo queryDB = do
}
}
planMultiplex
planSubscription
:: MonadError QErr m
=> OMap.InsOrdHashMap G.Name (QueryDB 'MSSQL (GraphQL.UnpreparedValue 'MSSQL))
-> SessionVariables
-> m (Reselect, PrepareState)
planMultiplex unpreparedMap sessionVariables = do
planSubscription unpreparedMap sessionVariables = do
let (rootFieldMap, prepareState) =
runState
(traverse
(traverseQueryDB (prepareValueMultiplex (getSessionVariablesSet sessionVariables)))
(traverseQueryDB (prepareValueSubscription (getSessionVariablesSet sessionVariables)))
unpreparedMap)
emptyPrepareState
selectMap <-
@ -149,14 +148,78 @@ emptyPrepareState = PrepareState
, sessionVariables = mempty
}
-- | Prepare a value without any query planning; Similar to
-- 'prepareValueMultiplex' we replace occurrences of session variables and
-- parameters with references, but with a slightly simpler object.
prepareValueQuery
:: Set.HashSet SessionVariable
-> GraphQL.UnpreparedValue 'MSSQL
-> State PrepareState TSQL.Expression
prepareValueQuery globalVariables =
\case
GraphQL.UVLiteral x -> pure x
GraphQL.UVSession -> do
modify' (\s -> s {sessionVariables = sessionVariables s <> globalVariables})
pure $ sessionVariable RootPath
GraphQL.UVSessionVar _typ text -> do
modify' (\s -> s {sessionVariables = text `Set.insert` sessionVariables s})
pure $ sessionVariable (RootPath `FieldPath` toTxt text)
GraphQL.UVParameter mVariableInfo columnValue ->
case fmap GraphQL.getName mVariableInfo of
Nothing -> do
currentIndex <- (toInteger . length) <$> gets positionalArguments
modify' (\s -> s {
positionalArguments = positionalArguments s <> [columnValue] })
pure (positionalArgument (RootPath `IndexPath` currentIndex))
Just name -> do
modify
(\s ->
s
{ namedArguments =
HM.insert name columnValue (namedArguments s)
})
pure $ namedArgument (RootPath `FieldPath` G.unName name)
where
-- A reference to `row.<column>`
rowDot :: Text -> Expression
rowDot field =
ColumnExpression
FieldName
{ fieldNameEntity = rowAlias
, fieldName = field
}
-- A reference to `row.session.<field>`
sessionVariable :: JsonPath -> Expression
sessionVariable = JsonValueExpression (rowDot "session")
-- A reference to `row.positionalArguments.[ix]`
positionalArgument :: JsonPath -> Expression
positionalArgument = JsonValueExpression (rowDot "positionalArguments")
-- A reference to `row.namedArguments.<field>`
namedArgument :: JsonPath -> Expression
namedArgument = JsonValueExpression (rowDot "namedArguments")
-- | Prepare a value without any query planning; we just execute the
-- query with the values embedded.
prepareValueNoPlan
_prepareValueMutation
:: MonadError QErr m
=> SessionVariables
-> GraphQL.UnpreparedValue 'MSSQL
-> m TSQL.Expression
prepareValueNoPlan sessionVariables =
_prepareValueMutation sessionVariables =
{- History note:
This function used to be called 'planNoPlan', and was used for building sql
expressions for queries. That evolved differently, but this function is now
left as a *suggestion* for implementing support for mutations.
-}
\case
GraphQL.UVLiteral x -> pure x
GraphQL.UVSession -> pure $ ValueExpression $ ODBC.ByteStringValue $ toStrict $ J.encode sessionVariables
@ -166,46 +229,31 @@ prepareValueNoPlan sessionVariables =
`onNothing` throw400 NotFound ("missing session variable: " <>> sessionVariable)
pure $ ValueExpression $ ODBC.TextValue value
-- | Prepare a value for multiplexed queries.
prepareValueMultiplex
prepareValueSubscription
:: Set.HashSet SessionVariable
-> GraphQL.UnpreparedValue 'MSSQL
-> State PrepareState TSQL.Expression
prepareValueMultiplex globalVariables =
prepareValueSubscription globalVariables =
\case
GraphQL.UVLiteral x -> pure x
GraphQL.UVSession -> do
modify' (\s -> s {sessionVariables = sessionVariables s <> globalVariables})
pure $ JsonValueExpression
(ColumnExpression
FieldName
{ fieldNameEntity = rowAlias
, fieldName = resultVarsAlias
})
(RootPath `FieldPath` "session")
pure $ resultVarExp (RootPath `FieldPath` "session")
GraphQL.UVSessionVar _typ text -> do
modify' (\s -> s {sessionVariables = text `Set.insert` sessionVariables s})
pure $ JsonValueExpression
(ColumnExpression
FieldName
{ fieldNameEntity = rowAlias
, fieldName = resultVarsAlias
})
(RootPath `FieldPath` "session" `FieldPath` toTxt text)
pure $ resultVarExp (sessionDot $ toTxt text)
GraphQL.UVParameter mVariableInfo columnValue ->
case fmap GraphQL.getName mVariableInfo of
Nothing -> do
currentIndex <- (toInteger . length) <$> gets positionalArguments
modify' (\s -> s {
positionalArguments = positionalArguments s <> [columnValue] })
pure
(JsonValueExpression
(ColumnExpression
FieldName
{ fieldNameEntity = rowAlias
, fieldName = resultVarsAlias
})
(RootPath `FieldPath` "synthetic" `IndexPath` currentIndex))
pure (resultVarExp (syntheticIx currentIndex))
Just name -> do
modify
(\s ->
@ -213,14 +261,26 @@ prepareValueMultiplex globalVariables =
{ namedArguments =
HM.insert name columnValue (namedArguments s)
})
pure
(JsonValueExpression
(ColumnExpression
FieldName
{ fieldNameEntity = rowAlias
, fieldName = resultVarsAlias
})
(RootPath `FieldPath` "query" `FieldPath` G.unName name))
pure $ resultVarExp (queryDot $ G.unName name)
where
resultVarExp :: JsonPath -> Expression
resultVarExp =
JsonValueExpression $
ColumnExpression $
FieldName
{ fieldNameEntity = rowAlias
, fieldName = resultVarsAlias
}
queryDot :: Text -> JsonPath
queryDot name = RootPath `FieldPath` "query" `FieldPath` name
syntheticIx :: Integer -> JsonPath
syntheticIx i = (RootPath `FieldPath` "synthetic" `IndexPath` i)
sessionDot :: Text -> JsonPath
sessionDot name = RootPath `FieldPath` "session" `FieldPath` name
resultIdAlias :: T.Text

View File

@ -57,7 +57,6 @@ data UnifiedOn = UnifiedOn
{ table :: !UnifiedTableName
, column :: !Text
}
-------------------------------------------------------------------------------
-- AST types

View File

@ -3,20 +3,21 @@ url: /v1/graphql/explain
status: 200
response:
- field: user
plan:
- "SELECT ISNULL((SELECT [t_user1].[id] AS [id],\n [t_user1].[name] AS [name],\n\
\ [t_user1].[age] AS [age]\nFROM [dbo].[user] AS [t_user1]\nWHERE ((((([t_user1].[id])\
\ = ((N'1')))\n OR ((([t_user1].[id]) IS NULL)\n AND (((N'1')) IS NULL)))))\n\
FOR JSON PATH), '[]')"
- " |--Compute Scalar(DEFINE:([Expr1003]=isnull([Expr1001],CONVERT_IMPLICIT(nvarchar(max),'[]',0))))"
- " |--UDX(([t_user1].[id], [t_user1].[name], [t_user1].[age]))"
- " |--Clustered Index Seek(OBJECT:([master].[dbo].[user].[PK__user__3213E83F2F718733]
AS [t_user1]), SEEK:([t_user1].[id]=(1)) ORDERED FORWARD)"
sql:
"SELECT ISNULL((SELECT [t_user1].[id] AS [id],\n [t_user1].[name] AS\
\ [name],\n [t_user1].[age] AS [age]\nFROM [dbo].[user] AS [t_user1]\nWHERE\
\ ((((([t_user1].[id]) = ((N'1')))\n OR ((([t_user1].[id]) IS NULL)\n \
\ AND (((N'1')) IS NULL)))))\nFOR JSON PATH), '[]')"
sql: |-
SELECT ISNULL((SELECT [t_user1].[id] AS [id],
[t_user1].[name] AS [name],
[t_user1].[age] AS [age]
FROM [dbo].[user] AS [t_user1]
OUTER APPLY (SELECT *
FROM OPENJSON((N''+NCHAR(123)+''+NCHAR(34)+'positionalArguments'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(91)+''+NCHAR(93)+','+NCHAR(34)+'namedArguments'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(123)+''+NCHAR(125)+','+NCHAR(34)+'session'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(123)+''+NCHAR(34)+'x-hasura-user-id'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(34)+'1'+NCHAR(34)+''+NCHAR(125)+''+NCHAR(125)+''))
WITH ([session] NVARCHAR(MAX) AS JSON,
[namedArguments] NVARCHAR(MAX) AS JSON,
[positionalArguments] NVARCHAR(MAX) AS JSON) AS [row])
AS [row]
WHERE ((((([t_user1].[id]) = (JSON_VALUE([row].[session], (N''+NCHAR(36)+'.'+NCHAR(34)+'x-hasura-user-id'+NCHAR(34)+''))))
OR ((([t_user1].[id]) IS NULL)
AND ((JSON_VALUE([row].[session], (N''+NCHAR(36)+'.'+NCHAR(34)+'x-hasura-user-id'+NCHAR(34)+''))) IS NULL)))))
FOR JSON PATH), '[]')
query:
user:
X-Hasura-Role: user

View File

@ -3,18 +3,18 @@ url: /v1/graphql/explain
status: 200
response:
- field: user
plan:
- "SELECT ISNULL((SELECT [t_user1].[id] AS [id],\n [t_user1].[name] AS [name],\n\
\ [t_user1].[age] AS [age]\nFROM [dbo].[user] AS [t_user1]\nFOR JSON PATH),\
\ '[]')"
- " |--Compute Scalar(DEFINE:([Expr1003]=isnull([Expr1001],CONVERT_IMPLICIT(nvarchar(max),'[]',0))))"
- " |--UDX(([t_user1].[id], [t_user1].[name], [t_user1].[age]))"
- " |--Clustered Index Scan(OBJECT:([master].[dbo].[user].[PK__user__3213E83F2F718733]
AS [t_user1]))"
sql:
"SELECT ISNULL((SELECT [t_user1].[id] AS [id],\n [t_user1].[name] AS\
\ [name],\n [t_user1].[age] AS [age]\nFROM [dbo].[user] AS [t_user1]\nFOR\
\ JSON PATH), '[]')"
sql: |-
SELECT ISNULL((SELECT [t_user1].[id] AS [id],
[t_user1].[name] AS [name],
[t_user1].[age] AS [age]
FROM [dbo].[user] AS [t_user1]
OUTER APPLY (SELECT *
FROM OPENJSON((N''+NCHAR(123)+''+NCHAR(34)+'positionalArguments'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(91)+''+NCHAR(93)+','+NCHAR(34)+'namedArguments'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(123)+''+NCHAR(125)+','+NCHAR(34)+'session'+NCHAR(34)+''+NCHAR(58)+''+NCHAR(123)+''+NCHAR(125)+''+NCHAR(125)+''))
WITH ([session] NVARCHAR(MAX) AS JSON,
[namedArguments] NVARCHAR(MAX) AS JSON,
[positionalArguments] NVARCHAR(MAX) AS JSON) AS [row])
AS [row]
FOR JSON PATH), '[]')
query:
query:
query: |