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

server: remove a thunk leak

(really a lot of these data structures should be eagerly evaluated into
normal form, i suspect there's still a lot to be gained)
parent 07483578
No related branches found
No related tags found
No related merge requests found
...@@ -6,7 +6,7 @@ verbose = true ...@@ -6,7 +6,7 @@ verbose = true
tmpdir = "/tmp" tmpdir = "/tmp"
# linting interval in seconds # linting interval in seconds
interval = 30 interval = 10000
exneuland = "http://localhost:4000" exneuland = "http://localhost:4000"
token = "hello, world!" token = "hello, world!"
......
...@@ -31,9 +31,9 @@ import Network.Wai.Middleware.RequestLogger (OutputFormat (..), ...@@ -31,9 +31,9 @@ import Network.Wai.Middleware.RequestLogger (OutputFormat (..),
RequestLoggerSettings (..), RequestLoggerSettings (..),
mkRequestLogger) mkRequestLogger)
import Servant (Application, Capture, import Servant (Application, Capture,
EmptyAPI, Get, JSON, Get, JSON, PlainText,
PlainText, Post, Raw, Post, Raw, ReqBody,
ReqBody, Server, serve, Server, serve,
type (:<|>) (..), type (:<|>) (..),
type (:>)) type (:>))
import Servant.HTML.Lucid (HTML) import Servant.HTML.Lucid (HTML)
...@@ -47,10 +47,8 @@ import Server (JobStatus, Org (..), ...@@ -47,10 +47,8 @@ import Server (JobStatus, Org (..),
import Worker (Job (Job), linterThread) import Worker (Job (Job), linterThread)
import Servant.API (Header) import Servant.API (Header)
import Servant.Client (BaseUrl (BaseUrl), import Servant.Client (ClientM, client,
ClientM, Scheme (Http), mkClientEnv, runClientM)
client, mkClientEnv,
runClientM)
type family PolyEndpoint method format payload where type family PolyEndpoint method format payload where
PolyEndpoint Get format payload = Get format payload PolyEndpoint Get format payload = Get format payload
...@@ -114,19 +112,19 @@ main = do ...@@ -114,19 +112,19 @@ main = do
-- TODO: what about tls / https? -- TODO: what about tls / https?
manager' <- newManager defaultManagerSettings manager' <- newManager defaultManagerSettings
updater <- async $ forever $ do -- updater <- async $ forever $ do
done <- readMVar state -- done <- readMVar state
res <- runClientM -- res <- runClientM
(postNewMaps (view token config) (MapService done)) -- (postNewMaps (view token config) (MapService done))
(mkClientEnv manager' (view exneuland config)) -- (mkClientEnv manager' (view exneuland config))
print res -- print res
threadDelay (view interval config * 1000000) -- threadDelay (view interval config * 1000000)
-- spawns threads for each job in the queue -- spawns threads for each job in the queue
linter <- async $ void $ linterThread config queue state linter <- async $ void $ linterThread config queue state
link linter link linter
link poker link poker
link updater -- link updater
let warpsettings = let warpsettings =
setPort (view port config) setPort (view port config)
......
...@@ -39,11 +39,12 @@ import qualified Data.ByteString.Base64.URL as Base64 ...@@ -39,11 +39,12 @@ import qualified Data.ByteString.Base64.URL as Base64
import Data.Coerce (coerce) import Data.Coerce (coerce)
import Data.Either.Extra (mapLeft) import Data.Either.Extra (mapLeft)
import Data.Functor.Contravariant (contramap) import Data.Functor.Contravariant (contramap)
import qualified Data.Map as M import qualified Data.Map.Strict as M
import Lens.Micro.Platform (at, ix, makeLenses, traverseOf) import Lens.Micro.Platform (at, ix, makeLenses, traverseOf)
import LintConfig (LintConfig') import LintConfig (LintConfig')
import Servant (FromHttpApiData) import Servant (FromHttpApiData)
import Servant.Client (BaseUrl, parseBaseUrl) import Servant.Client (BaseUrl, parseBaseUrl)
import qualified Text.Show as TS
import Toml (BiMap (BiMap), TomlBiMap, import Toml (BiMap (BiMap), TomlBiMap,
TomlBiMapError (ArbitraryError), TomlBiMapError (ArbitraryError),
TomlCodec, prettyTomlDecodeErrors, TomlCodec, prettyTomlDecodeErrors,
...@@ -157,9 +158,15 @@ configCodec = Config ...@@ -157,9 +158,15 @@ configCodec = Config
-- | a job status (of a specific uuid) -- | a job status (of a specific uuid)
data JobStatus = data JobStatus =
Pending | Linted DirResult Text | Failed Text Pending | Linted !DirResult Text | Failed Text
deriving (Generic, ToJSON) deriving (Generic, ToJSON)
instance TS.Show JobStatus where
show = \case
Pending -> "Pending"
Linted res rev -> "Linted result"
Failed err -> "Failed with: " <> show err
-- | the server's global state; might eventually end up with more -- | the server's global state; might eventually end up with more
-- stuff in here, hence the newtype -- stuff in here, hence the newtype
newtype ServerState = ServerState newtype ServerState = ServerState
...@@ -192,8 +199,14 @@ loadConfig path = do ...@@ -192,8 +199,14 @@ loadConfig path = do
-- | NOTE: this does not create the org if it does not yet exist! -- | NOTE: this does not create the org if it does not yet exist!
setJobStatus :: MVar ServerState -> Org True -> RemoteRef -> JobStatus -> IO () setJobStatus :: MVar ServerState -> Org True -> RemoteRef -> JobStatus -> IO ()
setJobStatus mvar !org !ref !status = modifyMVar_ mvar setJobStatus mvar !org !ref !status = do
$ pure . over (unState . ix org . at (toSha ref)) (const $ Just (ref, status)) modifyMVar_ mvar $ \state -> do
-- will otherwise cause a thunk leak, since Data.Map is annoyingly un-strict
-- even in its strict variety. for some reason it also doesn't work when
-- moved inside the `over` though …
_ <- evaluateWHNF (view (unState . ix org) state)
pure $ over (unState . ix org . at (toSha ref))
(const $ Just (ref, status)) state
getJobStatus :: MVar ServerState -> Text -> Sha1 -> IO (Maybe (RemoteRef, JobStatus)) getJobStatus :: MVar ServerState -> Text -> Sha1 -> IO (Maybe (RemoteRef, JobStatus))
getJobStatus mvar orgslug sha = withMVar mvar $ \state -> getJobStatus mvar orgslug sha = withMVar mvar $ \state ->
......
...@@ -47,7 +47,7 @@ linterThread config queue done = forever $ do ...@@ -47,7 +47,7 @@ linterThread config queue done = forever $ do
-- TODO: re-add proper fancy (colourful?) logging -- TODO: re-add proper fancy (colourful?) logging
runJob :: Config True -> Job -> MVar ServerState -> IO () runJob :: Config True -> Job -> MVar ServerState -> IO ()
runJob config Job {..} done = do runJob config Job {..} done = do
rand <- liftIO UUID.nextRandom rand <- UUID.nextRandom
let workdir = "/tmp" </> ("worktree-" <> UUID.toString rand) let workdir = "/tmp" </> ("worktree-" <> UUID.toString rand)
handle whoops handle whoops
...@@ -64,7 +64,8 @@ runJob config Job {..} done = do ...@@ -64,7 +64,8 @@ runJob config Job {..} done = do
rev <- map T.strip -- git returns a newline here rev <- map T.strip -- git returns a newline here
$ readgit' gitdir ["rev-parse", toString ref] $ readgit' gitdir ["rev-parse", toString ref]
callgit gitdir [ "worktree", "add", "--force", workdir, toString ref ] callgit gitdir [ "worktree", "add", "--force", workdir, toString ref ]
res <- liftIO $ recursiveCheckDir (orgLintconfig jobOrg) workdir (orgEntrypoint jobOrg)
res <- recursiveCheckDir (orgLintconfig jobOrg) workdir (orgEntrypoint jobOrg)
setJobStatus done jobOrg jobRef $ setJobStatus done jobOrg jobRef $
Linted res rev Linted res rev
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment