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

server: proper job handling

Note: the server will not check submissions for duplicates!
(nor does it do any kind of rate-limiting)
parent 24e5ccd9
No related branches found
No related tags found
No related merge requests found
...@@ -71,3 +71,5 @@ executables: ...@@ -71,3 +71,5 @@ executables:
- walint - walint
- uuid - uuid
- containers - containers
- microlens
- microlens-th
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
module Handlers (App, submitImpl,statusImpl) where module Handlers (App, submitImpl,statusImpl,relintImpl) where
import Bindings.Cli.Git (gitProc) import Bindings.Cli.Git (gitProc)
import CheckDir (DirResult, recursiveCheckDir) import CheckDir (recursiveCheckDir)
import Cli.Extras (CliT, ProcessFailure, Severity (..), import Cli.Extras (CliConfig, CliT, ProcessFailure,
callProcessAndLogOutput, getCliConfig, Severity (..), callProcessAndLogOutput,
prettyProcessFailure, runCli) getCliConfig, prettyProcessFailure,
import Control.Concurrent (MVar, forkIO, withMVar) runCli)
import Control.Concurrent (MVar, ThreadId, forkIO, withMVar)
import Control.Monad.Extra (ifM) import Control.Monad.Extra (ifM)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans (lift) import Control.Monad.Trans (lift)
import qualified Data.Map as M import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import Data.UUID (UUID)
import qualified Data.UUID as UUID import qualified Data.UUID as UUID
import qualified Data.UUID.V4 as UUID import qualified Data.UUID.V4 as UUID
import Servant (Handler, err404, err500, throwError) import Lens.Micro.Extras (view)
import Servant (Handler, NoContent (NoContent), err404,
err500, throwError)
import Server (Config (entrypoint, lintconfig, tmpdir), import Server (Config (entrypoint, lintconfig, tmpdir),
JobStatus (..), JobStatus (..),
RemoteRef (reporef, repourl), State, RemoteRef (reporef, repourl), State,
setJobStatus) jobs, registry, setJobStatus,
setRegistry)
import System.Directory (doesDirectoryExist) import System.Directory (doesDirectoryExist)
import System.FilePath ((</>)) import System.FilePath ((</>))
-- | this servant app can run cli programs! -- | this servant app can run cli programs!
type App = CliT ProcessFailure Handler type App = CliT ProcessFailure Handler
type App' = CliT ProcessFailure IO
-- | annoying (and afaik unused), but has to be here for type system reasons -- | annoying (and afaik unused), but has to be here for type system reasons
instance MonadFail Handler where instance MonadFail Handler where
fail _ = throwError $ err500 fail _ = throwError $ err500
-- | someone submitted a map; lint it (synchronously for now) -- | someone submitted a map; lint it (synchronously for now)
submitImpl :: Config True -> MVar State -> RemoteRef -> App () submitImpl :: Config True -> MVar State -> RemoteRef -> App UUID
submitImpl config state ref = do submitImpl config state ref = do
jobid <- liftIO UUID.nextRandom
-- TODO: these two should really be atomic
liftIO $ setJobStatus state ref Pending liftIO $ setJobStatus state ref Pending
liftIO $ setRegistry state jobid ref
cliconfig <- getCliConfig cliconfig <- getCliConfig
-- we'll just forget the thread id for now and trust this terminates … -- we'll just forget the thread id for now and trust this terminates …
_ <- liftIO $ forkIO $ do _ <- checkRef config cliconfig state ref
res <- runCli cliconfig $ do
ifM (liftIO $ doesDirectoryExist gitdir)
gitfetch gitclone
checkPath config gitdir (reporef ref)
setJobStatus state ref $ case res of
Right res -> Linted res
Left err -> Failed (prettyProcessFailure err)
-- the submission itself can't really fail or return anything useful -- the submission itself can't really fail or return anything useful
pure () pure jobid
where
-- TODO: these calls fail for dumb http, add some fallback! relintImpl :: Config True -> MVar State -> UUID -> App NoContent
gitclone = callProcessAndLogOutput (Debug, Error) relintImpl config state uuid = do
$ gitProc gitdir [ "clone", T.unpack $ repourl ref, "--bare", "--depth", "1", "-b", T.unpack (reporef ref)] mref <- liftIO $ withMVar state (pure . M.lookup uuid . view registry)
gitfetch = callProcessAndLogOutput (Debug, Error) case mref of
$ gitProc gitdir [ "fetch", "origin", T.unpack (reporef ref), "--depth", "1" ] Nothing -> lift $ throwError err404
gitdir = tmpdir config </> hashedname Just ref -> do
hashedname = fmap escapeSlash . T.unpack . repourl $ ref cliconfig <- getCliConfig
escapeSlash = \case { '/' -> '-'; a -> a } _ <- checkRef config cliconfig state ref
pure NoContent
statusImpl :: MVar State -> RemoteRef -> App JobStatus statusImpl :: MVar State -> UUID -> App JobStatus
statusImpl state ref = do statusImpl state uuid = do
status <- liftIO $ withMVar state (pure . M.lookup ref) status <- liftIO $ withMVar state $ \state ->
case M.lookup uuid (view registry state) of
Nothing -> pure Nothing
Just ref -> pure $ M.lookup ref (view jobs state)
case status of case status of
Just res -> pure res Just res -> pure res
Nothing -> lift $ throwError err404 Nothing -> lift $ throwError err404
-- | the actual check function. forks, calls out to git to update the
-- repository, create a new worktree, lints it, then tells git to
-- delete that tree again
checkRef :: Config True -> CliConfig -> MVar State -> RemoteRef -> App ThreadId
checkRef config cliconfig state ref = liftIO $ forkIO $ do
res <- liftIO $ runCli cliconfig $ do
ifM (liftIO $ doesDirectoryExist gitdir)
-- TODO: these calls fail for dumb http, add some fallback!
(callgit gitdir
[ "fetch", "origin", T.unpack (reporef ref), "--depth", "1" ])
(callgit gitdir
[ "clone", T.unpack $ repourl ref, "--bare"
, "--depth", "1", "-b", T.unpack (reporef ref)])
rand <- liftIO UUID.nextRandom
let workdir = "/tmp" </> ("worktree-" <> UUID.toString rand)
callgit gitdir [ "worktree", "add", workdir ]
callgit workdir [ "checkout", T.unpack (reporef ref) ]
res <- liftIO $ recursiveCheckDir (lintconfig config) workdir (entrypoint config)
callgit gitdir [ "worktree", "remove", "-f", "-f", workdir ]
pure res
liftIO $ setJobStatus state ref $ case res of
Right res -> Linted res
Left err -> Failed (prettyProcessFailure err)
where
callgit dir = callProcessAndLogOutput (Debug, Debug) . gitProc dir
gitdir = tmpdir config </> hashedname
hashedname = fmap escapeSlash . T.unpack . repourl $ ref
escapeSlash = \case { '/' -> '-'; a -> a }
checkPath :: Config True -> FilePath -> Text -> App' DirResult
checkPath config gitdir ref = do
rand <- liftIO UUID.nextRandom
let workdir = "/tmp" </> ("worktree-" <> UUID.toString rand)
callProcessAndLogOutput (Debug, Error)
$ gitProc gitdir [ "worktree", "add", workdir ]
callProcessAndLogOutput (Debug, Error)
$ gitProc workdir [ "checkout", T.unpack ref ]
res <- liftIO $ recursiveCheckDir (lintconfig config) gitdir (entrypoint config)
callProcessAndLogOutput (Debug, Error)
$ gitProc gitdir [ "worktree", "remove", "-f", "-f", workdir ]
pure res
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-} {-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
-- | simple server offering linting "as a service" -- | simple server offering linting "as a service"
...@@ -15,16 +15,20 @@ import Cli.Extras (mkDefaultCliConfig, runCli) ...@@ -15,16 +15,20 @@ import Cli.Extras (mkDefaultCliConfig, runCli)
import Control.Concurrent (MVar, newMVar) import Control.Concurrent (MVar, newMVar)
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 Handlers (App, statusImpl, submitImpl) import Data.UUID (UUID)
import Handlers (App, relintImpl, statusImpl,
submitImpl)
import Network.Wai.Handler.Warp (run) import Network.Wai.Handler.Warp (run)
import Servant (Application, Get, Handler, import Servant (Application, Capture, Get, Handler,
HasServer (ServerT), JSON, HasServer (ServerT), JSON,
Proxy (Proxy), ReqBody, NoContent, Post, Proxy (Proxy),
ServerError (errBody), err500, ReqBody, ServerError (errBody),
hoistServer, serve, throwError, err500, hoistServer, serve,
type (:<|>) (..), type (:>), Post) throwError, type (:<|>) (..),
type (:>))
import Server (Config (..), JobStatus, import Server (Config (..), JobStatus,
RemoteRef (..), State, loadConfig) RemoteRef (..), State,
defaultState, loadConfig)
{- {-
Needed: Needed:
...@@ -40,8 +44,9 @@ Needed: ...@@ -40,8 +44,9 @@ Needed:
-} -}
-- | Main API type -- | Main API type
type API format = type API format =
"submit" :> ReqBody '[JSON] RemoteRef :> Post '[format] () "submit" :> ReqBody '[JSON] RemoteRef :> Post '[format] UUID
:<|> "status" :> ReqBody '[JSON] RemoteRef :> Get '[format] JobStatus :<|> "status" :> Capture "jobid" UUID :> Get '[format] JobStatus
:<|> "relint" :> Capture "jobid" UUID :> Get '[format] NoContent
-- | API's implementation -- | API's implementation
...@@ -49,6 +54,7 @@ jsonAPI :: Config True -> MVar State -> ServerT (API JSON) App ...@@ -49,6 +54,7 @@ jsonAPI :: Config True -> MVar State -> ServerT (API JSON) App
jsonAPI config state = jsonAPI config state =
submitImpl config state submitImpl config state
:<|> statusImpl state :<|> statusImpl state
:<|> relintImpl config state
-- | 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 :: Config True -> MVar State -> Application
...@@ -65,7 +71,7 @@ app config = ...@@ -65,7 +71,7 @@ app config =
main :: IO () main :: IO ()
main = do main = do
state <- newMVar (mempty :: State) state <- newMVar defaultState
let config = Config "/tmp" 8080 "main.json" "./config.json" let config = Config "/tmp" 8080 "main.json" "./config.json"
config' <- loadConfig config config' <- loadConfig config
run (port config) (app config' state) run (port config) (app config' state)
...@@ -3,12 +3,13 @@ ...@@ -3,12 +3,13 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-} {-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Server (loadConfig, Config(..), RemoteRef(..), State, JobStatus(..), module Server (loadConfig, Config(..), RemoteRef(..), State, registry, jobs, JobStatus(..),
setJobStatus) where setJobStatus,defaultState,setRegistry) where
import CheckDir (DirResult) import CheckDir (DirResult)
import Control.Concurrent (MVar, modifyMVar_) import Control.Concurrent (MVar, modifyMVar_)
...@@ -17,9 +18,13 @@ import qualified Data.ByteString.Lazy as LB ...@@ -17,9 +18,13 @@ import qualified Data.ByteString.Lazy as LB
import Data.Map (Map) import Data.Map (Map)
import qualified Data.Map as M import qualified Data.Map as M
import Data.Text (Text) import Data.Text (Text)
import Data.UUID (UUID)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Lens.Micro (over)
import Lens.Micro.TH
import LintConfig (LintConfig') import LintConfig (LintConfig')
-- | a reference in a remote git repository -- | a reference in a remote git repository
data RemoteRef = RemoteRef data RemoteRef = RemoteRef
{ repourl :: Text { repourl :: Text
...@@ -44,7 +49,15 @@ data JobStatus = ...@@ -44,7 +49,15 @@ data JobStatus =
Pending | Linted DirResult | Failed Text Pending | Linted DirResult | Failed Text
deriving (Generic, ToJSON) deriving (Generic, ToJSON)
type State = Map RemoteRef JobStatus data State = State
{ _jobs :: Map RemoteRef JobStatus
, _registry :: Map UUID RemoteRef
}
makeLenses ''State
defaultState :: State
defaultState = State mempty mempty
loadConfig :: Config False -> IO (Config True) loadConfig :: Config False -> IO (Config True)
...@@ -57,5 +70,9 @@ loadConfig config = do ...@@ -57,5 +70,9 @@ loadConfig config = do
setJobStatus :: MVar State -> RemoteRef -> JobStatus -> IO () setJobStatus :: MVar State -> RemoteRef -> JobStatus -> IO ()
setJobStatus mvar ref status = modifyMVar_ mvar $ \state -> setJobStatus mvar ref status = modifyMVar_ mvar
pure $ M.insert ref status state $ pure . over jobs (M.insert ref status)
setRegistry :: MVar State -> UUID -> RemoteRef -> IO ()
setRegistry mvar uuid ref = modifyMVar_ mvar
$ pure . over registry (M.insert uuid ref)
...@@ -79,6 +79,8 @@ executable server ...@@ -79,6 +79,8 @@ executable server
, filepath , filepath
, http-media , http-media
, logging-effect , logging-effect
, microlens
, microlens-th
, mtl , mtl
, process , process
, servant , servant
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment