Skip to content
Snippets Groups Projects
Commit be108900 authored by stuebinm's avatar stuebinm
Browse files

server: added (somewhat) sensible logging

it's not very sensible, but at least it exists
parent 4fb5d083
No related branches found
No related tags found
No related merge requests found
...@@ -50,31 +50,28 @@ executables: ...@@ -50,31 +50,28 @@ executables:
- aeson-pretty - aeson-pretty
- template-haskell - template-haskell
- process - process
server: walint-server:
main: Main.hs main: Main.hs
source-dirs: 'server' source-dirs: 'server'
dependencies: dependencies:
- walint
- base-compat
- time - time
- directory
- filepath
- warp
- wai
- servant - servant
- servant-server - servant-server
- wai - lucid
- base-compat - servant-lucid
- string-conversions - http-types
- http-media
- warp
- cli-git - cli-git
- cli-extras - cli-extras
- filepath
- logging-effect
- process
- extra - extra
- directory
- walint
- uuid - uuid
- containers - containers
- microlens - microlens
- microlens-th - microlens-th
- tomland - tomland
- lucid
- servant-lucid
- dotgen - dotgen
...@@ -3,6 +3,7 @@ ...@@ -3,6 +3,7 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
module Handlers (App, submitImpl,statusImpl,relintImpl,adminOverviewImpl) where module Handlers (App, submitImpl,statusImpl,relintImpl,adminOverviewImpl) where
...@@ -12,7 +13,7 @@ import CheckDir (recursiveCheckDir) ...@@ -12,7 +13,7 @@ import CheckDir (recursiveCheckDir)
import Cli.Extras (CliConfig, CliT, ProcessFailure, import Cli.Extras (CliConfig, CliT, ProcessFailure,
Severity (..), callProcessAndLogOutput, Severity (..), callProcessAndLogOutput,
getCliConfig, prettyProcessFailure, getCliConfig, prettyProcessFailure,
runCli) putLog, runCli)
import Control.Concurrent (MVar, ThreadId, forkIO, readMVar, import Control.Concurrent (MVar, ThreadId, forkIO, readMVar,
withMVar) withMVar)
import Control.Monad.Extra (ifM) import Control.Monad.Extra (ifM)
......
...@@ -11,15 +11,23 @@ ...@@ -11,15 +11,23 @@
-- | simple server offering linting "as a service" -- | simple server offering linting "as a service"
module Main where module Main where
import Cli.Extras (mkDefaultCliConfig, runCli) import Cli.Extras (CliConfig, Severity (..),
mkDefaultCliConfig, putLog, runCli)
import Control.Concurrent (MVar, newMVar) import Control.Concurrent (MVar, newMVar)
import Control.Monad (void)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString.Lazy.Char8 as C8 import qualified Data.ByteString.Lazy.Char8 as C8
import Data.List (intersperse)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8)
import Data.UUID (UUID) import Data.UUID (UUID)
import Handlers (App, adminOverviewImpl, relintImpl, import Handlers (App, adminOverviewImpl, relintImpl,
statusImpl, submitImpl) statusImpl, submitImpl)
import HtmlOrphans () import HtmlOrphans ()
import Network.Wai.Handler.Warp (run) import Network.HTTP.Types.Status (Status (..))
import Network.Wai (Request, pathInfo, requestMethod)
import Network.Wai.Handler.Warp (defaultSettings, runSettings,
setLogger, setPort)
import Servant (Application, Capture, Get, Handler, import Servant (Application, Capture, Get, Handler,
HasServer (ServerT), JSON, HasServer (ServerT), JSON,
NoContent, Post, Proxy (Proxy), NoContent, Post, Proxy (Proxy),
...@@ -33,18 +41,7 @@ import Server (AdminOverview, Config (..), ...@@ -33,18 +41,7 @@ import Server (AdminOverview, Config (..),
JobStatus, RemoteRef (..), State, JobStatus, RemoteRef (..), State,
defaultState, loadConfig) defaultState, loadConfig)
{-
Needed:
- admin overview (perhaps on seperate port?)
- in json:
- submit a repository link & ref name, get back job id
- look up a lint status by job id
- in html
- look up a lint status, pretty-printed
- front page with overview & links
- possibly a "update & relint" button?
- links to documentation
-}
-- | Main API type -- | Main API type
type API format = type API format =
"submit" :> ReqBody '[JSON] RemoteRef :> Post '[format] UUID "submit" :> ReqBody '[JSON] RemoteRef :> Post '[format] UUID
...@@ -74,20 +71,37 @@ server config state = ...@@ -74,20 +71,37 @@ server config state =
:<|> serveDirectoryWebApp "./static" :<|> serveDirectoryWebApp "./static"
-- | make an application; convert any cli errors into a 500 -- | make an application; convert any cli errors into a 500
app :: Config True -> MVar State -> Application app :: CliConfig -> Config True -> MVar State -> Application
app config = app cliconfig config =
serve api . hoistServer api conv . server config serve api . hoistServer api conv . server config
where api = Proxy @Routes where api = Proxy @Routes
conv :: App a -> Handler a conv :: App a -> Handler a
conv m = do conv m = do
config <- liftIO $ mkDefaultCliConfig ["-v"] res <- runCli cliconfig m
res <- runCli config m
case res of case res of
Right a -> pure a Right a -> pure a
Left err -> throwError (err500 { errBody = C8.pack (show err) }) Left err -> throwError (err500 { errBody = C8.pack (show err) })
main :: IO () main :: IO ()
main = do main = do
config' <- loadConfig "./config.toml" cliconfig <- liftIO $ mkDefaultCliConfig ["-v"]
config <- loadConfig "./config.toml"
state <- newMVar defaultState state <- newMVar defaultState
run (port config') (app config' state) let warpsettings =
setPort (port config)
. setLogger (logRequest cliconfig)
$ defaultSettings
runSettings warpsettings (app cliconfig config state)
-- TODO: at some point i should learn how to do these things properly, but
-- for now this works well enough i guess
logRequest :: CliConfig -> Request -> Status -> Maybe Integer -> IO ()
logRequest cliconfig req status _size = void . runCli cliconfig $
putLog Notice
$ "request: "
<> decodeUtf8 (requestMethod req) <> " "
<> parts <> " "
<> T.pack (show (statusCode status)) <> " "
<> decodeUtf8 (statusMessage status)
where parts = T.concat $ intersperse "/" (pathInfo req)
...@@ -57,7 +57,28 @@ library ...@@ -57,7 +57,28 @@ library
, witherable , witherable
default-language: Haskell2010 default-language: Haskell2010
executable server executable walint
main-is: Main.hs
other-modules:
Version
Paths_walint
hs-source-dirs:
src
ghc-options: -Wall -Wno-name-shadowing -Wno-unticked-promoted-constructors
build-depends:
aeson
, aeson-pretty
, base
, bytestring
, getopt-generics
, mtl
, process
, template-haskell
, text
, walint
default-language: Haskell2010
executable walint-server
main-is: Main.hs main-is: Main.hs
other-modules: other-modules:
Handlers Handlers
...@@ -79,17 +100,14 @@ executable server ...@@ -79,17 +100,14 @@ executable server
, dotgen , dotgen
, extra , extra
, filepath , filepath
, http-media , http-types
, logging-effect
, lucid , lucid
, microlens , microlens
, microlens-th , microlens-th
, mtl , mtl
, process
, servant , servant
, servant-lucid , servant-lucid
, servant-server , servant-server
, string-conversions
, text , text
, time , time
, tomland , tomland
...@@ -98,24 +116,3 @@ executable server ...@@ -98,24 +116,3 @@ executable server
, walint , walint
, warp , warp
default-language: Haskell2010 default-language: Haskell2010
executable walint
main-is: Main.hs
ghc-options: -Wall -Wno-name-shadowing -Wno-unticked-promoted-constructors
build-depends:
aeson
, aeson-pretty
, base
, bytestring
, getopt-generics
, mtl
, process
, template-haskell
, text
, walint
hs-source-dirs:
src
default-language: Haskell2010
other-modules:
Version
Paths_walint
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment