@@ -11,7 +11,6 @@ module PostgREST.Query
1111import qualified Data.Aeson as JSON
1212import qualified Data.Aeson.KeyMap as KM
1313import qualified Data.ByteString as BS
14- import qualified Data.ByteString.Lazy.Char8 as LBS
1514import qualified Data.HashMap.Strict as HM
1615import qualified Data.Set as S
1716import qualified Hasql.Decoders as HD
@@ -22,6 +21,7 @@ import qualified Hasql.Transaction as SQL
2221import qualified Hasql.Transaction.Sessions as SQL
2322
2423import qualified PostgREST.Error as Error
24+ import qualified PostgREST.Query.PreQuery as PreQuery
2525import qualified PostgREST.Query.QueryBuilder as QueryBuilder
2626import qualified PostgREST.Query.Statements as Statements
2727import qualified PostgREST.SchemaCache as SchemaCache
@@ -32,7 +32,6 @@ import PostgREST.ApiRequest (ApiRequest (..),
3232import PostgREST.ApiRequest.Preferences (PreferCount (.. ),
3333 PreferHandling (.. ),
3434 PreferMaxAffected (.. ),
35- PreferTimezone (.. ),
3635 PreferTransaction (.. ),
3736 Preferences (.. ),
3837 shouldCount )
@@ -48,11 +47,6 @@ import PostgREST.Plan (ActionPlan (..),
4847 InfoPlan (.. ),
4948 InspectPlan (.. ))
5049import PostgREST.Plan.MutatePlan (MutatePlan (.. ))
51- import PostgREST.Query.SqlFragment (escapeIdentList , fromQi ,
52- intercalateSnippet ,
53- setConfigWithConstantName ,
54- setConfigWithConstantNameJSON ,
55- setConfigWithDynamicName )
5650import PostgREST.Query.Statements (ResultSet (.. ))
5751import PostgREST.SchemaCache (SchemaCache (.. ))
5852import PostgREST.SchemaCache.Identifiers (QualifiedIdentifier (.. ))
@@ -90,8 +84,8 @@ query config AuthResult{..} apiReq (Db plan) sCache =
9084 txMode = planTxMode plan
9185 (mainActionQuery, mainSQLQuery) = actionQuery plan config apiReq sCache
9286 dbHandler = do
93- setPgLocals plan config authClaims authRole apiReq
94- runPreReq config
87+ runTxVarQuery plan config authClaims authRole apiReq
88+ runPreReqQuery config
9589 mainActionQuery
9690
9791planTxMode :: DbActionPlan -> SQL. Mode
@@ -263,38 +257,17 @@ optionalRollback AppConfig{..} ApiRequest{iPreferences=Preferences{..}} = do
263257 shouldRollback =
264258 preferTransaction == Just Rollback
265259
266- -- | Set transaction scoped settings
267- setPgLocals :: DbActionPlan -> AppConfig -> KM. KeyMap JSON. Value -> BS. ByteString -> ApiRequest -> DbHandler ()
268- setPgLocals dbActPlan AppConfig {.. } claims role ApiRequest {.. } = lift $
260+ runTxVarQuery :: DbActionPlan -> AppConfig -> KM. KeyMap JSON. Value -> BS. ByteString -> ApiRequest -> DbHandler ()
261+ runTxVarQuery dbActPlan conf@ AppConfig {.. } claims role apireq = lift $
269262 SQL. statement mempty $ SQL. dynamicallyParameterized
270- -- To ensure `GRANT SET ON PARAMETER <superuser_setting> TO authenticator` works, the role settings must be set before the impersonated role.
271- -- Otherwise the GRANT SET would have to be applied to the impersonated role. See https://github.com/PostgREST/postgrest/issues/3045
272- (" select " <> intercalateSnippet " , " (searchPathSql : roleSettingsSql ++ roleSql ++ claimsSql ++ [methodSql, pathSql] ++ headersSql ++ cookiesSql ++ timezoneSql ++ funcSettingsSql ++ appSettingsSql))
263+ (PreQuery. txVarQuery dbActPlan conf claims role apireq)
273264 HD. noResult configDbPreparedStatements
274- where
275- methodSql = setConfigWithConstantName (" request.method" , iMethod)
276- pathSql = setConfigWithConstantName (" request.path" , iPath)
277- headersSql = setConfigWithConstantNameJSON " request.headers" iHeaders
278- cookiesSql = setConfigWithConstantNameJSON " request.cookies" iCookies
279- claimsSql = [setConfigWithConstantName (" request.jwt.claims" , LBS. toStrict $ JSON. encode claims)]
280- roleSql = [setConfigWithConstantName (" role" , role)]
281- roleSettingsSql = setConfigWithDynamicName <$> HM. toList (fromMaybe mempty $ HM. lookup role configRoleSettings)
282- appSettingsSql = setConfigWithDynamicName . join bimap toUtf8 <$> configAppSettings
283- timezoneSql = maybe mempty (\ (PreferTimezone tz) -> [setConfigWithConstantName (" timezone" , tz)]) $ preferTimezone iPreferences
284- funcSettingsSql = setConfigWithDynamicName . join bimap toUtf8 <$> funcSettings
285- searchPathSql =
286- let schemas = escapeIdentList (iSchema : configDbExtraSearchPath) in
287- setConfigWithConstantName (" search_path" , schemas)
288- funcSettings = case dbActPlan of
289- DbCall CallReadPlan {crProc} -> pdFuncSettings crProc
290- _ -> mempty
291265
292- -- | Runs the pre-request function.
293- runPreReq :: AppConfig -> DbHandler ()
294- runPreReq conf = lift $ traverse_ (SQL. statement mempty . stmt) (configDbPreRequest conf)
266+ runPreReqQuery :: AppConfig -> DbHandler ()
267+ runPreReqQuery conf = lift $ traverse_ (SQL. statement mempty . stmt) (configDbPreRequest conf)
295268 where
296269 stmt req = SQL. dynamicallyParameterized
297- (" select " <> fromQi req <> " () " )
270+ (PreQuery. preReqQuery req)
298271 HD. noResult
299272 (configDbPreparedStatements conf)
300273
0 commit comments