Skip to content
Snippets Groups Projects
Commit 82082e8b authored by stuebinm's avatar stuebinm
Browse files

server: show helpful information for result

This includes the backlink to the lobby (auto-generated only for now)
and a "help!"-button for sending mails. Also general info regarding
which commit was linted / published.
parent d15920f7
No related branches found
No related tags found
No related merge requests found
...@@ -25,6 +25,9 @@ webdir = "/tmp/var/www/divoc" ...@@ -25,6 +25,9 @@ webdir = "/tmp/var/www/divoc"
# (part of urls for linted maps; allows indefinite browser caching) # (part of urls for linted maps; allows indefinite browser caching)
generation = 1 generation = 1
backlink_prefix = "world://lobby#start_"
contact_mail = "world@muc.hacc.space"
# linter's config for this org # linter's config for this org
lintconfig = "./config.json" lintconfig = "./config.json"
# map's entrypoint (only maps reachable from here are included) # map's entrypoint (only maps reachable from here are included)
......
...@@ -30,9 +30,9 @@ import Network.WebSockets (PendingConnection, acceptRequest, ...@@ -30,9 +30,9 @@ import Network.WebSockets (PendingConnection, acceptRequest,
withPingThread) withPingThread)
import Servant (Handler, err404, throwError) import Servant (Handler, err404, throwError)
import Server (JobStatus (..), Org (orgUrl), import Server (JobStatus (..), Org (orgUrl),
RemoteRef (RemoteRef, reponame), RemoteRef (reponame), ServerState,
ServerState, Sha1, adjustedPath, Sha1, adjustedPath, getJobStatus,
getJobStatus, unState) unState)
import Worker (Job (Job)) import Worker (Job (Job))
...@@ -64,12 +64,12 @@ instance ToJSON MapService where ...@@ -64,12 +64,12 @@ instance ToJSON MapService where
statusImpl :: MVar ServerState -> Text -> Sha1 -> Handler JobStatus statusImpl :: MVar ServerState -> Text -> Sha1 -> Handler (Org True, RemoteRef, JobStatus, Maybe JobStatus)
statusImpl state orgslug sha1 = do statusImpl state orgslug sha1 = do
status <- liftIO $ getJobStatus state orgslug sha1 status <- liftIO $ getJobStatus state orgslug sha1
case status of case status of
Just (_,_,jobstatus,_) -> pure jobstatus Just stuff -> pure stuff
Nothing -> throwError err404 Nothing -> throwError err404
-- | since there are multiple apis that just get state information … -- | since there are multiple apis that just get state information …
stateImpl stateImpl
......
...@@ -7,6 +7,8 @@ ...@@ -7,6 +7,8 @@
-- so it's safe to never define it -- so it's safe to never define it
{-# OPTIONS_GHC -Wno-missing-methods #-} {-# OPTIONS_GHC -Wno-missing-methods #-}
{-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
-- | Module containing orphan instances of Lucid's ToHtml, used for rendering -- | Module containing orphan instances of Lucid's ToHtml, used for rendering
-- linter results as html -- linter results as html
...@@ -19,6 +21,7 @@ import CheckDir (DirResult (..), MissingAsset (MissingAsset), ...@@ -19,6 +21,7 @@ import CheckDir (DirResult (..), MissingAsset (MissingAsset),
import CheckMap (MapResult (..)) import CheckMap (MapResult (..))
import Data.List.Extra (escapeJSON) import Data.List.Extra (escapeJSON)
import qualified Data.Map as M import qualified Data.Map as M
import qualified Data.Text as T
import Handlers (AdminOverview (..)) import Handlers (AdminOverview (..))
import Lucid (HtmlT, ToHtml) import Lucid (HtmlT, ToHtml)
import Lucid.Base (ToHtml (toHtml)) import Lucid.Base (ToHtml (toHtml))
...@@ -27,9 +30,10 @@ import Lucid.Html5 (a_, body_, button_, class_, code_, disabled_, ...@@ -27,9 +30,10 @@ import Lucid.Html5 (a_, body_, button_, class_, code_, disabled_,
href_, html_, id_, li_, link_, main_, href_, html_, id_, li_, link_, main_,
onclick_, p_, rel_, script_, span_, src_, onclick_, p_, rel_, script_, span_, src_,
title_, type_, ul_) title_, type_, ul_)
import Server (JobStatus (..), Org (orgSlug), import Server (JobStatus (..),
RemoteRef (reporef, repourl), prettySha, Org (Org, orgBacklinkPrefix, orgContactMail, orgSlug),
unState) RemoteRef (RemoteRef, reponame, reporef, repourl),
prettySha, unState)
import Types (Hint (Hint), Level (..)) import Types (Hint (Hint), Level (..))
...@@ -47,20 +51,29 @@ htmldoc inner = html_ $ do ...@@ -47,20 +51,29 @@ htmldoc inner = html_ $ do
link_ [rel_ "stylesheet", type_ "text/css", href_ "/style.css" ] link_ [rel_ "stylesheet", type_ "text/css", href_ "/style.css" ]
body_ $ main_ [class_ "main-content"] inner body_ $ main_ [class_ "main-content"] inner
instance ToHtml JobStatus where instance ToHtml (Org True, RemoteRef, JobStatus, Maybe JobStatus) where
toHtml status = htmldoc $ case status of toHtml (org@Org{..}, ref@RemoteRef{..}, status, published) = htmldoc $ case status of
Pending _ -> do Pending _ -> do
h1_ "Pending …" h1_ "Pending …"
p_ "(please note that this site won't auto-reload, you'll have to refresh it yourself)"
autoReloadScript autoReloadScript
Linted res _rev (pending, _) -> do Linted res rev (pending, _) -> do
h1_ "Linter Result" h1_ $ do
p_ $ do "Linter Result"
"your map will be re-linted periodically. "
if pending if pending
then button_ [class_ "btn btn-primary btn-disabled", disabled_ "true"] "pending …" then button_ [class_ "btn btn-primary btn-disabled", disabled_ "true"] "pending …"
else button_ [onclick_ "relint()", class_ "btn btn-primary", id_ "relint_button"] "relint now" else button_ [onclick_ "relint()", class_ "btn btn-primary", id_ "relint_button"] "relint now"
toHtml res a_ [class_ "btn btn-primary"
, href_ ("mailto:" <> orgContactMail <> "?subject=[Help-walint] " <> reponame <> " " <> rev)]
"Help?"
p_ $ do
"For commit "; code_ (toHtml $ T.take 7 rev); " of repository "
code_ (toHtml repourl); " (on "; code_ (toHtml reporef); ")"
p_ $ case published of
Just (Linted _ rev _) ->
do "Currently published commit: "; code_ (toHtml $ T.take 7 rev); "."
_ -> "This Map has not yet been published."
toHtml (org,ref,res)
script_ script_
"function relint() {\n\ "function relint() {\n\
\ var xhr = new XMLHttpRequest ();\n\ \ var xhr = new XMLHttpRequest ();\n\
...@@ -128,25 +141,39 @@ instance ToHtml Hint where ...@@ -128,25 +141,39 @@ instance ToHtml Hint where
headerText :: Monad m => Level -> HtmlT m () headerText :: Monad m => Level -> HtmlT m ()
headerText = \case headerText = \case
Info -> "Couldn't find a thing to complain about. Congratulations!" Info ->
Suggestion -> "There's a couple smaller nitpicks; maybe take a look at those?" "Couldn't find a thing to complain about. Congratulations!"
Warning -> "The map is fine, but some things look like they might be mistakes; \ Suggestion ->
\perhaps you want to take a look at those?" "There's a couple smaller nitpicks; maybe take a look at those? \
Forbidden -> "The map is fine in principle, but contains things that are not\ \But overall the map looks great!"
\allowed at this event" Warning ->
Error -> "Your map currently contains errors and should probably be fixed" "The map is fine, but some things look like they might be mistakes; \
Fatal -> "Something broke while linting; if you're not sure why or how to make \ \perhaps you want to take a look at those?"
\it work, feel free to tell an admin about it" Forbidden ->
"While this map might work well with workadventure, it contains \
\things that are not allowed at this event. Please change those \
\so we can publish the map"
Error ->
"Your map currently contains errors. You will have to fix those before \
\we can publish your map."
Fatal ->
"Something broke while linting; if you're not sure why or how to make \
\it work, feel free to tell an admin about it."
-- | The fully monky -- | The fully monky
instance ToHtml (DirResult a) where instance ToHtml (Org True, RemoteRef, DirResult a) where
toHtml res@DirResult { .. } = do toHtml (Org {..}, RemoteRef {..}, res@DirResult { .. }) = do
p_ $ do badge maxlevel "Linted:"; " "; headerText maxlevel p_ $ do badge maxlevel "Linted:"; " "; headerText maxlevel
h2_ "Exits" h2_ "Exits"
p_ $ do
"Note: to link back to the lobby, please use "
code_ $ toHtml $ orgBacklinkPrefix <> reponame
" as exitUrl."
-- the exit graph thing -- the exit graph thing
script_ [ src_ "/dot-wasm.js" ] (""::Text) script_ [ src_ "/dot-wasm.js" ] (""::Text)
script_ [ src_ "/d3.js" ] (""::Text) script_ [ src_ "/d3.js" ] (""::Text)
......
...@@ -44,11 +44,11 @@ import Servant.HTML.Lucid (HTML) ...@@ -44,11 +44,11 @@ import Servant.HTML.Lucid (HTML)
import Servant.Server.StaticFiles (serveDirectoryWebApp) import Servant.Server.StaticFiles (serveDirectoryWebApp)
import Server (CliOptions (..), import Server (CliOptions (..),
JobStatus, Org (..), JobStatus, Org (..),
ServerState, Sha1, RemoteRef, ServerState,
emptyState, exneuland, Sha1, emptyState,
interval, loadConfig, exneuland, interval,
orgs, port, token, loadConfig, orgs, port,
verbose) token, verbose)
import Worker (Job (Job), linterThread) import Worker (Job (Job), linterThread)
import Control.Monad.Logger (logInfoN, import Control.Monad.Logger (logInfoN,
...@@ -57,8 +57,7 @@ import Servant.API (Header) ...@@ -57,8 +57,7 @@ import Servant.API (Header)
import Servant.API.WebSocket (WebSocketPending) import Servant.API.WebSocket (WebSocketPending)
import Servant.Client (ClientM, client, import Servant.Client (ClientM, client,
mkClientEnv, runClientM) mkClientEnv, runClientM)
import Universum.Bool.Reexport (Bool) import WithCli (withCli)
import WithCli (HasArguments, withCli)
type family PolyEndpoint method format payload where type family PolyEndpoint method format payload where
PolyEndpoint Get format payload = PolyEndpoint Get format payload =
...@@ -72,7 +71,7 @@ type MapServiceAPI method = ...@@ -72,7 +71,7 @@ type MapServiceAPI method =
-- | abstract api -- | abstract api
type API format = type API format =
"status" :> Capture "org" Text :> Capture "jobid" Sha1 :> Get '[format] JobStatus "status" :> Capture "org" Text :> Capture "jobid" Sha1 :> Get '[format] (Org True, RemoteRef, JobStatus, Maybe JobStatus)
:<|> "status" :> Capture "org" Text :> Capture "jobid" Sha1 :> "relint" :> Post '[format] Text :<|> "status" :> Capture "org" Text :> Capture "jobid" Sha1 :> "relint" :> Post '[format] Text
:<|> "status" :> Capture "org" Text :> Capture "jobid" Sha1 :> "realtime" :> WebSocketPending :<|> "status" :> Capture "org" Text :> Capture "jobid" Sha1 :> "realtime" :> WebSocketPending
:<|> "admin" :> "overview" :> Get '[format] AdminOverview :<|> "admin" :> "overview" :> Get '[format] AdminOverview
......
...@@ -92,13 +92,15 @@ toSha ref = Sha1 ...@@ -92,13 +92,15 @@ toSha ref = Sha1
$ (show ref :: Text) $ (show ref :: Text)
data Org (loaded :: Bool) = Org data Org (loaded :: Bool) = Org
{ orgSlug :: Text { orgSlug :: Text
, orgLintconfig :: ConfigRes loaded (LintConfig Skeleton) , orgLintconfig :: ConfigRes loaded (LintConfig Skeleton)
, orgEntrypoint :: FilePath , orgEntrypoint :: FilePath
, orgGeneration :: Int , orgGeneration :: Int
, orgRepos :: [RemoteRef] , orgRepos :: [RemoteRef]
, orgUrl :: Text , orgUrl :: Text
, orgWebdir :: Text , orgWebdir :: Text
, orgBacklinkPrefix :: Text
, orgContactMail :: Text
} deriving (Generic) } deriving (Generic)
instance NFData (LintConfig Skeleton) => NFData (Org True) instance NFData (LintConfig Skeleton) => NFData (Org True)
...@@ -160,6 +162,8 @@ orgCodec = Org ...@@ -160,6 +162,8 @@ orgCodec = Org
<*> T.list remoteCodec "repo" .= orgRepos <*> T.list remoteCodec "repo" .= orgRepos
<*> T.text "url" .= orgUrl <*> T.text "url" .= orgUrl
<*> T.text "webdir" .= orgWebdir <*> T.text "webdir" .= orgWebdir
<*> T.text "backlink_prefix" .= orgBacklinkPrefix
<*> T.text "contact_mail" .= orgContactMail
-- why exactly does everything in tomland need to be invertable -- why exactly does everything in tomland need to be invertable
urlBimap :: TomlBiMap BaseUrl String urlBimap :: TomlBiMap BaseUrl String
......
...@@ -15,6 +15,11 @@ body { ...@@ -15,6 +15,11 @@ body {
font-family: Ubuntu, sans-serif; font-family: Ubuntu, sans-serif;
} }
.btn {
margin-left: 2em;
font-family: Ubuntu;
}
.main-content { .main-content {
padding: 2em; padding: 2em;
border-radius: 1em; border-radius: 1em;
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment