{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeApplications #-} module Ema.Server where import Control.Concurrent.Async (race) import Control.Exception (catch, try) import Control.Monad.Logger import Data.LVar (LVar) import qualified Data.LVar as LVar import qualified Data.Text as T import Ema.Asset import Ema.Class (Ema (..)) import GHC.IO.Unsafe (unsafePerformIO) import NeatInterpolation (text) import qualified Network.HTTP.Types as H import qualified Network.Wai as Wai import qualified Network.Wai.Handler.Warp as Warp import qualified Network.Wai.Handler.WebSockets as WaiWs import qualified Network.Wai.Middleware.Static as Static import Network.WebSockets (ConnectionException) import qualified Network.WebSockets as WS import System.FilePath (()) import Text.Printf (printf) import UnliftIO (MonadUnliftIO) runServerWithWebSocketHotReload :: forall model route m. ( Ema model route, Show route, MonadIO m, MonadUnliftIO m, MonadLoggerIO m ) => String -> Int -> LVar model -> (model -> route -> Asset LByteString) -> m () runServerWithWebSocketHotReload host port model render = do let settings = Warp.defaultSettings & Warp.setPort port & Warp.setHost (fromString host) logger <- askLoggerIO logInfoN "============================================" logInfoN $ "Running live server at http://" <> toText host <> ":" <> show port logInfoN "============================================" liftIO $ Warp.runSettings settings $ assetsMiddleware $ WaiWs.websocketsOr WS.defaultConnectionOptions (flip runLoggingT logger . wsApp) (httpApp logger) where wsApp pendingConn = do conn :: WS.Connection <- lift $ WS.acceptRequest pendingConn logger <- askLoggerIO lift $ WS.withPingThread conn 30 (pure ()) $ flip runLoggingT logger $ do subId <- LVar.addListener model let log lvl (s :: Text) = logWithoutLoc (toText @String $ printf "WS.Client.%.2d" subId) lvl s log LevelInfo "Connected" let askClientForRoute = do msg :: Text <- liftIO $ WS.receiveData conn -- TODO: Let non-html routes pass through. let pathInfo = pathInfoFromWsMsg msg log LevelDebug $ "<~~ " <> show pathInfo pure pathInfo decodeRouteWithCurrentModel pathInfo = do val <- LVar.get model pure $ routeFromPathInfo val pathInfo sendRouteHtmlToClient pathInfo s = do decodeRouteWithCurrentModel pathInfo >>= \case Nothing -> liftIO $ WS.sendTextData conn $ emaErrorHtmlResponse decodeRouteNothingMsg Just r -> do case renderCatchingErrors logger s r of AssetStatic staticPath -> -- HACK: Websocket client should check for REDIRECT prefix. -- Not bothering with JSON to avoid having to JSON parse every HTML dump. liftIO $ WS.sendTextData conn $ "REDIRECT " <> toText staticPath AssetGenerated Html html -> liftIO $ WS.sendTextData conn $ html <> emaStatusHtml AssetGenerated Other _s -> -- HACK: Websocket client should check for REDIRECT prefix. -- Not bothering with JSON to avoid having to JSON parse every HTML dump. liftIO $ WS.sendTextData conn $ "REDIRECT " <> toText (encodeRoute s r) log LevelDebug $ " ~~> " <> show r loop = flip runLoggingT logger $ do -- Notice that we @askClientForRoute@ in succession twice here. -- The first route will be the route the client intends to observe -- for changes on. The second route, *if* it is sent, indicates -- that the client wants to *switch* to that route. This proecess -- repeats ad infinitum: i.e., the third route is for observing -- changes, the fourth route is for switching to, and so on. mWatchingRoute <- askClientForRoute -- Listen *until* either we get a new value, or the client requests -- to switch to a new route. liftIO $ do race (LVar.listenNext model subId) (runLoggingT askClientForRoute logger) >>= \res -> flip runLoggingT logger $ case res of Left newModel -> do -- The page the user is currently viewing has changed. Send -- the new HTML to them. sendRouteHtmlToClient mWatchingRoute newModel lift loop Right mNextRoute -> do -- The user clicked on a route link; send them the HTML for -- that route this time, ignoring what we are watching -- currently (we expect the user to initiate a watch route -- request immediately following this). sendRouteHtmlToClient mNextRoute =<< LVar.get model lift loop liftIO (try loop) >>= \case Right () -> pure () Left (connExc :: ConnectionException) -> do case connExc of WS.CloseRequest _ (decodeUtf8 -> reason) -> log LevelInfo $ "Closing websocket connection (reason: " <> reason <> ")" _ -> log LevelError $ "Websocket error: " <> show connExc LVar.removeListener model subId assetsMiddleware = Static.static httpApp logger req f = do flip runLoggingT logger $ do val <- LVar.get model let path = Wai.pathInfo req mr = routeFromPathInfo val path logInfoNS "HTTP" $ show path <> " as " <> show mr case mr of Nothing -> liftIO $ f $ Wai.responseLBS H.status404 [(H.hContentType, "text/plain")] $ encodeUtf8 decodeRouteNothingMsg Just r -> do case renderCatchingErrors logger val r of AssetStatic staticPath -> do let mimeType = Static.getMimeType staticPath liftIO $ f $ Wai.responseFile H.status200 [(H.hContentType, mimeType)] staticPath Nothing AssetGenerated Html html -> do let s = html <> emaStatusHtml <> wsClientShim liftIO $ f $ Wai.responseLBS H.status200 [(H.hContentType, "text/html")] s AssetGenerated Other s -> do let mimeType = Static.getMimeType $ encodeRoute val r liftIO $ f $ Wai.responseLBS H.status200 [(H.hContentType, mimeType)] s renderCatchingErrors logger m r = unsafeCatch (render m r) $ \(err :: SomeException) -> unsafePerformIO $ do -- Log the error first. flip runLoggingT logger $ logErrorNS "App" $ show @Text err pure $ AssetGenerated Html . emaErrorHtml $ show @Text err routeFromPathInfo m = decodeUrlRoute m . T.intercalate "/" -- TODO: It would be good have this also get us the stack trace. unsafeCatch :: Exception e => a -> (e -> a) -> a unsafeCatch x f = unsafePerformIO $ catch (seq x $ pure x) (pure . f) -- | A basic error response for displaying in the browser emaErrorHtmlResponse :: Text -> LByteString emaErrorHtmlResponse err = emaErrorHtml err <> emaStatusHtml emaErrorHtml :: Text -> LByteString emaErrorHtml s = encodeUtf8 $ "

Ema App threw an exception

"
      <> s
      <> "

Once you fix the source of the error, this page will automatically refresh." -- | Return the equivalent of WAI's @pathInfo@, from the raw path string -- (`document.location.pathname`) the browser sends us. pathInfoFromWsMsg :: Text -> [Text] pathInfoFromWsMsg = filter (/= "") . T.splitOn "/" . T.drop 1 -- | Decode a URL path into a route -- -- This function is used only in live server. decodeUrlRoute :: forall model route. Ema model route => model -> Text -> Maybe route decodeUrlRoute model (toString -> s) = do decodeRoute @model @route model s <|> decodeRoute @model @route model (s <> ".html") <|> decodeRoute @model @route model (s "index.html") decodeRouteNothingMsg :: Text decodeRouteNothingMsg = "Ema: 404 (decodeRoute returned Nothing)" -- Browser-side JavaScript code for interacting with the Haskell server wsClientShim :: LByteString wsClientShim = encodeUtf8 [text| |] emaStatusHtml :: LByteString emaStatusHtml = encodeUtf8 [text|

|]