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

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

import           Universum

import           CheckDir       (DirResult (dirresultMaps))
import           CheckMap       (MapResult (MapResult, mapresultBadges))
import           Data.Aeson     (ToJSON (..), (.=))
import qualified Data.Aeson     as A
import qualified Data.Aeson.Key as A
import           Data.Coerce    (coerce)
import qualified Data.Map       as M
import           Servant        (Handler, err404, throwError)
import           Server         (JobStatus (..), Org (orgUrl),
                                 RemoteRef (RemoteRef, reponame), ServerState,
                                 Sha1, getJobStatus, unState)

-- | an info type wrapped around the server state, to carry serialisation instances.
newtype AdminOverview =
  AdminOverview { unAdminOverview :: ServerState }


newtype MapService =
  MapService { unMapService :: ServerState }

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

instance ToJSON MapService where
  toJSON (MapService state) =
    toJSON $ M.mapWithKey orgObject (view unState state)
     where
      orgObject org = A.object . mapMaybe worldObject . M.elems
       where
        worldObject (RemoteRef {..}, job) = case job of
          Linted res rev ->
            Just (A.fromText reponame .=
                    M.mapWithKey (mapInfo rev) (dirresultMaps res))
          _ -> Nothing
        mapInfo rev mappath MapResult { .. } = A.object
                [ "badges" .= mapresultBadges
                , "url" .= (orgUrl org <> rev <> "/" <> toText mappath) ]



statusImpl :: MVar ServerState -> Text -> Sha1 -> Handler JobStatus
statusImpl state orgslug sha1 = do
   status <- liftIO $ getJobStatus state orgslug sha1
   case status of
     Just res -> pure $ snd res
     Nothing  -> throwError err404

-- | since there are multiple apis that just get state information …
stateImpl
  :: forall s
  .  Coercible s ServerState
  => MVar ServerState
  -> Handler s
stateImpl state = readMVar state <&> coerce