Skip to content

Commit

Permalink
wip
Browse files Browse the repository at this point in the history
  • Loading branch information
tchoutri committed Dec 21, 2024
1 parent 551ffa9 commit 4b74672
Show file tree
Hide file tree
Showing 4 changed files with 42 additions and 46 deletions.
2 changes: 1 addition & 1 deletion cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ source-repository-package
source-repository-package
type: git
location: https://github.com/kleidukos/servant-effectful
tag: cec4d54
tag: 02e7fe0ab9fa0af06b1e2ec21cecfae405d39fc5

source-repository-package
type: git
Expand Down
1 change: 1 addition & 0 deletions flora.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -390,6 +390,7 @@ library flora-web
, servant
, servant-client
, servant-client-core
, servant-effectful
, servant-openapi3
, servant-server
, text
Expand Down
83 changes: 39 additions & 44 deletions src/web/FloraWeb/Server.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
module FloraWeb.Server where

import Colourista.IO (blueMessage)
Expand All @@ -13,10 +14,11 @@ import Data.Text.Display (display)
import Effectful
import Effectful.Concurrent
import Effectful.Dispatch.Static
import Effectful.Error.Static (runErrorNoCallStack, runErrorWith)
import Effectful.Error.Static (Error, runErrorNoCallStack, runErrorWith)
import Effectful.Fail (runFailIO)
import Effectful.PostgreSQL.Transact.Effect (runDB)
import Effectful.Reader.Static (runReader)
import Effectful.Servant
import Effectful.Time (runTime)
import Effectful.Trace qualified as Trace
import Log (Logger)
Expand All @@ -27,7 +29,6 @@ import Network.HTTP.Client.TLS (tlsManagerSettings)
import Network.HTTP.Types (notFound404)
import Network.Wai.Handler.Warp
( defaultSettings
, runSettings
, setOnException
, setPort
)
Expand All @@ -43,6 +44,7 @@ import Servant
, Context (..)
, ErrorFormatters
, Handler
, HasServer (ServerT)
, NotFoundErrorFormatter
, Proxy (Proxy)
, defaultErrorFormatters
Expand Down Expand Up @@ -87,6 +89,7 @@ import FloraWeb.Pages.Templates (defaultTemplateEnv, defaultsToEnv)
import FloraWeb.Pages.Templates.Error (renderError)
import FloraWeb.Routes
import FloraWeb.Types
import Servant.Server (ServerError, ServerContext)

type FloraAuthContext =
'[ OptionalAuthContext
Expand Down Expand Up @@ -150,11 +153,16 @@ runServer appLogger floraEnv = do
unsafeEff_ $
Safe.withException (startJobRunner oddJobsCfg) (logException floraEnv.environment appLogger)
loggingMiddleware <- Logging.runLog floraEnv.environment appLogger WaiLog.mkLogMiddleware
oddJobsEnv <- OddJobs.mkEnv oddjobsUiCfg ("/admin/odd-jobs/" <>)
jobsRunnerEnv <- OddJobs.mkEnv oddjobsUiCfg ("/admin/odd-jobs/" <>)
let webEnv = WebEnv floraEnv
webEnvStore <- liftIO $ newWebEnvStore webEnv
ioref <- liftIO $ newIORef True
let server = mkServer appLogger webEnvStore floraEnv oddjobsUiCfg oddJobsEnv zipkin ioref
-- let server = mkServer appLogger webEnvStore floraEnv oddjobsUiCfg oddJobsEnv zipkin ioref
let middleware =
heartbeatMiddleware
. loggingMiddleware
. const

let warpSettings =
setPort (fromIntegral floraEnv.httpPort) $
setOnException
Expand All @@ -164,28 +172,15 @@ runServer appLogger floraEnv = do
floraEnv.mltp
)
defaultSettings
liftIO
$ runSettings warpSettings
$ heartbeatMiddleware
. loggingMiddleware
. const
$ server

mkServer
:: Logger
-> WebEnvStore
-> FloraEnv
-> OddJobs.UIConfig
-> OddJobs.Env
-> Zipkin
-> IORef Bool
-> Application
mkServer logger webEnvStore floraEnv cfg jobsRunnerEnv zipkin ioref =
serveWithContextT
(Proxy @ServerRoutes)
(genAuthServerContext logger floraEnv)
(naturalTransform floraEnv logger webEnvStore zipkin)
(floraServer cfg jobsRunnerEnv floraEnv.environment ioref)
runWarpServerSettingsContext @ServerRoutes
warpSettings
(genAuthServerContext appLogger floraEnv)
middleware

Check failure on line 179 in src/web/FloraWeb/Server.hs

View workflow job for this annotation

GitHub Actions / Backend_tests (9.6.6, ubuntu-latest)

• Couldn't match type: Application -> Application
( naturalTransform floraEnv appLogger webEnvStore zipkin $

Check failure on line 180 in src/web/FloraWeb/Server.hs

View workflow job for this annotation

GitHub Actions / Backend_tests (9.6.6, ubuntu-latest)

• Couldn't match expected type ‘Zipkin’

Check failure on line 180 in src/web/FloraWeb/Server.hs

View workflow job for this annotation

GitHub Actions / Backend_tests (9.6.6, ubuntu-latest)

• Couldn't match type ‘Zipkin’ with ‘Eff RouteEffects a1’
floraServer oddjobsUiCfg jobsRunnerEnv floraEnv.environment ioref
)
pure ()

floraServer
:: OddJobs.UIConfig
Expand All @@ -204,29 +199,29 @@ floraServer cfg jobsRunnerEnv environment ioref =
, livereload = LiveReload.livereloadHandler environment ioref
}

naturalTransform :: FloraEnv -> Logger -> WebEnvStore -> Zipkin -> FloraEff a -> Handler a
naturalTransform floraEnv logger _webEnvStore zipkin app = do
naturalTransform
:: (HasServer api context, ServerContext context)
=> FloraEnv
-> Logger
-> Zipkin
-> FloraEff a
-> ServerT api (Eff (Error ServerError : es))
naturalTransform floraEnv logger zipkin app = do
let runTrace =
if floraEnv.environment == Production
then Trace.runTrace zipkin.zipkinTracer
else Trace.runNoTrace
result <-
liftIO $
Right
<$> app
& runTrace
& runDB floraEnv.pool
& runTime
& runReader floraEnv.features
& ( case floraEnv.features.blobStoreImpl of
Just (BlobStoreFS fp) -> runBlobStoreFS fp
_ -> runBlobStorePure
)
& Logging.runLog floraEnv.environment logger
& runErrorWith (\_callstack err -> pure $ Left err)
& runConcurrent
& runEff
either Except.throwError pure result
liftIO $ app
& runTrace
& runDB floraEnv.pool
& runTime
& runReader floraEnv.features
& ( case floraEnv.features.blobStoreImpl of
Just (BlobStoreFS fp) -> runBlobStoreFS fp
_ -> runBlobStorePure
)
& Logging.runLog floraEnv.environment logger
& runConcurrent

Check failure on line 224 in src/web/FloraWeb/Server.hs

View workflow job for this annotation

GitHub Actions / Backend_tests (9.6.6, ubuntu-latest)

• Couldn't match type: Eff [Error ServerError, IOE] a

genAuthServerContext :: Logger -> FloraEnv -> Context FloraAuthContext
genAuthServerContext logger floraEnv =
Expand Down
2 changes: 1 addition & 1 deletion src/web/FloraWeb/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,8 @@ type RouteEffects =
, Reader FeatureEnv
, BlobStoreAPI
, Log
, Error ServerError
, Concurrent
, Error ServerError
, IOE
]

Expand Down

0 comments on commit 4b74672

Please sign in to comment.