{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeApplications #-} -- | TODO: Refactor this module 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.Class (Ema (decodeRoute, staticAssets), MonadEma) 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 Relude.Extra.Foldable1 (foldl1') import Text.Printf (printf) runServerWithWebSocketHotReload :: forall model route m. (Ema model route, Show route, MonadEma m) => Int -> LVar model -> (model -> route -> LByteString) -> m () runServerWithWebSocketHotReload port model render = do let settings = Warp.setPort port Warp.defaultSettings logger <- askLoggerIO logInfoN $ "Launching Ema at http://localhost:" <> show port 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 let r = msg & pathInfoFromWsMsg & routeFromPathInfo & fromMaybe (error "invalid route from ws") log LevelDebug $ "<~~ " <> show r pure r sendRouteHtmlToClient r s = do liftIO $ WS.sendTextData conn $ renderWithEmaHtmlShims logger 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. watchingRoute <- 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 newHtml -> do -- The page the user is currently viewing has changed. Send -- the new HTML to them. sendRouteHtmlToClient watchingRoute newHtml lift loop Right nextRoute -> 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 nextRoute =<< LVar.get model lift loop liftIO (try loop) >>= \case Right () -> pure () Left (err :: ConnectionException) -> do log LevelError $ "Websocket error: " <> show err LVar.removeListener model subId assetsMiddleware = do case nonEmpty (staticAssets $ Proxy @route) of Nothing -> id Just topLevelPaths -> let assetPolicy :: Static.Policy = foldl1' (Static.<|>) $ Static.hasPrefix <$> topLevelPaths in Static.staticPolicy assetPolicy httpApp logger req f = do flip runLoggingT logger $ do let path = Wai.pathInfo req mr = routeFromPathInfo path logInfoNS "HTTP" $ show path <> " as " <> show mr (status, v) <- case mr of Nothing -> pure (H.status404, "No route") Just r -> do val <- LVar.get model let html = renderCatchingErrors logger val r pure (H.status200, html <> emaStatusHtml <> wsClientShim) liftIO $ f $ Wai.responseLBS status [(H.hContentType, "text/html")] v renderWithEmaHtmlShims logger m r = renderCatchingErrors logger m r <> emaStatusHtml 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 $ encodeUtf8 $ "

Ema App threw an exception

"
                <> show @Text err
                <> "

Once you fix your code this page will automatically update." routeFromPathInfo = decodeRoute @model . fmap (fromString . toString) -- 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) -- | 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 -- Browser-side JavaScript code for interacting with the Haskell server wsClientShim :: LByteString wsClientShim = encodeUtf8 [text| |] emaStatusHtml :: LByteString emaStatusHtml = encodeUtf8 [text|

|]