clean up and generalize code generating param charts
This commit is contained in:
parent
5105652838
commit
e263a37eca
@ -5,8 +5,7 @@ module Foundation where
|
|||||||
import Database.Persist.Sql (ConnectionPool, runSqlPool)
|
import Database.Persist.Sql (ConnectionPool, runSqlPool)
|
||||||
import Import.NoFoundation
|
import Import.NoFoundation
|
||||||
import Text.Hamlet (hamletFile)
|
import Text.Hamlet (hamletFile)
|
||||||
import Yesod.Auth.HashDB (HashDBUser(..),authHashDB,authHashDBWithForm)
|
import Yesod.Auth.HashDB (HashDBUser(..), authHashDBWithForm)
|
||||||
import Yesod.Auth.Message (AuthMessage (InvalidLogin))
|
|
||||||
import qualified Yesod.Core.Unsafe as Unsafe
|
import qualified Yesod.Core.Unsafe as Unsafe
|
||||||
import Yesod.Core.Types (Logger)
|
import Yesod.Core.Types (Logger)
|
||||||
import Yesod.Default.Util (addStaticContentExternal)
|
import Yesod.Default.Util (addStaticContentExternal)
|
||||||
@ -50,6 +49,7 @@ mkMessage "App" "messages" "en"
|
|||||||
-- | A convenient synonym for creating forms.
|
-- | A convenient synonym for creating forms.
|
||||||
type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget)
|
type Form x = Html -> MForm (HandlerT App IO) (FormResult x, Widget)
|
||||||
|
|
||||||
|
isTrustedAuthorized :: (AuthEntity (HandlerSite m) ~ User, AuthId (HandlerSite m) ~ Key User, MonadHandler m, YesodAuthPersist (HandlerSite m)) => m AuthResult
|
||||||
isTrustedAuthorized = do
|
isTrustedAuthorized = do
|
||||||
mauth <- maybeAuth
|
mauth <- maybeAuth
|
||||||
case mauth of
|
case mauth of
|
||||||
@ -58,6 +58,7 @@ isTrustedAuthorized = do
|
|||||||
| isTrusted user -> return Authorized
|
| isTrusted user -> return Authorized
|
||||||
| otherwise -> return $ Unauthorized "???"
|
| otherwise -> return $ Unauthorized "???"
|
||||||
|
|
||||||
|
isAdmin :: (AuthEntity (HandlerSite m) ~ User, AuthId (HandlerSite m) ~ Key User, MonadHandler m, YesodAuthPersist (HandlerSite m)) => m AuthResult
|
||||||
isAdmin = do
|
isAdmin = do
|
||||||
mauth <- maybeAuth
|
mauth <- maybeAuth
|
||||||
case mauth of
|
case mauth of
|
||||||
@ -153,7 +154,7 @@ instance Yesod App where
|
|||||||
|
|
||||||
isAuthorized (ApiTxtScoreR _) _ = return Authorized
|
isAuthorized (ApiTxtScoreR _) _ = return Authorized
|
||||||
|
|
||||||
isAuthorized (ChallengeParamGraphDataR _ _) _ = return Authorized
|
isAuthorized (ChallengeParamGraphDataR _ _ _) _ = return Authorized
|
||||||
|
|
||||||
-- Default to Authorized for now.
|
-- Default to Authorized for now.
|
||||||
isAuthorized _ _ = isTrustedAuthorized
|
isAuthorized _ _ = isTrustedAuthorized
|
||||||
@ -228,6 +229,7 @@ contactEmailLabel site =
|
|||||||
Nothing -> ""
|
Nothing -> ""
|
||||||
where maybeContactMail = appContactEmail $ appSettings site
|
where maybeContactMail = appContactEmail $ appSettings site
|
||||||
|
|
||||||
|
myLoginForm :: App -> Route site -> WidgetFor site ()
|
||||||
myLoginForm site action = $(whamletFile "templates/auth.hamlet")
|
myLoginForm site action = $(whamletFile "templates/auth.hamlet")
|
||||||
|
|
||||||
instance YesodAuthPersist App
|
instance YesodAuthPersist App
|
||||||
|
@ -18,17 +18,15 @@ data ParamGraphItem = ParamGraphItem TableEntry Text Text MetricValue
|
|||||||
|
|
||||||
data ParamGraphSeries = ParamGraphSeries Text [(TableEntry, Text, MetricValue)]
|
data ParamGraphSeries = ParamGraphSeries Text [(TableEntry, Text, MetricValue)]
|
||||||
|
|
||||||
getChallengeParamGraphDataR :: Text -> Text -> Handler Value
|
getChallengeParamGraphDataR :: Text -> (Key Test) -> Text -> Handler Value
|
||||||
getChallengeParamGraphDataR challengeName paramName = do
|
getChallengeParamGraphDataR challengeName testId paramName = do
|
||||||
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName challengeName
|
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
|
|
||||||
(entries, tests) <- getChallengeSubmissionInfos (const True) challengeId
|
(entries, tests) <- getChallengeSubmissionInfos (const True) challengeId
|
||||||
|
|
||||||
let mainTestId = entityKey $ getMainTest tests
|
|
||||||
|
|
||||||
let values = map (findParamValue paramName) entries
|
let values = map (findParamValue paramName) entries
|
||||||
|
|
||||||
let items = Data.Maybe.catMaybes $ map (toParamGraphItem mainTestId paramName) $ zip entries values
|
let items = Data.Maybe.catMaybes $ map (toParamGraphItem testId paramName) $ zip entries values
|
||||||
|
|
||||||
let series = map (\(label, rs) -> ParamGraphSeries label rs)
|
let series = map (\(label, rs) -> ParamGraphSeries label rs)
|
||||||
$ organizeBy
|
$ organizeBy
|
||||||
|
@ -529,16 +529,16 @@ challengeAllSubmissionsWidget :: Maybe UserId
|
|||||||
challengeAllSubmissionsWidget muserId challenge scheme challengeRepo submissions tests params =
|
challengeAllSubmissionsWidget muserId challenge scheme challengeRepo submissions tests params =
|
||||||
$(widgetFile "challenge-all-submissions")
|
$(widgetFile "challenge-all-submissions")
|
||||||
where chartJSs = mconcat $ map (getChartJs challenge mainTest) params
|
where chartJSs = mconcat $ map (getChartJs challenge mainTest) params
|
||||||
mainTest = entityVal $ getMainTest tests
|
mainTest = getMainTest tests
|
||||||
|
|
||||||
getChartJs :: Challenge
|
getChartJs :: Challenge
|
||||||
-> Test
|
-> Entity Test
|
||||||
-> Text
|
-> Text
|
||||||
-> JavascriptUrl (Route App)
|
-> JavascriptUrl (Route App)
|
||||||
getChartJs challenge test param = [julius|
|
getChartJs challenge (Entity testId test) param = [julius|
|
||||||
$.getJSON("@{ChallengeParamGraphDataR (challengeName challenge) param}", function(data) {
|
$.getJSON("@{ChallengeParamGraphDataR (challengeName challenge) testId param}", function(data) {
|
||||||
c3.generate({
|
c3.generate({
|
||||||
bindto: '#chart-' + #{toJSON param},
|
bindto: '#chart-' + #{toJSON param} + '-' + #{toJSON testId},
|
||||||
data: data,
|
data: data,
|
||||||
axis: {
|
axis: {
|
||||||
x: {
|
x: {
|
||||||
|
@ -20,7 +20,7 @@
|
|||||||
/challenge-how-to/#Text ChallengeHowToR GET
|
/challenge-how-to/#Text ChallengeHowToR GET
|
||||||
/challenge-graph-data/#Text ChallengeGraphDataR GET
|
/challenge-graph-data/#Text ChallengeGraphDataR GET
|
||||||
/challenge-discussion/#Text ChallengeDiscussionR GET POST
|
/challenge-discussion/#Text ChallengeDiscussionR GET POST
|
||||||
/challenge-param-graph-data/#Text/#Text ChallengeParamGraphDataR GET
|
/challenge-param-graph-data/#Text/#TestId/#Text ChallengeParamGraphDataR GET
|
||||||
/challenge-discussion-rss/#Text ChallengeDiscussionFeedR GET
|
/challenge-discussion-rss/#Text ChallengeDiscussionFeedR GET
|
||||||
/trigger-remotely TriggerRemotelyR POST
|
/trigger-remotely TriggerRemotelyR POST
|
||||||
/trigger-locally TriggerLocallyR POST
|
/trigger-locally TriggerLocallyR POST
|
||||||
|
@ -15,7 +15,7 @@ $if not (null params)
|
|||||||
<h3>Graphs by parameters
|
<h3>Graphs by parameters
|
||||||
|
|
||||||
$forall param <- params
|
$forall param <- params
|
||||||
<div id="chart-#{param}"></div>
|
<div id="chart-#{param}-#{toPathPiece $ entityKey mainTest}"></div>
|
||||||
|
|
||||||
<script src="/static/js/d3.min.js" charset="utf-8"></script>
|
<script src="/static/js/d3.min.js" charset="utf-8"></script>
|
||||||
<script src="/static/js/c3.min.js"></script>
|
<script src="/static/js/c3.min.js"></script>
|
||||||
|
Loading…
Reference in New Issue
Block a user