Skip to content

Commit f099ce3

Browse files
committed
refactor: add observation module
1 parent fac7aca commit f099ce3

File tree

8 files changed

+255
-141
lines changed

8 files changed

+255
-141
lines changed

postgrest.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,7 @@ library
5454
PostgREST.Error
5555
PostgREST.Logger
5656
PostgREST.MediaType
57+
PostgREST.Observation
5758
PostgREST.Query
5859
PostgREST.Query.QueryBuilder
5960
PostgREST.Query.SqlFragment

src/PostgREST/Admin.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -16,32 +16,32 @@ import qualified Data.ByteString.Lazy as LBS
1616
import Network.Socket
1717
import Network.Socket.ByteString
1818

19-
import PostgREST.AppState (AppState)
20-
import PostgREST.Config (AppConfig (..))
19+
import PostgREST.AppState (AppState)
20+
import PostgREST.Config (AppConfig (..))
21+
import PostgREST.Observation (Observation (..))
2122

2223
import qualified PostgREST.AppState as AppState
2324
import qualified PostgREST.Config as Config
2425

2526
import Protolude
26-
import Protolude.Partial (fromJust)
2727

28-
runAdmin :: AppConfig -> AppState -> Warp.Settings -> IO ()
29-
runAdmin conf@AppConfig{configAdminServerPort} appState settings =
28+
runAdmin :: AppConfig -> AppState -> Warp.Settings -> (Observation -> IO ()) -> IO ()
29+
runAdmin conf@AppConfig{configAdminServerPort} appState settings observer =
3030
whenJust (AppState.getSocketAdmin appState) $ \adminSocket -> do
31-
AppState.logWithZTime appState $ "Admin server listening on port " <> show (fromIntegral (fromJust configAdminServerPort) :: Integer)
31+
observer $ AdminStartObs configAdminServerPort
3232
void . forkIO $ Warp.runSettingsSocket settings adminSocket adminApp
3333
where
34-
adminApp = admin appState conf
34+
adminApp = admin appState conf observer
3535

3636
-- | PostgREST admin application
37-
admin :: AppState.AppState -> AppConfig -> Wai.Application
38-
admin appState appConfig req respond = do
37+
admin :: AppState.AppState -> AppConfig -> (Observation -> IO ()) -> Wai.Application
38+
admin appState appConfig observer req respond = do
3939
isMainAppReachable <- isRight <$> reachMainApp (AppState.getSocketREST appState)
4040
isSchemaCacheLoaded <- isJust <$> AppState.getSchemaCache appState
4141
isConnectionUp <-
4242
if configDbChannelEnabled appConfig
4343
then AppState.getIsListenerOn appState
44-
else isRight <$> AppState.usePool appState appConfig (SQL.sql "SELECT 1")
44+
else isRight <$> AppState.usePool appState appConfig (SQL.sql "SELECT 1") observer
4545

4646
case Wai.pathInfo req of
4747
["ready"] ->

src/PostgREST/App.hs

Lines changed: 25 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ import PostgREST.Auth (AuthResult (..))
5050
import PostgREST.Config (AppConfig (..))
5151
import PostgREST.Config.PgVersion (PgVersion (..))
5252
import PostgREST.Error (Error)
53+
import PostgREST.Observation (Observation (..))
5354
import PostgREST.Query (DbHandler)
5455
import PostgREST.Response.Performance (ServerTiming (..),
5556
serverTimingHeader)
@@ -66,26 +67,26 @@ import System.TimeIt (timeItT)
6667

6768
type Handler = ExceptT Error
6869

69-
run :: AppState -> IO ()
70-
run appState = do
71-
AppState.logWithZTime appState $ "Starting PostgREST " <> T.decodeUtf8 prettyVersion <> "..."
70+
run :: AppState -> (Observation -> IO ()) -> IO ()
71+
run appState observer = do
72+
observer $ AppStartObs prettyVersion
7273

7374
conf@AppConfig{..} <- AppState.getConfig appState
7475
AppState.connectionWorker appState -- Loads the initial SchemaCache
75-
Unix.installSignalHandlers (AppState.getMainThreadId appState) (AppState.connectionWorker appState) (AppState.reReadConfig False appState)
76+
Unix.installSignalHandlers (AppState.getMainThreadId appState) (AppState.connectionWorker appState) (AppState.reReadConfig False appState observer)
7677
-- reload schema cache + config on NOTIFY
77-
AppState.runListener conf appState
78+
AppState.runListener conf appState observer
7879

79-
Admin.runAdmin conf appState $ serverSettings conf
80+
Admin.runAdmin conf appState (serverSettings conf) observer
8081

81-
let app = postgrest conf appState (AppState.connectionWorker appState)
82+
let app = postgrest conf appState (AppState.connectionWorker appState) observer
8283

83-
what <- case configServerUnixSocket of
84-
Just path -> pure $ "unix socket " <> show path
84+
case configServerUnixSocket of
85+
Just path -> do
86+
observer $ AppServerUnixObs path
8587
Nothing -> do
8688
port <- NS.socketPort $ AppState.getSocketREST appState
87-
pure $ "port " <> show port
88-
AppState.logWithZTime appState $ "Listening on " <> what
89+
observer $ AppServerPortObs port
8990

9091
Warp.runSettingsSocket (serverSettings conf) (AppState.getSocketREST appState) app
9192

