Skip to content

Commit

Permalink
cut out a query
Browse files Browse the repository at this point in the history
  • Loading branch information
robx committed Feb 24, 2023
1 parent cb537e8 commit fac0b62
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 2 deletions.
5 changes: 3 additions & 2 deletions src/PostgREST/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,7 @@ runDbHandler appState mode authenticated prepared handler = do
liftEither resp

handleRequest :: AuthResult -> AppConfig -> AppState.AppState -> Bool -> Bool -> ByteString -> PgVersion -> ApiRequest -> SchemaCache -> Handler IO Wai.Response
handleRequest AuthResult{..} conf appState authenticated prepared jsonDbS pgVer apiReq@ApiRequest{..} sCache =
handleRequest _ conf appState authenticated prepared _jsonDbS pgVer apiReq@ApiRequest{..} sCache =
case (iAction, iTarget) of
(ActionRead headersOnly, TargetIdent identifier) -> do
rPlan <- liftEither $ Plan.readPlan identifier conf sCache apiReq
Expand Down Expand Up @@ -216,5 +216,6 @@ handleRequest AuthResult{..} conf appState authenticated prepared jsonDbS pgVer
where
runQuery mode query =
runDbHandler appState mode authenticated prepared $ do
Query.setPgLocals conf authClaims authRole apiReq jsonDbS pgVer
Query.select1
-- Query.setPgLocals conf authClaims authRole apiReq jsonDbS pgVer
query
4 changes: 4 additions & 0 deletions src/PostgREST/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ module PostgREST.Query
, readQuery
, singleUpsertQuery
, updateQuery
, select1
, setPgLocals
, DbHandler
) where
Expand Down Expand Up @@ -232,6 +233,9 @@ optionalRollback AppConfig{..} ApiRequest{..} = do
shouldRollback =
configDbTxAllowOverride && iPreferTransaction == Just Rollback

select1 :: DbHandler ()
select1 = lift $ SQL.sql "select 1"

-- | Runs local(transaction scoped) GUCs for every request, plus the pre-request function
setPgLocals :: AppConfig -> KM.KeyMap JSON.Value -> Text ->
ApiRequest -> ByteString -> PgVersion -> DbHandler ()
Expand Down

0 comments on commit fac0b62

Please sign in to comment.