@@ -45,11 +45,11 @@ import qualified PostgREST.Unix as Unix (installSignalHandlers)
45
45
46
46
import PostgREST.ApiRequest (Action (.. ), ApiRequest (.. ),
47
47
Mutation (.. ), Target (.. ))
48
- import PostgREST.AppState (AppState )
48
+ import PostgREST.AppState (AppState , getOTelTracer )
49
49
import PostgREST.Auth (AuthResult (.. ))
50
50
import PostgREST.Config (AppConfig (.. ))
51
51
import PostgREST.Config.PgVersion (PgVersion (.. ))
52
- import PostgREST.Error (Error )
52
+ import PostgREST.Error (Error ( .. ) )
53
53
import PostgREST.Observation (Observation (.. ))
54
54
import PostgREST.Query (DbHandler )
55
55
import PostgREST.Response.Performance (ServerTiming (.. ),
@@ -58,12 +58,15 @@ import PostgREST.SchemaCache (SchemaCache (..))
58
58
import PostgREST.SchemaCache.Routine (Routine (.. ))
59
59
import PostgREST.Version (docsVersion , prettyVersion )
60
60
61
- import qualified Data.ByteString.Char8 as BS
62
- import qualified Data.List as L
63
- import qualified Network.HTTP.Types as HTTP
64
- import qualified Network.Socket as NS
65
- import Protolude hiding (Handler )
66
- import System.TimeIt (timeItT )
61
+ import qualified Data.ByteString.Char8 as BS
62
+ import qualified Data.List as L
63
+ import qualified Network.HTTP.Types as HTTP
64
+ import qualified Network.Socket as NS
65
+ import OpenTelemetry.Instrumentation.Wai (newOpenTelemetryWaiMiddleware )
66
+ import OpenTelemetry.Trace (defaultSpanArguments )
67
+ import OpenTelemetry.Utils.Exceptions (inSpanM )
68
+ import Protolude hiding (Handler )
69
+ import System.TimeIt (timeItT )
67
70
68
71
type Handler = ExceptT Error
69
72
@@ -88,7 +91,9 @@ run appState observer = do
88
91
port <- NS. socketPort $ AppState. getSocketREST appState
89
92
observer $ AppServerPortObs port
90
93
91
- Warp. runSettingsSocket (serverSettings conf) (AppState. getSocketREST appState) app
94
+ oTelMWare <- newOpenTelemetryWaiMiddleware
95
+
96
+ Warp. runSettingsSocket (serverSettings conf) (AppState. getSocketREST appState) (oTelMWare app)
92
97
93
98
serverSettings :: AppConfig -> Warp. Settings
94
99
serverSettings AppConfig {.. } =
@@ -106,27 +111,28 @@ postgrest conf appState connWorker observer =
106
111
Logger. middleware (configLogLevel conf) $
107
112
-- fromJust can be used, because the auth middleware will **always** add
108
113
-- some AuthResult to the vault.
109
- \ req respond -> case fromJust $ Auth. getResult req of
110
- Left err -> respond $ Error. errorResponseFor err
111
- Right authResult -> do
112
- appConf <- AppState. getConfig appState -- the config must be read again because it can reload
113
- maybeSchemaCache <- AppState. getSchemaCache appState
114
- pgVer <- AppState. getPgVersion appState
115
-
116
- let
117
- eitherResponse :: IO (Either Error Wai. Response )
118
- eitherResponse =
119
- runExceptT $ postgrestResponse appState appConf maybeSchemaCache pgVer authResult req observer
120
-
121
- response <- either Error. errorResponseFor identity <$> eitherResponse
122
- -- Launch the connWorker when the connection is down. The postgrest
123
- -- function can respond successfully (with a stale schema cache) before
124
- -- the connWorker is done.
125
- when (isServiceUnavailable response) connWorker
126
- resp <- do
127
- delay <- AppState. getRetryNextIn appState
128
- return $ addRetryHint delay response
129
- respond resp
114
+ \ req respond -> inSpanM (getOTelTracer appState) " respond" defaultSpanArguments $
115
+ case fromJust $ Auth. getResult req of
116
+ Left err -> respond $ Error. errorResponseFor err
117
+ Right authResult -> do
118
+ appConf <- AppState. getConfig appState -- the config must be read again because it can reload
119
+ maybeSchemaCache <- AppState. getSchemaCache appState
120
+ pgVer <- AppState. getPgVersion appState
121
+
122
+ let
123
+ eitherResponse :: IO (Either Error Wai. Response )
124
+ eitherResponse = inSpanM (getOTelTracer appState) " eitherResponse" defaultSpanArguments $
125
+ runExceptT $ postgrestResponse appState appConf maybeSchemaCache pgVer authResult req observer
126
+
127
+ response <- either Error. errorResponseFor identity <$> eitherResponse
128
+ -- Launch the connWorker when the connection is down. The postgrest
129
+ -- function can respond successfully (with a stale schema cache) before
130
+ -- the connWorker is done.
131
+ when (isServiceUnavailable response) connWorker
132
+ resp <- do
133
+ delay <- AppState. getRetryNextIn appState
134
+ return $ addRetryHint delay response
135
+ respond resp
130
136
131
137
postgrestResponse
132
138
:: AppState. AppState
@@ -172,54 +178,54 @@ handleRequest :: AuthResult -> AppConfig -> AppState.AppState -> Bool -> Bool ->
172
178
handleRequest AuthResult {.. } conf appState authenticated prepared pgVer apiReq@ ApiRequest {.. } sCache jwtTime parseTime observer =
173
179
case (iAction, iTarget) of
174
180
(ActionRead headersOnly, TargetIdent identifier) -> do
175
- (planTime', wrPlan) <- withTiming $ liftEither $ Plan. wrappedReadPlan identifier conf sCache apiReq
176
- (txTime', resultSet) <- withTiming $ runQuery roleIsoLvl mempty (Plan. wrTxMode wrPlan) $ Query. readQuery wrPlan conf apiReq
177
- (respTime', pgrst) <- withTiming $ liftEither $ Response. readResponse wrPlan headersOnly identifier apiReq resultSet
181
+ (planTime', wrPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. wrappedReadPlan identifier conf sCache apiReq
182
+ (txTime', resultSet) <- withOTel " query " $ withTiming $ runQuery roleIsoLvl [] (Plan. wrTxMode wrPlan) $ Query. readQuery wrPlan conf apiReq
183
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. readResponse wrPlan headersOnly identifier apiReq resultSet
178
184
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
179
185
180
186
(ActionMutate MutationCreate , TargetIdent identifier) -> do
181
- (planTime', mrPlan) <- withTiming $ liftEither $ Plan. mutateReadPlan MutationCreate apiReq identifier conf sCache
182
- (txTime', resultSet) <- withTiming $ runQuery roleIsoLvl mempty (Plan. mrTxMode mrPlan) $ Query. createQuery mrPlan apiReq conf
183
- (respTime', pgrst) <- withTiming $ liftEither $ Response. createResponse identifier mrPlan apiReq resultSet
187
+ (planTime', mrPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. mutateReadPlan MutationCreate apiReq identifier conf sCache
188
+ (txTime', resultSet) <- withOTel " query " $ withTiming $ runQuery roleIsoLvl [] (Plan. mrTxMode mrPlan) $ Query. createQuery mrPlan apiReq conf
189
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. createResponse identifier mrPlan apiReq resultSet
184
190
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
185
191
186
192
(ActionMutate MutationUpdate , TargetIdent identifier) -> do
187
- (planTime', mrPlan) <- withTiming $ liftEither $ Plan. mutateReadPlan MutationUpdate apiReq identifier conf sCache
188
- (txTime', resultSet) <- withTiming $ runQuery roleIsoLvl mempty (Plan. mrTxMode mrPlan) $ Query. updateQuery mrPlan apiReq conf
189
- (respTime', pgrst) <- withTiming $ liftEither $ Response. updateResponse mrPlan apiReq resultSet
193
+ (planTime', mrPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. mutateReadPlan MutationUpdate apiReq identifier conf sCache
194
+ (txTime', resultSet) <- withOTel " query " $ withTiming $ runQuery roleIsoLvl [] (Plan. mrTxMode mrPlan) $ Query. updateQuery mrPlan apiReq conf
195
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. updateResponse mrPlan apiReq resultSet
190
196
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
191
197
192
198
(ActionMutate MutationSingleUpsert , TargetIdent identifier) -> do
193
- (planTime', mrPlan) <- withTiming $ liftEither $ Plan. mutateReadPlan MutationSingleUpsert apiReq identifier conf sCache
194
- (txTime', resultSet) <- withTiming $ runQuery roleIsoLvl mempty (Plan. mrTxMode mrPlan) $ Query. singleUpsertQuery mrPlan apiReq conf
195
- (respTime', pgrst) <- withTiming $ liftEither $ Response. singleUpsertResponse mrPlan apiReq resultSet
199
+ (planTime', mrPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. mutateReadPlan MutationSingleUpsert apiReq identifier conf sCache
200
+ (txTime', resultSet) <- withOTel " query " $ withTiming $ runQuery roleIsoLvl [] (Plan. mrTxMode mrPlan) $ Query. singleUpsertQuery mrPlan apiReq conf
201
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. singleUpsertResponse mrPlan apiReq resultSet
196
202
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
197
203
198
204
(ActionMutate MutationDelete , TargetIdent identifier) -> do
199
- (planTime', mrPlan) <- withTiming $ liftEither $ Plan. mutateReadPlan MutationDelete apiReq identifier conf sCache
200
- (txTime', resultSet) <- withTiming $ runQuery roleIsoLvl mempty (Plan. mrTxMode mrPlan) $ Query. deleteQuery mrPlan apiReq conf
201
- (respTime', pgrst) <- withTiming $ liftEither $ Response. deleteResponse mrPlan apiReq resultSet
205
+ (planTime', mrPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. mutateReadPlan MutationDelete apiReq identifier conf sCache
206
+ (txTime', resultSet) <- withOTel " query " $ withTiming $ runQuery roleIsoLvl [] (Plan. mrTxMode mrPlan) $ Query. deleteQuery mrPlan apiReq conf
207
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. deleteResponse mrPlan apiReq resultSet
202
208
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
203
209
204
210
(ActionInvoke invMethod, TargetProc identifier _) -> do
205
- (planTime', cPlan) <- withTiming $ liftEither $ Plan. callReadPlan identifier conf sCache apiReq invMethod
206
- (txTime', resultSet) <- withTiming $ runQuery (fromMaybe roleIsoLvl $ pdIsoLvl (Plan. crProc cPlan)) (pdFuncSettings $ Plan. crProc cPlan) (Plan. crTxMode cPlan) $ Query. invokeQuery (Plan. crProc cPlan) cPlan apiReq conf pgVer
207
- (respTime', pgrst) <- withTiming $ liftEither $ Response. invokeResponse cPlan invMethod (Plan. crProc cPlan) apiReq resultSet
211
+ (planTime', cPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. callReadPlan identifier conf sCache apiReq invMethod
212
+ (txTime', resultSet) <- withOTel " query " $ withTiming $ runQuery (fromMaybe roleIsoLvl $ pdIsoLvl (Plan. crProc cPlan)) (pdFuncSettings $ Plan. crProc cPlan) (Plan. crTxMode cPlan) $ Query. invokeQuery (Plan. crProc cPlan) cPlan apiReq conf pgVer
213
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. invokeResponse cPlan invMethod (Plan. crProc cPlan) apiReq resultSet
208
214
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
209
215
210
216
(ActionInspect headersOnly, TargetDefaultSpec tSchema) -> do
211
- (planTime', iPlan) <- withTiming $ liftEither $ Plan. inspectPlan apiReq
212
- (txTime', oaiResult) <- withTiming $ runQuery roleIsoLvl mempty (Plan. ipTxmode iPlan) $ Query. openApiQuery sCache pgVer conf tSchema
213
- (respTime', pgrst) <- withTiming $ liftEither $ Response. openApiResponse (T. decodeUtf8 prettyVersion, docsVersion) headersOnly oaiResult conf sCache iSchema iNegotiatedByProfile
217
+ (planTime', iPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. inspectPlan apiReq
218
+ (txTime', oaiResult) <- withOTel " query " $ withTiming $ runQuery roleIsoLvl [] (Plan. ipTxmode iPlan) $ Query. openApiQuery sCache pgVer conf tSchema
219
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. openApiResponse (T. decodeUtf8 prettyVersion, docsVersion) headersOnly oaiResult conf sCache iSchema iNegotiatedByProfile
214
220
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' txTime' respTime') pgrst
215
221
216
222
(ActionInfo , TargetIdent identifier) -> do
217
- (respTime', pgrst) <- withTiming $ liftEither $ Response. infoIdentResponse identifier sCache
223
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. infoIdentResponse identifier sCache
218
224
return $ pgrstResponse (ServerTiming jwtTime parseTime Nothing Nothing respTime') pgrst
219
225
220
226
(ActionInfo , TargetProc identifier _) -> do
221
- (planTime', cPlan) <- withTiming $ liftEither $ Plan. callReadPlan identifier conf sCache apiReq ApiRequest. InvHead
222
- (respTime', pgrst) <- withTiming $ liftEither $ Response. infoProcResponse (Plan. crProc cPlan)
227
+ (planTime', cPlan) <- withOTel " plan " $ withTiming $ liftEither $ Plan. callReadPlan identifier conf sCache apiReq ApiRequest. InvHead
228
+ (respTime', pgrst) <- withOTel " response " $ withTiming $ liftEither $ Response. infoProcResponse (Plan. crProc cPlan)
223
229
return $ pgrstResponse (ServerTiming jwtTime parseTime planTime' Nothing respTime') pgrst
224
230
225
231
(ActionInfo , TargetDefaultSpec _) -> do
@@ -244,6 +250,8 @@ handleRequest AuthResult{..} conf appState authenticated prepared pgVer apiReq@A
244
250
245
251
withTiming = calcTiming $ configServerTimingEnabled conf
246
252
253
+ withOTel label = inSpanM (getOTelTracer appState) label defaultSpanArguments
254
+
247
255
calcTiming :: Bool -> Handler IO a -> Handler IO (Maybe Double , a )
248
256
calcTiming timingEnabled f = if timingEnabled
249
257
then do
0 commit comments