summaryrefslogtreecommitdiff
path: root/server/Worker.hs
blob: 8b3903c226150e38ccf44086046c7af55b4fd711 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
{-# LANGUAGE DataKinds           #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE RecordWildCards     #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell     #-}

module Worker (linterThread, Job(..)) where

import           Universum

import           CheckDir                      (recursiveCheckDir,
                                                shrinkDirResult)
import           Control.Concurrent.Async      (async, link)
import           Control.Concurrent.STM        (writeTChan)
import           Control.Concurrent.STM.TQueue
import           Control.Exception             (IOException, handle)
import           Control.Monad.Logger          (logError, logErrorN, logInfoN,
                                                runStdoutLoggingT)
import qualified Data.Text                     as T
import qualified Data.UUID                     as UUID
import qualified Data.UUID.V4                  as UUID
import           Fmt                           ((+|), (|+))
import           Server                        (Config, JobStatus (..),
                                                Org (..),
                                                RealtimeMsg (RelintPending, Reload),
                                                RemoteRef (reporef, repourl),
                                                ServerState, adjustedPath,
                                                getJobStatus,
                                                newRealtimeChannel,
                                                setJobStatus, tmpdir, toSha)
import           System.Directory              (doesDirectoryExist)
import           System.Exit                   (ExitCode (ExitFailure, ExitSuccess))
import           System.FilePath               ((</>))
import           System.Process
import           WriteRepo                     (writeAdjustedRepository)

data Job = Job
  { jobRef :: RemoteRef
  , jobOrg :: Org True
  }

linterThread :: Config True -> TQueue Job -> MVar ServerState -> IO Void
linterThread config queue done = forever $ do
  next <- atomically (readTQueue queue)
  -- TODO: this doesn't guard against two jobs running on the same repo!
  job <- async $ runJob config next done
  -- TODO: is this a good idea? will crash the server if a job thread fails
  link job

-- | the actual check function. Calls out to git to update the
-- repository, create a new worktree, lints it, then tells git to
-- delete that tree again.
--
-- May occasionally be brittle (if someone else changed files)
-- TODO: re-add proper fancy (colourful?) logging
runJob :: Config True -> Job -> MVar ServerState -> IO ()
runJob config Job {..} done = do
  rand <- UUID.nextRandom
  let workdir = "/tmp" </> ("worktree-" <> UUID.toString rand)

  handle whoops
    $ finally (lint workdir) (cleanup workdir)
  where
    lint workdir = do
      maybeRealtime <- getJobStatus done (orgSlug jobOrg) (toSha jobRef) >>= \case
        Nothing -> pure Nothing
        Just (org, ref, jobstatus) -> case jobstatus of
          Linted res rev (_, realtime) -> do
            setJobStatus done org ref (Linted res rev (True, realtime))
            pure $ Just realtime
          Pending realtime -> pure $ Just realtime
          _ -> pure Nothing

      whenJust maybeRealtime $ \realtime ->
        atomically $ writeTChan realtime RelintPending

      ifM (doesDirectoryExist gitdir)
        -- TODO: these calls fail for dumb http, add some fallback!
        (callgit gitdir
         [ "fetch", "origin", toString ref, "--depth", "1" ])
        (callgit gitdir
         [ "clone", toString ref, "--bare"
         , "--depth", "1", "-b", toString ref])
      rev <- map T.strip -- git returns a newline here
        $ readgit' gitdir ["rev-parse", toString ref]

      let outPath = adjustedPath rev jobOrg

      callgit gitdir [ "worktree", "add", "--force", workdir, toString ref ]

      res <- recursiveCheckDir (orgLintconfig jobOrg) workdir (orgEntrypoint jobOrg)
               >>= evaluateNF

      writeAdjustedRepository (orgLintconfig jobOrg) workdir (toString outPath) res
        >>= runStdoutLoggingT . \case
        ExitSuccess ->
          logInfoN $ "linted map "+| (show jobRef :: Text) |+"."
        ExitFailure 1 ->
          logInfoN $ "linted map "+| (show jobRef :: Text) |+ ", which failed."
        ExitFailure 2 ->
          -- TODO: shouldn't have linted this map at all
          logErrorN $ "outpath "+|outPath|+" already exists!"
        ExitFailure _ ->
          -- writeAdjustedRepository does not return other codes
          $(logError) "wtf, this is impossible"

      realtime <- case maybeRealtime of
        Just realtime -> do
          atomically $ writeTChan realtime Reload
          pure realtime
        Nothing ->
          newRealtimeChannel

      setJobStatus done jobOrg jobRef $
        Linted (shrinkDirResult res) rev (False, realtime)


    cleanup workdir = do
      callgit gitdir [ "worktree", "remove", "-f", "-f", workdir ]

    whoops (error :: IOException) = runStdoutLoggingT $ do
      logErrorN (show error)
      liftIO $ setJobStatus done jobOrg jobRef $ Failed (show error)

    url = repourl jobRef
    ref = reporef jobRef
    callgit = callgit'
    gitdir = view tmpdir config </> toString hashedname
    hashedname = T.map escapeSlash url
      where escapeSlash = \case { '/' -> '-'; a -> a }

readgit' :: MonadIO m => FilePath -> [String] -> m Text
readgit' dir args = map toText $
  liftIO $ do
    print args
    readProcess "git" ([ "-C", toString dir ] <> args) ""

callgit' :: MonadIO m => FilePath -> [String] -> m ()
callgit' dir args =
  liftIO $ do
    print args
    callProcess "git" ([ "-C", toString dir ] <> args)