Add API for viewing progress logs

This commit is contained in:
Filip Gralinski 2021-07-30 12:19:27 +02:00
parent 51e98bee68
commit 0c5bbd63aa
7 changed files with 229 additions and 12 deletions

View File

@ -231,11 +231,15 @@ instance Yesod App where
isAuthorized CreateTeamR _ = isTrustedAuthorized isAuthorized CreateTeamR _ = isTrustedAuthorized
isAuthorized (TestProgressR _ _) _ = isTrustedAuthorized isAuthorized (TestProgressR _ _) _ = isTrustedAuthorized
isAuthorized (TestProgressJsonR _ _) _ = return Authorized
isAuthorized SwaggerR _ = return Authorized isAuthorized SwaggerR _ = return Authorized
isAuthorized (ViewProgressWithWebSocketsR _) _ = isTrustedAuthorized isAuthorized (ViewProgressWithWebSocketsR _) _ = isTrustedAuthorized
isAuthorized (ViewProgressWithWebSocketsJsonR _) _ = return Authorized
isAuthorized (ViewProgressLogR _) _ = return Authorized
-- Default to Authorized for now. -- Default to Authorized for now.
isAuthorized _ _ = isTrustedAuthorized isAuthorized _ _ = isTrustedAuthorized

View File

@ -1,5 +1,6 @@
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE QuasiQuotes #-}
module Handler.Shared where module Handler.Shared where
@ -12,6 +13,8 @@ import Yesod.WebSockets
import Handler.Runner import Handler.Runner
import System.Exit import System.Exit
import Handler.JWT
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Encoding as DTE import qualified Data.Text.Encoding as DTE
@ -117,7 +120,7 @@ consoleApp jobId = do
m <- readTVar jobs m <- readTVar jobs
case IntMap.lookup jobId m of case IntMap.lookup jobId m of
Nothing -> return Nothing Nothing -> return Nothing
Just chan -> fmap Just $ dupTChan chan Just chan -> fmap Just $ cloneTChan chan
case mchan of case mchan of
Nothing -> do Nothing -> do
sendTextData ("CANNOT FIND THE OUTPUT (ALREADY SHOWN??)" :: Text) sendTextData ("CANNOT FIND THE OUTPUT (ALREADY SHOWN??)" :: Text)
@ -135,10 +138,27 @@ consoleApp jobId = do
return () return ()
getViewProgressWithWebSocketsR :: Int -> Handler Html getViewProgressWithWebSocketsJsonR :: Int -> Handler Value
getViewProgressWithWebSocketsR jobId = do getViewProgressWithWebSocketsJsonR jobId = do
webSockets $ consoleApp jobId webSockets $ consoleApp jobId
defaultLayout $ do return $ String $ pack $ show jobId
getViewProgressLogR :: Int -> Handler Html
getViewProgressLogR jobId = do
webSockets $ consoleApp jobId
p <- widgetToPageContent logWidget
hamletToRepHtml [hamlet|
<html>
<head>
<title>
#{pageTitle p}
^{pageHead p}
<body>
^{pageBody p}
|]
logWidget = do
[whamlet| [whamlet|
<div #outwindow> <div #outwindow>
<div #output> <div #output>
@ -196,6 +216,11 @@ getViewProgressWithWebSocketsR jobId = do
|] |]
getViewProgressWithWebSocketsR :: Int -> Handler Html
getViewProgressWithWebSocketsR jobId = do
webSockets $ consoleApp jobId
defaultLayout logWidget
runViewProgressAsynchronously :: (Channel -> Handler ()) -> Handler Value runViewProgressAsynchronously :: (Channel -> Handler ()) -> Handler Value
runViewProgressAsynchronously action = runViewProgressGeneralized getJobIdAsJson action runViewProgressAsynchronously action = runViewProgressGeneralized getJobIdAsJson action
-- where getJobIdAsJson jobId = return $ Number (scientific (toInteger jobId) 0) -- where getJobIdAsJson jobId = return $ Number (scientific (toInteger jobId) 0)
@ -208,9 +233,11 @@ runViewProgress' route action = runViewProgressGeneralized doRedirection action
runViewProgressGeneralized :: (Int -> Handler v) -> (Channel -> Handler ()) -> Handler v runViewProgressGeneralized :: (Int -> Handler v) -> (Channel -> Handler ()) -> Handler v
runViewProgressGeneralized handler action = do runViewProgressGeneralized handler action = do
App {..} <- getYesod App {..} <- getYesod
jobId <- randomInt jobId' <- randomInt
-- we don't want negative numbers (so that nobody would be confused)
let jobId = abs jobId'
chan <- liftIO $ atom $ do chan <- liftIO $ atom $ do
chan <- newBroadcastTChan chan <- newTChan
m <- readTVar jobs m <- readTVar jobs
writeTVar jobs $ IntMap.insert jobId chan m writeTVar jobs $ IntMap.insert jobId chan m
return chan return chan
@ -221,10 +248,10 @@ runViewProgressGeneralized handler action = do
liftIO $ atom $ do liftIO $ atom $ do
writeTChan chan $ Just "All done\n" writeTChan chan $ Just "All done\n"
writeTChan chan Nothing writeTChan chan Nothing
m <- readTVar jobs -- TODO we don't remove logs, they could clog up the memory
writeTVar jobs $ IntMap.delete jobId m -- m <- readTVar jobs
-- writeTVar jobs $ IntMap.delete jobId m
handler jobId handler jobId
data RepoCloningSpec = RepoCloningSpec { data RepoCloningSpec = RepoCloningSpec {
cloningSpecRepo :: RepoSpec, cloningSpecRepo :: RepoSpec,
cloningSpecReferenceRepo :: RepoSpec cloningSpecReferenceRepo :: RepoSpec
@ -497,7 +524,7 @@ getViewProgressR jobId = do
m <- readTVar jobs m <- readTVar jobs
case IntMap.lookup jobId m of case IntMap.lookup jobId m of
Nothing -> return Nothing Nothing -> return Nothing
Just chan -> fmap Just $ dupTChan chan Just chan -> fmap Just $ cloneTChan chan
case mchan of case mchan of
Nothing -> notFound Nothing -> notFound
Just chan -> respondSource typePlain $ do Just chan -> respondSource typePlain $ do

View File

@ -1610,6 +1610,48 @@ challengeLayout withHeader challenge widget = do
getTestProgressR :: Int -> Int -> Handler TypedContent getTestProgressR :: Int -> Int -> Handler TypedContent
getTestProgressR m d = runViewProgress $ doTestProgress m d getTestProgressR m d = runViewProgress $ doTestProgress m d
getTestProgressJsonR :: Int -> Int -> Handler Value
getTestProgressJsonR m d = do
_ <- requireAuthPossiblyByToken
runViewProgressAsynchronously $ doTestProgress m d
declareTestProgressSwagger :: Declare (Definitions Schema) Swagger
declareTestProgressSwagger = do
-- param schemas
let numberSchema = toParamSchema (Proxy :: Proxy Int)
numberResponse <- declareResponse (Proxy :: Proxy Int)
return $ mempty
& paths .~
fromList [ ("/api/test-progress/{num}/{delay}",
mempty & DS.get ?~ (mempty
& parameters .~ [ Inline $ mempty
& name .~ "num"
& description ?~ "The number up to which to count"
& required ?~ True
& schema .~ ParamOther (mempty
& in_ .~ ParamPath
& paramSchema .~ numberSchema),
Inline $ mempty
& name .~ "delay"
& description ?~ "Delay in seconds"
& required ?~ True
& schema .~ ParamOther (mempty
& in_ .~ ParamPath
& paramSchema .~ numberSchema)
]
& produces ?~ MimeList ["application/json"]
& description ?~ "Counts up to a given number, returns an ID of an asynchronous job. This is just a sample end-point for testing logging of asynchronous jobs."
& at 200 ?~ Inline numberResponse))
]
testProgressApi :: Swagger
testProgressApi = spec & definitions .~ defs
where
(defs, spec) = runDeclare declareTestProgressSwagger mempty
doTestProgress :: Int -> Int -> Channel -> Handler () doTestProgress :: Int -> Int -> Channel -> Handler ()
doTestProgress m d chan = do doTestProgress m d chan = do
_ <- forM [1..m] $ (\i -> do _ <- forM [1..m] $ (\i -> do
@ -1617,3 +1659,32 @@ doTestProgress m d chan = do
liftIO $ threadDelay (d * 1000000) liftIO $ threadDelay (d * 1000000)
return ()) return ())
return () return ()
declareViewProgressWithWebSocketsSwagger :: Declare (Definitions Schema) Swagger
declareViewProgressWithWebSocketsSwagger = do
-- param schemas
let numberSchema = toParamSchema (Proxy :: Proxy Int)
numberResponse <- declareResponse (Proxy :: Proxy Int)
return $ mempty
& paths .~
fromList [ ("/api/view-progress-with-web-sockets/{jobId}",
mempty & DS.get ?~ (mempty
& parameters .~ [ Inline $ mempty
& name .~ "jobId"
& description ?~ "The ID for the job to be shown"
& required ?~ True
& schema .~ ParamOther (mempty
& in_ .~ ParamPath
& paramSchema .~ numberSchema)]
& produces ?~ MimeList ["application/json"]
& description ?~ "Initiates a web socket communication with which progress logs can be read. Returns just the Job ID (the same number as the parameter)"
& at 200 ?~ Inline numberResponse))
]
viewProgressWithWebSockets :: Swagger
viewProgressWithWebSockets = spec & definitions .~ defs
where
(defs, spec) = runDeclare declareViewProgressWithWebSocketsSwagger mempty

View File

@ -31,6 +31,8 @@ apiDescription = generalApi
<> myTeamsApi <> myTeamsApi
<> challengeImgApi <> challengeImgApi
<> challengeRepoApi <> challengeRepoApi
<> testProgressApi
<> viewProgressWithWebSockets
generalApi :: Swagger generalApi :: Swagger
generalApi = (mempty :: Swagger) generalApi = (mempty :: Swagger)

View File

@ -101,7 +101,9 @@ application, this feature is on the way).
5. Set _Web Origin_ for the `gonito` client in Keycloak (e.g. simply add `*` there). 5. Set _Web Origin_ for the `gonito` client in Keycloak (e.g. simply add `*` there).
6. Set `JSON_WEB_KEY` variable to the content of the JWK key (or `GONITO_JSON_WEB_KEY` when using docker-compose) 6. Add some test user, set up some first/last name for them.
7. Set `JSON_WEB_KEY` variable to the content of the JWK key (or `GONITO_JSON_WEB_KEY` when using docker-compose)
and run Gonito. and run Gonito.
If you create a new user, you need to run `/api/add-info` GET If you create a new user, you need to run `/api/add-info` GET

View File

@ -10,7 +10,10 @@
/view-progress/#Int ViewProgressR GET /view-progress/#Int ViewProgressR GET
/open-view-progress/#Int OpenViewProgressR GET /open-view-progress/#Int OpenViewProgressR GET
/view-progress-with-web-sockets/#Int ViewProgressWithWebSocketsR GET /view-progress-with-web-sockets/#Int ViewProgressWithWebSocketsR GET
/api/view-progress-with-web-sockets/#Int ViewProgressWithWebSocketsJsonR GET
/api/view-progress-log/#Int ViewProgressLogR GET
/test-progress/#Int/#Int TestProgressR GET /test-progress/#Int/#Int TestProgressR GET
/api/test-progress/#Int/#Int TestProgressJsonR GET
/list-challenges ListChallengesR GET /list-challenges ListChallengesR GET
/api/list-challenges ListChallengesJsonR GET /api/list-challenges ListChallengesJsonR GET

View File

@ -1,6 +1,39 @@
<html> <html>
<head> <head>
<!-- This is an example of how to create a front-end using the Gonito
backend.
The code is ugly, but it is as simple as possible, no front-end
framework was assumed!
-->
<style type="text/css" media="screen">
#outwindow {
border: 2px solid black;
margin-bottom: 1em;
color: white;
background-color: black;
padding: 10pt;
}
#outwindow pre {
color: white;
background-color: black;
}
#wait {
animation: blink 1s linear infinite;
}
@keyframes blink {
0% {
opacity: 0;
}
50% {
opacity: .5;
}
100% {
opacity: 1;
}
</style>
<script src="/static/js/keycloak.js"></script> <script src="/static/js/keycloak.js"></script>
<script> <script>
var keycloak; var keycloak;
@ -82,6 +115,69 @@
xhr.send(); xhr.send();
} }
var getJSON = function(url, callback) {
var xhr = new XMLHttpRequest();
xhr.open('GET', '/api/' + url, true);
xhr.setRequestHeader('Accept', 'application/json');
xhr.setRequestHeader('Authorization', 'Bearer ' + keycloak.token);
xhr.responseType = 'json';
xhr.onload = function() {
callback(xhr.response);
};
xhr.send();
};
// This is an example of how to handle logs obtained by an
// asynchronous process.
// As an example, "/api/test-progress/10/2" end-point was used
// (which just counts up to 10 with 2-second delays), it a
// similar way logs from, for example,
// "/api/challenge-submission/..." end-point could be handled
function testLogs() {
getJSON('test-progress/10/2', function(data) {
// the end-point just returns a job id, then we invoke
// the '/api/view-progress-with-web-sockets/' with this
// job Id
url = 'view-progress-with-web-sockets/' + data;
getJSON('view-progress-with-web-sockets/' + data, function(data) {
var output = document.getElementById("output");
var wait = document.getElementById("wait");
var seealso = document.getElementById("seealso");
wait.appendChild(document.createTextNode('... PLEASE WAIT ...'));
var parsed_url = new URL(document.URL);
var ws_protocol = 'wss://';
if (parsed_url.protocol == 'http:') {
ws_protocol = 'ws://';
}
msg = "The logs will be also available at "
+ parsed_url.protocol
+ "//"
+ parsed_url.host
+ '/api/view-progress-log/' + data;
seealso.appendChild(document.createTextNode(msg));
conn = new WebSocket(ws_protocol + parsed_url.host + '/api/' + url);
conn.onmessage = function(e) {
var p = document.createElement("pre");
p.appendChild(document.createTextNode(e.data));
output.appendChild(p);
};
conn.onclose = function(e) {
wait.parentNode.removeChild(wait);
};
});
});
}
</script> </script>
</head> </head>
<body onload="initKeycloak()"> <body onload="initKeycloak()">
@ -101,5 +197,17 @@
<p><button onclick="testCors()">CORS</button></p> <p><button onclick="testCors()">CORS</button></p>
<p><button onclick="testLogs()">Logs</button></p>
<p id="seealso"></p>
<div id="outwindow">
<div id="output">
</div>
<div id="wait">
</div>
</div>
</body> </body>
</html> </html>