summaryrefslogtreecommitdiff
path: root/server/Handlers.hs
blob: cb714d938080cb9388e84ba348d1af410f401f63 (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
{-# LANGUAGE DataKinds         #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}

module Handlers (
                -- , submitImpl
                 statusImpl
                -- , relintImpl
                , adminOverviewImpl
                , AdminOverview(..)
                ) where

import           Universum

import           Control.Concurrent.MVar (withMVar)
import           Data.Aeson              (ToJSON (..), (.=))
import qualified Data.Aeson              as A
import qualified Data.Map                as M
import           Servant                 (Handler, err404, throwError)
import           Server                  (JobStatus (..), ServerState, Sha1,
                                          unState)

-- | annoying (and afaik unused), but has to be here for type system reasons
-- instance MonadFail Handler where
--   fail _ = throwError err500

-- -- | someone submitted a map; lint it (synchronously for now)
-- submitImpl :: Config True -> MVar ServerState -> RemoteRef -> App UUID
-- submitImpl config state ref = do
--   jobid <- liftIO UUID.nextRandom
--   -- TODO: these two should really be atomic
--   liftIO $ setJobStatus state ref Pending
--   liftIO $ setRegistry state jobid ref
--   cliconfig <- getCliConfig
--   -- we'll just forget the thread id for now and trust this terminates …
--   _ <- checkRef config cliconfig state ref
--   -- the submission itself can't really fail or return anything useful
--   pure jobid

-- relintImpl :: Config True -> MVar ServerState -> UUID -> App NoContent
-- relintImpl config state uuid = do
--   mref <- liftIO $ withMVar state (pure . M.lookup uuid . view registry)
--   case mref of
--     Nothing -> lift $ throwError err404
--     Just ref -> do
--       cliconfig <- getCliConfig
--       _ <- checkRef config cliconfig state ref
--       pure NoContent

-- | an info type wrapped around the server state, to carry serialisation instances.
-- TODO: should probably not be defined here
newtype AdminOverview =
  AdminOverview { unAdminOverview :: ServerState }

instance ToJSON AdminOverview where
  toJSON (AdminOverview state) =
    toJSON $ view unState state <&> \(ref, status) ->
      A.object [ "remote" .= ref
               , "status" .= status
               ]

statusImpl :: MVar ServerState -> Sha1 -> Handler JobStatus
statusImpl state sha1 = do
   status <- liftIO $ withMVar state $ \state ->
     pure $ M.lookup sha1 (map snd $ view unState state)
   case status of
     Just res -> pure res
     Nothing  -> throwError err404


adminOverviewImpl :: MVar ServerState -> Handler AdminOverview
adminOverviewImpl state = do
  state <- readMVar state
  pure (AdminOverview state)