summaryrefslogtreecommitdiff
path: root/server/Server.hs
blob: d7205bc4dae766761726c4282b9ade508278a0c0 (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
{-# LANGUAGE BangPatterns               #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeApplications           #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE TypeOperators              #-}

module Server (loadConfig, Config(..), RemoteRef(..), State, registry, jobs, JobStatus(..),
                    setJobStatus,defaultState,setRegistry, AdminOverview(..)) where

import           CheckDir             (DirResult)
import           Control.Concurrent   (MVar, modifyMVar_)
import           Data.Aeson           (FromJSON, ToJSON (toJSON), eitherDecode,
                                       (.=))
import qualified Data.Aeson           as A
import qualified Data.ByteString.Lazy as LB
import           Data.Map             (Map)
import qualified Data.Map             as M
import           Data.Text            (Text)
import           Data.UUID            (UUID)
import           GHC.Generics         (Generic)
import           Lens.Micro           (over)
import           Lens.Micro.Extras    (view)
import           Lens.Micro.TH
import           LintConfig           (LintConfig')
import           System.Exit.Compat   (exitFailure)
import           Toml                 (TomlCodec)
import qualified Toml                 as T

-- | a reference in a remote git repository
data RemoteRef = RemoteRef
  { repourl :: Text
  , reporef :: Text
  } deriving (Generic, FromJSON, ToJSON, Eq, Ord)

type family ConfigRes (b :: Bool) a where
  ConfigRes True a = a
  ConfigRes False a = FilePath

-- | the server's configuration
data Config (loaded :: Bool) = Config
  { tmpdir     :: FilePath
  -- ^ dir to clone git things in
  , port       :: Int
  -- ^ port to bind to
  , entrypoint :: FilePath
  , lintconfig :: ConfigRes loaded LintConfig'
  } deriving Generic

configCodec :: TomlCodec (Config False)
configCodec = Config
    <$> T.string "tmpdir" T..= tmpdir
    <*> T.int "port" T..= port
    <*> T.string "entrypoint" T..= entrypoint
    <*> T.string "lintconfig" T..= lintconfig

-- | a job status (of a specific uuid)
data JobStatus =
  Pending | Linted DirResult | Failed Text
  deriving (Generic, ToJSON)

-- | the server's global state
data State = State
  { _jobs     :: Map RemoteRef JobStatus
  , _registry :: Map UUID RemoteRef
  }
makeLenses ''State

defaultState :: State
defaultState = State mempty mempty

newtype AdminOverview =
  AdminOverview { unAdminOverview :: State }

instance ToJSON AdminOverview where
  toJSON (AdminOverview state) =
    toJSON . flip M.mapWithKey (view registry state) $ \uuid ref ->
      A.object [ "reference" .= uuid
               , "remote" .= ref
               , "status" .= M.lookup ref (view jobs state)
               ]



loadConfig :: FilePath -> IO (Config True)
loadConfig path = do
  res <- T.decodeFileEither configCodec path
  case res of
    Right config -> loadConfig' config
    Left err -> do
      print err
      exitFailure

loadConfig' :: Config False -> IO (Config True)
loadConfig' config = do
  loaded <- LB.readFile (lintconfig config) >>= \res ->
      case eitherDecode res :: Either String LintConfig' of
        Left err   -> error $ "config file invalid: " <> err
        Right file -> pure file
  pure $ config { lintconfig = loaded }


setJobStatus :: MVar State -> RemoteRef -> JobStatus -> IO ()
setJobStatus mvar !ref !status = modifyMVar_ mvar
  $ 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)