@@ -97,8 +98,8 @@ serverSettings AppConfig{..} =
9798
& setServerName ("postgrest/" <> prettyVersion)
9899

99100
-- | PostgREST application
100-
postgrest :: AppConfig -> AppState.AppState -> IO () -> Wai.Application
101-
postgrest conf appState connWorker =
101+
postgrest :: AppConfig -> AppState.AppState -> IO () -> (Observation -> IO ()) -> Wai.Application
102+
postgrest conf appState connWorker observer =
102103
traceHeaderMiddleware conf .
103104
Cors.middleware (configServerCorsAllowedOrigins conf) .
104105
Auth.middleware appState .
@@ -115,7 +116,7 @@ postgrest conf appState connWorker =
115116
let
116117
eitherResponse :: IO (Either Error Wai.Response)
117118
eitherResponse =
118-
runExceptT $ postgrestResponse appState appConf maybeSchemaCache pgVer authResult req
119+
runExceptT $ postgrestResponse appState appConf maybeSchemaCache pgVer authResult req observer
119120

120121
response <- either Error.errorResponseFor identity <$> eitherResponse
121122
-- Launch the connWorker when the connection is down. The postgrest
@@ -134,8 +135,9 @@ postgrestResponse
134135
-> PgVersion
135136
-> AuthResult
136137
-> Wai.Request
138+
-> (Observation -> IO ())
137139
-> Handler IO Wai.Response
138-
postgrestResponse appState conf@AppConfig{..} maybeSchemaCache pgVer authResult@AuthResult{..} req = do
140+
postgrestResponse appState conf@AppConfig{..} maybeSchemaCache pgVer authResult@AuthResult{..} req observer = do
139141
sCache <-
140142
case maybeSchemaCache of
141143
Just sCache ->
@@ -151,22 +153,23 @@ postgrestResponse appState conf@AppConfig{..} maybeSchemaCache pgVer authResult@
151153
ApiRequest.userApiRequest conf req body sCache
152154

153155
let jwtTime = if configServerTimingEnabled then Auth.getJwtDur req else Nothing
154-
handleRequest authResult conf appState (Just authRole /= configDbAnonRole) configDbPreparedStatements pgVer apiRequest sCache jwtTime parseTime
156+
handleRequest authResult conf appState (Just authRole /= configDbAnonRole) configDbPreparedStatements pgVer apiRequest sCache jwtTime parseTime observer
155157

156-
runDbHandler :: AppState.AppState -> AppConfig -> SQL.IsolationLevel -> SQL.Mode -> Bool -> Bool -> DbHandler b -> Handler IO b
157-
runDbHandler appState config isoLvl mode authenticated prepared handler = do
158+
runDbHandler :: AppState.AppState -> AppConfig -> SQL.IsolationLevel -> SQL.Mode -> Bool -> Bool -> (Observation -> IO ()) -> DbHandler b -> Handler IO b
159+
runDbHandler appState config isoLvl mode authenticated prepared observer handler = do
158160
dbResp <- lift $ do
159161
let transaction = if prepared then SQL.transaction else SQL.unpreparedTransaction
160-
AppState.usePool appState config . transaction isoLvl mode $ runExceptT handler
162+
AppState.usePool appState config (transaction isoLvl mode $ runExceptT handler) observer
161163

162164
resp <-
163165
liftEither . mapLeft Error.PgErr $
164166
mapLeft (Error.PgError authenticated) dbResp
165167

166168
liftEither resp
167169

168-
handleRequest :: AuthResult -> AppConfig -> AppState.AppState -> Bool -> Bool -> PgVersion -> ApiRequest -> SchemaCache -> Maybe Double -> Maybe Double -> Handler IO Wai.Response
169-
handleRequest AuthResult{..} conf appState authenticated prepared pgVer apiReq@ApiRequest{..} sCache jwtTime parseTime =
170+
handleRequest :: AuthResult -> AppConfig -> AppState.AppState -> Bool -> Bool -> PgVersion -> ApiRequest -> SchemaCache ->
171+
Maybe Double -> Maybe Double -> (Observation -> IO ()) -> Handler IO Wai.Response
172+
handleRequest AuthResult{..} conf appState authenticated prepared pgVer apiReq@ApiRequest{..} sCache jwtTime parseTime observer =
170173
case (iAction, iTarget) of
171174
(ActionRead headersOnly, TargetIdent identifier) -> do
172175
(planTime', wrPlan) <- withTiming $ liftEither $ Plan.wrappedReadPlan identifier conf sCache apiReq
@@ -231,7 +234,7 @@ handleRequest AuthResult{..} conf appState authenticated prepared pgVer apiReq@A
231234
roleSettings = fromMaybe mempty (HM.lookup authRole $ configRoleSettings conf)
232235
roleIsoLvl = HM.findWithDefault SQL.ReadCommitted authRole $ configRoleIsoLvl conf
233236
runQuery isoLvl funcSets mode query =
234-
runDbHandler appState conf isoLvl mode authenticated prepared $ do
237+
runDbHandler appState conf isoLvl mode authenticated prepared observer $ do
235238
Query.setPgLocals conf authClaims authRole (HM.toList roleSettings) funcSets apiReq
236239
Query.runPreReq conf
237240
query

0 commit comments

Comments
 (0)