{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} module Hsm.Web ( Web , runServer , runWeb ) where import Data.Aeson (encode) import Effectful (Dispatch (Static), DispatchOf, Eff, IOE, liftIO, (:>)) import Effectful.Dispatch.Static ( SideEffects (WithSideEffects) , StaticRep , evalStaticRep , getStaticRep , unEff , unsafeEff ) import Effectful.Dispatch.Static.Primitive (Env) import Effectful.Exception (finally) import Hsm.INA226 (I2CINA226, INA226, readINA226State) import Hsm.Log (Logs, Severity (Info, Trace), logMsg, makeLoggerIO) import Network.Wai.Handler.Warp (defaultSettings, setLogger) import Network.Wai.Middleware.Static (addBase, noDots, staticPolicy, (>->)) import Paths_hsm_web (getDataFileName) import Web.Scotty (Options (settings, verbose), defaultOptions, file, get, middleware, raw, scottyOpts, setHeader) data Web (a :: * -> *) (b :: *) type instance DispatchOf Web = Static WithSideEffects newtype instance StaticRep Web = Web Options server :: (I2CINA226 :> es, INA226 :> es, Logs '["i2c", "ina226"] es) => Options -> Env es -> IO () server options env = do dist <- getDataFileName "Client/dist/" scottyOpts options $ do middleware . staticPolicy $ noDots >-> addBase dist get "/" . file $ dist <> "index.html" get "/ina226" $ do setHeader "Content-Type" "application/json" liftIO (unEff readINA226State env) >>= raw . encode runServer :: (I2CINA226 :> es, INA226 :> es, Logs '["i2c", "ina226", "web"] es, Web :> es) => Eff es () runServer = finally startServer stopServer where startServer = do Web options <- getStaticRep logMsg @"web" Info "Starting scotty web server" unsafeEff $ server options stopServer = logMsg @"web" Info "Stopping scotty web server" runWeb :: (IOE :> es, Logs '["scotty", "web"] es) => Eff (Web : es) a -> Eff es a runWeb action = do logMsg @"web" Info "Registering logger for scotty web server" scottyLogger <- logRequest <$> makeLoggerIO @"scotty" evalStaticRep (Web $ options scottyLogger) action where logRequest loggerIO request status fileSize = loggerIO Trace $ unwords [show request, show status, show fileSize] options logger = defaultOptions{verbose = 0, settings = setLogger logger defaultSettings}