{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_HADDOCK prune #-}
module Core.Webserver.Warp (
Port,
launchWebserver,
requestContextKey,
contextFromRequest,
) where
import qualified Control.Exception.Safe as Safe (catch)
import Core.Program.Context
import Core.Program.Logging
import Core.System.Base
import Core.Telemetry.Observability
import Core.Text.Rope
import qualified Data.ByteString.Lazy as L
import qualified Data.Vault.Lazy as Vault
import Network.HTTP.Types (
hContentType,
status400,
status413,
status431,
status500,
statusCode,
)
import Network.HTTP2.Frame (
ErrorCodeId (UnknownErrorCode),
HTTP2Error (ConnectionError),
)
import Network.Wai
import Network.Wai.Handler.Warp (InvalidRequest, Port)
import qualified Network.Wai.Handler.Warp as Warp
launchWebserver :: Port -> Application -> Program τ ()
launchWebserver :: Port -> Application -> Program τ ()
launchWebserver Port
port Application
application = do
Context τ
context <- Program τ (Context τ)
forall τ. Program τ (Context τ)
getContext
let settings :: Settings
settings =
(Maybe Request -> SomeException -> IO ()) -> Settings -> Settings
Warp.setOnException
(Context τ -> Maybe Request -> SomeException -> IO ()
forall τ. Context τ -> Maybe Request -> SomeException -> IO ()
onExceptionHandler Context τ
context)
(Settings -> Settings)
-> (Settings -> Settings) -> Settings -> Settings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Port -> Settings -> Settings
Warp.setPort Port
port
(Settings -> Settings) -> Settings -> Settings
forall a b. (a -> b) -> a -> b
$ Settings
Warp.defaultSettings
IO () -> Program τ ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Program τ ()) -> IO () -> Program τ ()
forall a b. (a -> b) -> a -> b
$ do
Settings -> Application -> IO ()
Warp.runSettings
Settings
settings
( Context τ -> Application -> Application
forall τ. Context τ -> Application -> Application
loggingMiddleware
Context τ
context
Application
application
)
requestContextKey :: forall t. Vault.Key (Context t)
requestContextKey :: Key (Context t)
requestContextKey = IO (Key (Context t)) -> Key (Context t)
forall a. IO a -> a
unsafePerformIO IO (Key (Context t))
forall a. IO (Key a)
Vault.newKey
{-# NOINLINE requestContextKey #-}
contextFromRequest :: forall t. Request -> Maybe (Context t)
contextFromRequest :: Request -> Maybe (Context t)
contextFromRequest Request
request = Key (Context t) -> Vault -> Maybe (Context t)
forall a. Key a -> Vault -> Maybe a
Vault.lookup Key (Context t)
forall t. Key (Context t)
requestContextKey (Request -> Vault
vault Request
request)
loggingMiddleware :: Context τ -> Application -> Application
loggingMiddleware :: Context τ -> Application -> Application
loggingMiddleware (Context τ
context0 :: Context τ) Application
application Request
request Response -> IO ResponseReceived
sendResponse = do
let path :: Rope
path = ByteString -> Rope
forall α. Textual α => α -> Rope
intoRope (Request -> ByteString
rawPathInfo Request
request)
Context τ -> Program τ ResponseReceived -> IO ResponseReceived
forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context0 (Program τ ResponseReceived -> IO ResponseReceived)
-> Program τ ResponseReceived -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ do
Program τ ResponseReceived -> Program τ ResponseReceived
forall τ α. Program τ α -> Program τ α
beginTrace (Program τ ResponseReceived -> Program τ ResponseReceived)
-> Program τ ResponseReceived -> Program τ ResponseReceived
forall a b. (a -> b) -> a -> b
$ do
Rope -> Program τ ResponseReceived -> Program τ ResponseReceived
forall z a. Rope -> Program z a -> Program z a
encloseSpan Rope
path (Program τ ResponseReceived -> Program τ ResponseReceived)
-> Program τ ResponseReceived -> Program τ ResponseReceived
forall a b. (a -> b) -> a -> b
$ do
Context τ
context1 <- Program τ (Context τ)
forall τ. Program τ (Context τ)
getContext
let query :: Rope
query = ByteString -> Rope
forall α. Textual α => α -> Rope
intoRope (Request -> ByteString
rawQueryString Request
request)
path' :: Rope
path' = Rope
path Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Rope
query
method :: Rope
method = ByteString -> Rope
forall α. Textual α => α -> Rope
intoRope (Request -> ByteString
requestMethod Request
request)
IO ResponseReceived -> Program τ ResponseReceived
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ResponseReceived -> Program τ ResponseReceived)
-> IO ResponseReceived -> Program τ ResponseReceived
forall a b. (a -> b) -> a -> b
$ do
let vault' :: Vault
vault' = Key (Context τ) -> Context τ -> Vault -> Vault
forall a. Key a -> a -> Vault -> Vault
Vault.insert (Key (Context τ)
forall t. Key (Context t)
requestContextKey @τ) Context τ
context1 (Request -> Vault
vault Request
request)
request' :: Request
request' = Request
request{vault :: Vault
vault = Vault
vault'}
IO ResponseReceived
-> (SomeException -> IO ResponseReceived) -> IO ResponseReceived
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
Safe.catch
( Application
application Request
request' ((Response -> IO ResponseReceived) -> IO ResponseReceived)
-> (Response -> IO ResponseReceived) -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ \Response
response -> do
let status :: Rope
status = String -> Rope
forall α. Textual α => α -> Rope
intoRope (Port -> String
forall a. Show a => a -> String
show (Status -> Port
statusCode (Response -> Status
responseStatus Response
response)))
Context τ -> Program τ () -> IO ()
forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context1 (Program τ () -> IO ()) -> Program τ () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
[MetricValue] -> Program τ ()
forall τ. [MetricValue] -> Program τ ()
telemetry
[ Rope -> Rope -> MetricValue
forall σ. Telemetry σ => Rope -> σ -> MetricValue
metric Rope
"request.method" Rope
method
, Rope -> Rope -> MetricValue
forall σ. Telemetry σ => Rope -> σ -> MetricValue
metric Rope
"request.path" Rope
path'
, Rope -> Rope -> MetricValue
forall σ. Telemetry σ => Rope -> σ -> MetricValue
metric Rope
"response.status_code" Rope
status
]
Response -> IO ResponseReceived
sendResponse Response
response
)
( \(SomeException
e :: SomeException) -> do
let text :: Rope
text = String -> Rope
forall α. Textual α => α -> Rope
intoRope (SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
e)
Context τ -> Program τ () -> IO ()
forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context1 (Program τ () -> IO ()) -> Program τ () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Rope -> Program τ ()
forall τ. Rope -> Program τ ()
warn Rope
"Trapped internal exception"
Rope -> Rope -> Program τ ()
forall τ. Rope -> Rope -> Program τ ()
debug Rope
"e" Rope
text
[MetricValue] -> Program τ ()
forall τ. [MetricValue] -> Program τ ()
telemetry
[ Rope -> Rope -> MetricValue
forall σ. Telemetry σ => Rope -> σ -> MetricValue
metric Rope
"request.method" Rope
method
, Rope -> Rope -> MetricValue
forall σ. Telemetry σ => Rope -> σ -> MetricValue
metric Rope
"request.path" Rope
path'
, Rope -> Rope -> MetricValue
forall σ. Telemetry σ => Rope -> σ -> MetricValue
metric Rope
"error" Rope
text
]
Response -> IO ResponseReceived
sendResponse (SomeException -> Response
onExceptionResponse SomeException
e)
)
onExceptionResponse :: SomeException -> Response
onExceptionResponse :: SomeException -> Response
onExceptionResponse SomeException
e
| Just (InvalidRequest
_ :: InvalidRequest) <-
SomeException -> Maybe InvalidRequest
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e =
Status -> ResponseHeaders -> ByteString -> Response
responseLBS
Status
status400
[(HeaderName
hContentType, ByteString
"text/plain; charset=utf-8")]
(Rope -> ByteString
forall α. Textual α => Rope -> α
fromRope (Rope
"Bad Request\n" Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> String -> Rope
forall α. Textual α => α -> Rope
intoRope (SomeException -> String
forall e. Exception e => e -> String
displayException SomeException
e)))
| Just (ConnectionError (UnknownErrorCode ErrorCode
413) ByteString
t) <-
SomeException -> Maybe HTTP2Error
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e =
Status -> ResponseHeaders -> ByteString -> Response
responseLBS
Status
status413
[(HeaderName
hContentType, ByteString
"text/plain; charset=utf-8")]
(ByteString -> ByteString
L.fromStrict ByteString
t)
| Just (ConnectionError (UnknownErrorCode ErrorCode
431) ByteString
t) <-
SomeException -> Maybe HTTP2Error
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e =
Status -> ResponseHeaders -> ByteString -> Response
responseLBS
Status
status431
[(HeaderName
hContentType, ByteString
"text/plain; charset=utf-8")]
(ByteString -> ByteString
L.fromStrict ByteString
t)
| Bool
otherwise =
Status -> ResponseHeaders -> ByteString -> Response
responseLBS
Status
status500
[(HeaderName
hContentType, ByteString
"text/plain; charset=utf-8")]
ByteString
"Internal Server Error"
onExceptionHandler :: Context τ -> Maybe Request -> SomeException -> IO ()
onExceptionHandler :: Context τ -> Maybe Request -> SomeException -> IO ()
onExceptionHandler Context τ
context Maybe Request
possibleRequest SomeException
e = do
Context τ -> Program τ () -> IO ()
forall τ α. Context τ -> Program τ α -> IO α
subProgram Context τ
context (Program τ () -> IO ()) -> Program τ () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Rope -> Program τ ()
forall τ. Rope -> Program τ ()
critical Rope
"Exception escaped webserver"
Rope -> SomeException -> Program τ ()
forall α τ. Show α => Rope -> α -> Program τ ()
debugS Rope
"e" SomeException
e
case Maybe Request
possibleRequest of
Maybe Request
Nothing -> () -> Program τ ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just Request
request ->
let line :: Rope
line = ByteString -> Rope
forall α. Textual α => α -> Rope
intoRope (Request -> ByteString
requestMethod Request
request) Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Rope
" " Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> ByteString -> Rope
forall α. Textual α => α -> Rope
intoRope (Request -> ByteString
rawPathInfo Request
request) Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> ByteString -> Rope
forall α. Textual α => α -> Rope
intoRope (Request -> ByteString
rawQueryString Request
request)
in Rope -> Rope -> Program τ ()
forall τ. Rope -> Rope -> Program τ ()
debug Rope
"request" Rope
line