gonito/Handler/ShowChallenge.hs

761 lines
33 KiB
Haskell
Raw Normal View History

2015-09-04 23:23:32 +02:00
module Handler.ShowChallenge where
import Import
2018-07-05 22:17:25 +02:00
import Yesod.Form.Bootstrap3 (BootstrapFormLayout (..), renderBootstrap3, bfs)
2017-09-22 14:23:03 +02:00
import qualified Data.Text.Lazy as TL
2015-09-06 14:24:49 +02:00
import Text.Markdown
2015-09-29 14:15:49 +02:00
import qualified Data.Text as T
2015-12-12 18:53:20 +01:00
import qualified Yesod.Table as Table
2015-09-06 14:24:49 +02:00
import Handler.Extract
import Handler.Shared
2018-06-05 08:22:51 +02:00
import Handler.Runner
2015-12-12 18:53:20 +01:00
import Handler.Tables
2017-09-27 19:38:42 +02:00
import Handler.TagUtils
2018-07-24 15:33:35 +02:00
import Handler.MakePublic
2019-02-22 14:41:43 +01:00
import Handler.Dashboard
2019-03-20 16:31:08 +01:00
import Handler.Common
2019-12-14 14:10:50 +01:00
import Handler.Evaluate
2015-09-06 14:24:49 +02:00
2020-05-30 23:40:03 +02:00
import Data.Maybe (fromJust)
2019-08-29 21:34:13 +02:00
import Text.Blaze
2020-05-30 23:40:03 +02:00
import Data.Aeson
import Gonito.ExtractMetadata (ExtractionOptions(..),
extractMetadataFromRepoDir,
GonitoMetadata(..),
2018-11-12 20:41:46 +01:00
parseTags,
Link(..))
2018-09-01 14:23:41 +02:00
import qualified Text.Read as TR
2015-09-29 18:23:11 +02:00
import GEval.Core
import GEval.EvaluationScheme
2015-09-29 22:31:56 +02:00
2015-09-29 14:15:49 +02:00
import PersistSHA1
2017-09-22 14:23:03 +02:00
import System.IO (readFile)
2017-09-28 16:11:22 +02:00
import Data.Text (pack, unpack)
2018-07-28 17:04:27 +02:00
import Data.List (nub)
2018-11-13 16:15:02 +01:00
import qualified Database.Esqueleto as E
import Database.Esqueleto ((^.))
2020-10-15 22:27:16 +02:00
instance ToJSON LeaderboardEntry where
toJSON entry = object
[ "submitter" .= (formatSubmitter $ leaderboardUser entry)
, "when" .= (submissionStamp $ leaderboardBestSubmission entry)
, "version" .= (formatVersion $ leaderboardVersion entry)
, "description" .= descriptionToBeShown (leaderboardBestSubmission entry)
(leaderboardBestVariant entry)
(leaderboardParams entry)
, "times" .= leaderboardNumberOfSubmissions entry
]
getLeaderboardJsonR :: Text -> Handler Value
getLeaderboardJsonR name = do
app <- getYesod
let leaderboardStyle = appLeaderboardStyle $ appSettings app
Entity challengeId _ <- runDB $ getBy404 $ UniqueName name
(leaderboard, (_, tests)) <- getLeaderboardEntries 1 leaderboardStyle challengeId
return $ array $ map (leaderboardEntryJson tests) leaderboard
leaderboardEntryJson tests entry = object [
"metadata" .= entry,
"metrics" .=
map (\e@(Entity _ t) -> object [
"metric" .= testName t,
"score" .= (formatTruncatedScore (getTestFormattingOpts t) $ extractScoreFromLeaderboardEntry (getTestReference e) entry)]) tests]
2015-09-04 23:23:32 +02:00
getShowChallengeR :: Text -> Handler Html
getShowChallengeR name = do
2018-09-08 21:21:21 +02:00
app <- getYesod
let leaderboardStyle = appLeaderboardStyle $ appSettings app
2019-03-20 16:31:08 +01:00
challengeEnt@(Entity challengeId challenge) <- runDB $ getBy404 $ UniqueName name
2015-09-28 17:45:10 +02:00
Just repo <- runDB $ get $ challengePublicRepo challenge
(leaderboard, (entries, tests)) <- getLeaderboardEntries 1 leaderboardStyle challengeId
showAltLeaderboard <- runDB $ hasMetricsOfSecondPriority challengeId
(altLeaderboard, altTests) <- if showAltLeaderboard
then
do
(leaderboard', (_, tests')) <- getLeaderboardEntries 3 ByTag challengeId
return $ (Just leaderboard', Just tests')
else
return (Nothing, Nothing)
2016-02-16 21:10:10 +01:00
mauth <- maybeAuth
2018-09-01 14:23:41 +02:00
let params = getNumericalParams entries
let scheme = appRepoScheme $ appSettings app
challengeRepo <- runDB $ get404 $ challengePublicRepo challenge
2019-03-20 16:31:08 +01:00
challengeLayout True challenge (showChallengeWidget mauth
challengeEnt
scheme
2018-07-28 21:36:45 +02:00
challengeRepo
repo
leaderboard
altLeaderboard
params
tests
altTests)
2020-02-22 19:12:07 +01:00
hasMetricsOfSecondPriority :: (PersistQueryRead backend, MonadIO m, BaseBackend backend ~ SqlBackend) => Key Challenge -> ReaderT backend m Bool
hasMetricsOfSecondPriority challengeId = do
tests' <- selectList [TestChallenge ==. challengeId, TestActive ==. True] []
let tests = filter (\t -> (evaluationSchemePriority $ testMetric $ entityVal t) == 2) tests'
return $ not (null tests)
2015-09-06 14:24:49 +02:00
getChallengeReadmeR :: Text -> Handler Html
getChallengeReadmeR name = do
2016-05-16 23:44:28 +02:00
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
readme <- challengeReadme name
challengeLayout False challenge $ toWidget readme
2018-07-14 07:42:28 +02:00
challengeReadme :: Text -> HandlerFor App Html
2016-05-16 23:44:28 +02:00
challengeReadme name = do
2015-09-06 14:24:49 +02:00
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
let repoId = challengePublicRepo challenge
2016-01-08 21:57:29 +01:00
repoDir <- getRepoDir repoId
2015-09-06 14:24:49 +02:00
let readmeFilePath = repoDir </> readmeFile
2019-08-29 21:34:13 +02:00
theContents <- liftIO $ System.IO.readFile readmeFilePath
return $ markdown def $ TL.pack theContents
2015-09-06 14:24:49 +02:00
2019-03-20 16:31:08 +01:00
showChallengeWidget :: Maybe (Entity User)
-> Entity Challenge
2018-07-28 21:36:45 +02:00
-> RepoScheme
-> Repo
-> Repo
-> [LeaderboardEntry]
-> (Maybe [LeaderboardEntry])
-> [Text]
-> [Entity Test]
-> (Maybe [Entity Test])
2018-07-28 21:36:45 +02:00
-> WidgetFor App ()
2019-03-20 16:31:08 +01:00
showChallengeWidget mUserEnt
(Entity challengeId challenge)
scheme
challengeRepo
repo
leaderboard
mAltLeaderboard
params
tests
mAltTests
= $(widgetFile "show-challenge")
2015-12-12 18:53:20 +01:00
where leaderboardWithRanks = zip [1..] leaderboard
mAltLeaderboardWithRanks = zip [1..] <$> mAltLeaderboard
maybeRepoLink = getRepoLink repo
delta = Number 4
higherTheBetterArray = getIsHigherTheBetterArray $ map entityVal tests
2019-03-20 16:31:08 +01:00
mUserId = entityKey <$> mUserEnt
getRepoLink :: Repo -> Maybe Text
getRepoLink repo
| sitePrefix `isPrefixOf` url = Just $ (browsableGitRepo bareRepoName) ++ "/" ++ (repoBranch repo)
| otherwise = Nothing
where sitePrefix = "git://gonito.net/" :: Text
sitePrefixLen = length sitePrefix
url = repoUrl repo
bareRepoName = drop sitePrefixLen url
2015-09-06 14:24:49 +02:00
2015-11-11 22:10:41 +01:00
getChallengeHowToR :: Text -> Handler Html
getChallengeHowToR name = do
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
maybeUser <- maybeAuth
2017-09-28 16:51:10 +02:00
2018-06-05 23:04:58 +02:00
app <- getYesod
let settings = appSettings app
let publicRepoId = challengePublicRepo challenge
repo <- runDB $ get404 publicRepoId
2018-06-05 23:04:58 +02:00
2017-09-28 16:51:10 +02:00
case maybeUser of
Just (Entity userId user) -> do
enableTriggerToken userId (userTriggerToken user)
Nothing -> return ()
let mToken = case maybeUser of
Just (Entity _ user) -> userTriggerToken user
Nothing -> Nothing
2017-09-25 12:47:01 +02:00
let isIDSet = case maybeUser of
Just (Entity _ user) -> isJust $ userLocalId user
Nothing -> False
isSSHUploaded <- case maybeUser of
Just (Entity userId _) -> do
2018-07-28 17:30:00 +02:00
ukeys <- runDB $ selectList [PublicKeyUser ==. userId] []
return $ not (null ukeys)
2017-09-25 12:47:01 +02:00
Nothing -> return False
2018-07-28 17:30:00 +02:00
challengeLayout False challenge (challengeHowTo
challenge
settings
repo
(idToBeShown challenge maybeUser)
isIDSet
isSSHUploaded
(join $ userAltRepoScheme <$> entityVal <$> maybeUser)
2018-07-28 17:30:00 +02:00
mToken)
2015-11-11 22:10:41 +01:00
2018-07-14 07:42:28 +02:00
idToBeShown :: p -> Maybe (Entity User) -> Text
2018-07-28 17:04:27 +02:00
idToBeShown _ maybeUser =
2015-11-11 22:10:41 +01:00
case maybeUser of
Just user -> case userLocalId $ entityVal user of
Just localId -> localId
Nothing -> defaultIdToBe
Nothing -> defaultIdToBe
where defaultIdToBe = "YOURID" :: Text
defaultRepo :: RepoScheme -> Text -> Challenge -> Repo -> Maybe (Entity User) -> Text
defaultRepo SelfHosted repoHost challenge _ maybeUser = repoHost ++ (idToBeShown challenge maybeUser) ++ "/" ++ (challengeName challenge)
defaultRepo Branches _ _ repo _ = repoUrl repo
2018-07-14 07:42:28 +02:00
defaultBranch :: IsString a => RepoScheme -> Maybe a
defaultBranch SelfHosted = Just "master"
defaultBranch Branches = Nothing
2015-11-11 22:10:41 +01:00
challengeHowTo :: Challenge -> AppSettings -> Repo -> Text -> Bool -> Bool -> Maybe Text -> Maybe Text -> WidgetFor App ()
challengeHowTo challenge settings repo shownId isIDSet isSSHUploaded mAltRepoScheme mToken = $(widgetFile "challenge-how-to")
where myBranch = "my-brilliant-branch" :: Text
urlToYourRepo = case mAltRepoScheme of
Just altRepoScheme -> encodeSlash (altRepoScheme <> (challengeName challenge))
Nothing -> "URL_TO_YOUR_REPO"
2015-09-06 15:33:37 +02:00
2019-03-20 16:31:08 +01:00
postArchiveR :: ChallengeId -> Handler Html
postArchiveR challengeId = doSetArchive True challengeId
postUnarchiveR :: ChallengeId -> Handler Html
postUnarchiveR challengeId = doSetArchive False challengeId
doSetArchive :: Bool -> ChallengeId -> Handler Html
doSetArchive status challengeId = do
runDB $ update challengeId [ChallengeArchived =. Just status]
challenge <- runDB $ get404 challengeId
getShowChallengeR $ challengeName challenge
archiveForm :: ChallengeId -> Form ChallengeId
archiveForm challengeId = renderBootstrap3 BootstrapBasicForm $ areq hiddenField "" (Just challengeId)
2015-09-06 15:33:37 +02:00
getChallengeSubmissionR :: Text -> Handler Html
getChallengeSubmissionR name = do
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
2015-11-11 22:10:41 +01:00
maybeUser <- maybeAuth
Just repo <- runDB $ get $ challengePublicRepo challenge
app <- getYesod
let scheme = appRepoScheme $ appSettings app
let repoHost = appRepoHost $ appSettings app
let defaultUrl = fromMaybe (defaultRepo scheme repoHost challenge repo maybeUser)
((<> name) <$> (join $ userAltRepoScheme <$> entityVal <$> maybeUser))
(formWidget, formEnctype) <- generateFormPost $ submissionForm (Just defaultUrl) (defaultBranch scheme) (repoGitAnnexRemote repo)
2015-09-06 15:33:37 +02:00
challengeLayout True challenge $ challengeSubmissionWidget formWidget formEnctype challenge
postChallengeSubmissionR :: Text -> Handler TypedContent
postChallengeSubmissionR name = do
2018-07-14 07:42:28 +02:00
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName name
((result, _), _) <- runFormPost $ submissionForm Nothing Nothing Nothing
2020-03-28 18:08:44 +01:00
let submissionData' = case result of
2015-09-06 15:33:37 +02:00
FormSuccess res -> Just res
_ -> Nothing
2020-03-28 18:08:44 +01:00
Just submissionData = submissionData'
2015-09-06 15:33:37 +02:00
2017-09-28 11:29:48 +02:00
userId <- requireAuthId
2020-03-28 18:08:44 +01:00
runViewProgress $ doCreateSubmission userId challengeId submissionData
2017-09-28 11:29:48 +02:00
2017-09-28 16:11:22 +02:00
postTriggerLocallyR :: Handler TypedContent
postTriggerLocallyR = do
(Just challengeName) <- lookupPostParam "challenge"
(Just localId) <- lookupPostParam "user"
mBranch <- lookupPostParam "branch"
mGitAnnexRemote <- lookupPostParam "git-annex-remote"
2017-09-28 16:11:22 +02:00
[Entity userId _] <- runDB $ selectList [UserLocalId ==. Just localId] []
2019-12-07 22:34:24 +01:00
app <- getYesod
let repoHost = appRepoHost $ appSettings app
let localRepo = repoHost ++ localId ++ "/" ++ challengeName
trigger userId challengeName localRepo mBranch mGitAnnexRemote
2017-09-28 16:11:22 +02:00
2017-09-28 11:29:48 +02:00
postTriggerRemotelyR :: Handler TypedContent
postTriggerRemotelyR = do
2017-09-28 16:11:22 +02:00
(Just challengeName) <- lookupPostParam "challenge"
2017-09-28 11:29:48 +02:00
(Just url) <- lookupPostParam "url"
2017-09-28 16:11:22 +02:00
(Just token) <- lookupPostParam "token"
2017-09-28 11:29:48 +02:00
mBranch <- lookupPostParam "branch"
mGitAnnexRemote <- lookupPostParam "git-annex-remote"
2020-02-21 22:56:39 +01:00
doTrigger token challengeName url mBranch mGitAnnexRemote
postTriggerRemotelySimpleR :: Text -> Text -> Text -> Text -> Handler TypedContent
postTriggerRemotelySimpleR token challengeName url branch =
doTrigger token challengeName (decodeSlash url) (Just branch) Nothing
2020-02-21 22:56:39 +01:00
getTriggerRemotelySimpleR :: Text -> Text -> Text -> Text -> Handler TypedContent
getTriggerRemotelySimpleR token challengeName url branch =
doTrigger token challengeName (decodeSlash url) (Just branch) Nothing
2020-02-21 22:56:39 +01:00
2020-05-30 23:40:03 +02:00
data GitServerPayload = GitServerPayload {
gitServerPayloadRef :: Text,
-- Unfortunately, the URL is given in "ssh_url" field
-- for Gogs and "git_ssh_url" for GitLab, hence two
-- fields here
gitServerPayloadSshUrl :: Maybe Text,
gitServerPayloadGitSshUrl :: Maybe Text
}
deriving (Show, Eq)
instance FromJSON GitServerPayload where
parseJSON (Object o) = GitServerPayload
<$> o .: "ref"
<*> ((o .: "repository") >>= (.:? "ssh_url"))
<*> ((o .: "repository") >>= (.:? "git_ssh_url"))
postTriggerByWebhookR :: Text -> Text -> Handler TypedContent
postTriggerByWebhookR token challengeName = do
payload <- requireJsonBody :: Handler GitServerPayload
let ref = gitServerPayloadRef payload
let refPrefix = "refs/heads/"
if refPrefix `isPrefixOf` ref
then
do
let branch = T.replace refPrefix "" ref
let url = fromMaybe (fromJust $ gitServerPayloadGitSshUrl payload)
(gitServerPayloadSshUrl payload)
doTrigger token challengeName url (Just branch) Nothing
else
error $ "unexpected ref `" ++ (T.unpack ref) ++ "`"
2020-02-21 22:56:39 +01:00
doTrigger :: Text -> Text -> Text -> Maybe Text -> Maybe Text -> Handler TypedContent
doTrigger token challengeName url mBranch mGitAnnexRemote = do
2017-09-28 16:11:22 +02:00
[Entity userId _] <- runDB $ selectList [UserTriggerToken ==. Just token] []
trigger userId challengeName url mBranch mGitAnnexRemote
2017-09-28 16:11:22 +02:00
trigger :: UserId -> Text -> Text -> Maybe Text -> Maybe Text -> Handler TypedContent
trigger userId challengeName url mBranch mGitAnnexRemote = do
2017-09-28 11:29:48 +02:00
let branch = fromMaybe "master" mBranch
2017-09-28 16:11:22 +02:00
mChallengeEnt <- runDB $ getBy $ UniqueName challengeName
2020-03-28 18:08:44 +01:00
let defSubmission = ChallengeSubmissionData {
challengeSubmissionDataDescription = Nothing,
challengeSubmissionDataTags = Nothing,
challengeSubmissionDataRepo = RepoSpec {
repoSpecUrl=url,
repoSpecBranch=branch,
repoSpecGitAnnexRemote=mGitAnnexRemote}
}
2017-09-28 16:11:22 +02:00
case mChallengeEnt of
2020-03-28 18:08:44 +01:00
Just (Entity challengeId _) -> runOpenViewProgress $ doCreateSubmission userId challengeId defSubmission
2017-09-28 16:11:22 +02:00
Nothing -> return $ toTypedContent (("Unknown challenge `" ++ (Data.Text.unpack challengeName) ++ "`. Cannot be triggered, must be submitted manually at Gonito.net!\n") :: String)
2017-09-28 11:29:48 +02:00
2019-09-24 22:52:25 +02:00
isBefore :: UTCTime -> Maybe UTCTime -> Bool
isBefore _ Nothing = True
isBefore moment (Just deadline) = moment <= deadline
2020-05-30 21:56:52 +02:00
-- | An attempt to filtre out mistaken/unwanted submissions (without cloning
-- the submission repo, just by looking at the metadata)
willClone :: Challenge -> ChallengeSubmissionData -> Bool
2020-05-30 22:06:21 +02:00
willClone challenge submissionData =
(challengeName challenge) `isInfixOf` url && branch /= dontPeek && not (dontPeek `isInfixOf` url)
2020-05-30 21:56:52 +02:00
where url = repoSpecUrl $ challengeSubmissionDataRepo submissionData
2020-05-30 22:06:21 +02:00
branch = repoSpecBranch $ challengeSubmissionDataRepo submissionData
dontPeek = "dont-peek"
2020-05-30 21:56:52 +02:00
-- | Main place where submission is done (whether manually or by trigger)
doCreateSubmission :: UserId -> Key Challenge -> ChallengeSubmissionData -> Channel -> Handler ()
2020-03-28 18:08:44 +01:00
doCreateSubmission userId challengeId challengeSubmissionData chan = do
2019-03-20 16:31:08 +01:00
challenge <- runDB $ get404 challengeId
2019-09-24 22:52:25 +02:00
version <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
theNow <- liftIO getCurrentTime
if theNow `isBefore` (versionDeadline $ entityVal version)
then
2020-05-30 21:56:52 +02:00
do
let wanted = willClone challenge challengeSubmissionData
if wanted
then
doCreateSubmission' (challengeArchived challenge) userId challengeId challengeSubmissionData chan
else
msg chan "Refusing to clone the submission from this URL"
2019-09-24 22:52:25 +02:00
else
msg chan "Submission is past the deadline, no submission will be accepted from now on."
2019-03-20 16:31:08 +01:00
2020-03-28 18:08:44 +01:00
doCreateSubmission' :: Maybe Bool -> UserId -> Key Challenge -> ChallengeSubmissionData -> Channel -> Handler ()
doCreateSubmission' (Just True) _ _ _ chan = msg chan "This challenge is archived, you cannot submit to it. Ask the site admin to unarchive it."
doCreateSubmission' _ userId challengeId challengeSubmissionData chan = do
let mDescription = challengeSubmissionDataDescription challengeSubmissionData
let mTags = challengeSubmissionDataTags challengeSubmissionData
let repoSpec = challengeSubmissionDataRepo challengeSubmissionData
maybeRepoKey <- getSubmissionRepo userId challengeId repoSpec chan
case maybeRepoKey of
2015-09-28 23:43:55 +02:00
Just repoId -> do
2018-11-12 22:01:51 +01:00
2018-11-14 17:41:01 +01:00
challenge <- runDB $ get404 challengeId
2018-11-14 20:59:40 +01:00
user <- runDB $ get404 userId
2018-11-14 17:41:01 +01:00
2019-02-22 14:41:43 +01:00
relevantIndicators <- getOngoingTargets challengeId
2019-09-10 08:59:30 +02:00
(Entity mainTestId mainTest) <- runDB $ fetchMainTest challengeId
(Entity _ currentVersion) <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
let submittedMajorVersion = versionMajor currentVersion
2018-11-13 16:15:02 +01:00
let orderDirection = case getMetricOrdering (evaluationSchemeMetric $ testMetric mainTest) of
2018-11-13 16:15:02 +01:00
TheHigherTheBetter -> E.desc
TheLowerTheBetter -> E.asc
2019-09-10 08:59:30 +02:00
bestResultSoFar <- runDB $ E.select $ E.from $ \(evaluation, submission, variant, out, test, version) -> do
2018-11-13 16:15:02 +01:00
E.where_ (submission ^. SubmissionChallenge E.==. E.val challengeId
2018-11-17 09:49:25 +01:00
E.&&. submission ^. SubmissionIsHidden E.==. E.val False
2018-11-13 16:15:02 +01:00
E.&&. variant ^. VariantSubmission E.==. submission ^. SubmissionId
E.&&. evaluation ^. EvaluationChecksum E.==. out ^. OutChecksum
2018-11-14 17:41:01 +01:00
E.&&. (E.not_ (E.isNothing (evaluation ^. EvaluationScore)))
2018-11-13 16:15:02 +01:00
E.&&. out ^. OutVariant E.==. variant ^. VariantId
2019-09-10 08:59:30 +02:00
E.&&. evaluation ^. EvaluationTest E.==. test ^. TestId
E.&&. test ^. TestChallenge E.==. E.val challengeId
E.&&. test ^. TestName E.==. E.val (testName mainTest)
E.&&. test ^. TestMetric E.==. E.val (testMetric mainTest)
E.&&. test ^. TestActive
2019-12-14 14:10:50 +01:00
E.&&. (evaluation ^. EvaluationVersion E.==. E.just (version ^. VersionCommit)
E.||. E.isNothing (evaluation ^. EvaluationVersion))
2019-09-10 08:59:30 +02:00
E.&&. version ^. VersionCommit E.==. test ^. TestCommit
E.&&. version ^. VersionMajor E.>=. E.val submittedMajorVersion)
2018-11-13 16:15:02 +01:00
E.orderBy [orderDirection (evaluation ^. EvaluationScore)]
E.limit 1
return evaluation
let bestScoreSoFar = join (evaluationScore <$> entityVal <$> (listToMaybe bestResultSoFar))
2018-11-12 22:01:51 +01:00
case bestScoreSoFar of
Just s -> msg chan ("best score so far is: " ++ (Data.Text.pack $ show s))
Nothing -> msg chan "first submission so far"
2015-09-28 23:43:55 +02:00
repo <- runDB $ get404 repoId
repoDir <- getRepoDirOrClone repoId chan
gonitoMetadata <- liftIO
$ extractMetadataFromRepoDir repoDir (ExtractionOptions {
extractionOptionsDescription = mDescription,
extractionOptionsTags = Just $ parseTags mTags,
extractionOptionsGeneralParams = Nothing,
2018-11-03 12:30:39 +01:00
extractionOptionsUnwantedParams = Nothing,
extractionOptionsParamFiles = Nothing,
2018-11-13 14:48:41 +01:00
extractionOptionsMLRunPath = Nothing,
2018-11-16 12:43:44 +01:00
extractionOptionsExternalLinks = Nothing,
extractionOptionsDependencies = Nothing })
submissionId <- getSubmission userId
repoId
(repoCurrentCommit repo)
challengeId
(gonitoMetadataDescription gonitoMetadata)
chan
2018-11-12 20:41:46 +01:00
_ <- runDB $ mapM insert $ map (\l -> ExternalLink {
externalLinkSubmission = submissionId,
externalLinkTitle = linkTitle l,
externalLinkUrl = linkUrl l }) $ gonitoMetadataExternalLinks gonitoMetadata
_ <- runDB $ mapM insertUnique $ map (\s -> Dependency {
dependencySubRepoCommit = s,
dependencySuperRepoCommit = (repoCurrentCommit repo) }) $ gonitoMetadataDependencies gonitoMetadata
2018-11-16 12:43:44 +01:00
2020-09-05 15:07:23 +02:00
outs <- getOuts False chan submissionId (gonitoMetadataGeneralParams gonitoMetadata)
2018-11-12 22:01:51 +01:00
2018-11-14 20:59:40 +01:00
currentTagIds <- runDB $ selectList [SubmissionTagSubmission ==. submissionId] []
runDB $ addTags submissionId (gonitoMetadataTags gonitoMetadata) (
map (submissionTagTag . entityVal) currentTagIds)
msg chan "SUBMISSION CREATED"
app <- getYesod
2018-11-12 22:01:51 +01:00
newScores <- mapM (getScoreForOut mainTestId) outs
let newScores' = catMaybes newScores
let newScores'' = case getMetricOrdering (evaluationSchemeMetric $ testMetric mainTest) of
2018-11-12 22:01:51 +01:00
TheHigherTheBetter -> reverse $ sort newScores'
TheLowerTheBetter -> sort newScores'
let compOp = case getMetricOrdering (evaluationSchemeMetric $ testMetric mainTest) of
2018-11-12 22:01:51 +01:00
TheLowerTheBetter -> (<)
TheHigherTheBetter -> (>)
2019-02-22 14:41:43 +01:00
let submissionLink = slackLink app "submission" ("q/" ++ (fromSHA1ToText (repoCurrentCommit repo)))
2018-11-12 22:01:51 +01:00
case bestScoreSoFar of
Just b -> case newScores'' of
(s:_) -> if compOp s b
2018-11-14 17:41:01 +01:00
then
do
2018-11-14 20:59:40 +01:00
let challengeLink = slackLink app (challengeTitle challenge) ("challenge/"
++ (challengeName challenge))
let message = ("Whoa! New best result for "
++ challengeLink
++ " challenge by "
++ (fromMaybe "???" $ userName user)
++ ", "
2018-11-14 17:41:01 +01:00
++ (T.pack $ show $ testMetric mainTest)
2018-11-14 20:59:40 +01:00
++ ": "
++ (formatScore (testPrecision mainTest) s)
2018-11-14 17:41:01 +01:00
++ " ("
++ (if s > b
then "+"
else "")
2018-11-14 20:59:40 +01:00
++ (formatScore (testPrecision mainTest) (s-b))
++ ")."
++ " See " ++ submissionLink ++ "."
++ " :clap:")
2018-11-14 17:41:01 +01:00
msg chan message
case appNewBestResultSlackHook $ appSettings app of
Just "" -> return ()
2018-11-14 17:41:01 +01:00
Just hook -> liftIO $ runSlackHook hook message
Nothing -> return ()
2018-11-12 22:01:51 +01:00
else return ()
[] -> return ()
Nothing -> return ()
2018-07-24 15:33:35 +02:00
if appAutoOpening $ appSettings app
then
doMakePublic userId submissionId chan
2018-07-24 15:33:35 +02:00
else
return ()
2019-02-22 14:41:43 +01:00
if not (null relevantIndicators)
then
checkIndicators user challengeId submissionId submissionLink relevantIndicators chan
else
return ()
2015-09-28 23:43:55 +02:00
Nothing -> return ()
2019-02-22 14:41:43 +01:00
checkIndicators :: User -> ChallengeId -> SubmissionId -> Text -> [IndicatorEntry] -> Channel -> Handler ()
checkIndicators user challengeId submissionId submissionLink relevantIndicators chan = do
msg chan "Checking indicators..."
theNow <- liftIO $ getCurrentTime
mapM_ (\indicator -> checkIndicator theNow user challengeId submissionId submissionLink indicator chan) relevantIndicators
checkIndicator :: UTCTime -> User -> ChallengeId -> SubmissionId -> Text -> IndicatorEntry -> Channel -> Handler ()
checkIndicator theNow user challengeId submissionId submissionLink indicator chan = do
(entries, _) <- runDB $ getChallengeSubmissionInfos 1 (\(Entity sid _) -> sid == submissionId) (const True) id challengeId
2019-02-22 14:41:43 +01:00
mapM_ (\t -> checkTarget theNow user submissionLink entries indicator t chan) (indicatorEntryTargets indicator)
checkTarget :: UTCTime -> User -> Text -> [TableEntry] -> IndicatorEntry -> Entity Target -> Channel -> Handler ()
checkTarget theNow user submissionLink entries indicator target chan = do
app <- getYesod
let status = getTargetStatus theNow entries indicator target
if status == TargetPassed
then
do
let message = "Congratulations!!! The target " ++ indicatorText
++ " was beaten by "
++ (fromMaybe "???" $ userName user)
++ ", "
++ " See " ++ submissionLink ++ "."
++ (T.replicate 10 " :champagne: ") ++ " :mleczko: "
msg chan message
case appNewBestResultSlackHook $ appSettings app of
Just "" -> return ()
Just hook -> liftIO $ runSlackHook hook message
Nothing -> return ()
else
return ()
where indicatorText = prettyIndicatorEntry indicator
2019-08-29 21:34:13 +02:00
getScoreForOut :: (PersistQueryRead (YesodPersistBackend site), YesodPersist site, BaseBackend (YesodPersistBackend site) ~ SqlBackend) => Key Test -> Out -> HandlerFor site (Maybe Double)
2018-11-12 22:01:51 +01:00
getScoreForOut mainTestId out = do
mEvaluation <- runDB $ selectFirst [EvaluationChecksum ==. (outChecksum out),
EvaluationTest ==. mainTestId]
[]
return $ case mEvaluation of
Just evaluation -> evaluationScore $ entityVal evaluation
Nothing -> Nothing
2017-09-28 11:29:48 +02:00
getSubmission :: UserId -> Key Repo -> SHA1 -> Key Challenge -> Text -> Channel -> Handler (Key Submission)
getSubmission userId repoId commit challengeId description chan = do
2019-08-27 22:36:51 +02:00
challenge <- runDB $ get404 challengeId
2015-09-29 14:15:49 +02:00
maybeSubmission <- runDB $ getBy $ UniqueSubmissionRepoCommitChallenge repoId commit challengeId
case maybeSubmission of
Just (Entity submissionId _) -> do
2015-09-29 14:15:49 +02:00
msg chan "Submission already there, re-checking"
return submissionId
Nothing -> do
msg chan "Creating new submission"
time <- liftIO getCurrentTime
runDB $ insert $ Submission {
submissionRepo=repoId,
submissionCommit=commit,
submissionChallenge=challengeId,
submissionDescription=description,
2015-09-30 20:32:06 +02:00
submissionStamp=time,
2016-02-14 08:44:16 +01:00
submissionSubmitter=userId,
submissionIsPublic=False,
2019-08-27 22:36:51 +02:00
submissionIsHidden=False,
submissionVersion=challengeVersion challenge}
2015-09-29 14:15:49 +02:00
getSubmissionRepo :: UserId -> Key Challenge -> RepoSpec -> Channel -> Handler (Maybe (Key Repo))
2019-08-29 08:56:22 +02:00
getSubmissionRepo userId challengeId repoSpec chan = getPossiblyExistingRepo checkRepoAvailibility userId challengeId repoSpec chan
2015-09-28 23:43:55 +02:00
checkRepoAvailibility :: Key Challenge -> Key Repo -> Channel -> Handler Bool
checkRepoAvailibility challengeId repoId chan = do
maybeOtherChallengeId <- runDB $ selectFirst ( [ChallengePublicRepo ==. repoId]
||. [ChallengePrivateRepo ==. repoId]) []
case maybeOtherChallengeId of
Just _ -> do
err chan "Repository already used as a challenge repo, please use a different repo or a different branch"
return False
Nothing -> do
maybeOtherSubmissionId <- runDB $ selectFirst [SubmissionRepo ==. repoId,
SubmissionChallenge !=. challengeId] []
case maybeOtherSubmissionId of
Just _ -> do
err chan "Repository already used as a submission repo for a different challenge, please use a different repo or a different branch"
return False
Nothing -> return True
2019-08-29 21:34:13 +02:00
challengeSubmissionWidget :: (ToMarkup a1, ToWidget App a2) => a2 -> a1 -> Challenge -> WidgetFor App ()
2015-09-06 15:33:37 +02:00
challengeSubmissionWidget formWidget formEnctype challenge = $(widgetFile "challenge-submission")
2020-03-28 18:08:44 +01:00
data ChallengeSubmissionData = ChallengeSubmissionData {
challengeSubmissionDataDescription :: Maybe Text,
challengeSubmissionDataTags :: Maybe Text,
challengeSubmissionDataRepo :: RepoSpec }
submissionForm :: Maybe Text -> Maybe Text -> Maybe Text -> Form ChallengeSubmissionData
submissionForm defaultUrl defBranch defaultGitAnnexRemote = renderBootstrap3 BootstrapBasicForm $ ChallengeSubmissionData
<$> aopt textField (fieldWithTooltip MsgSubmissionDescription MsgSubmissionDescriptionTooltip) Nothing
2017-09-27 19:38:42 +02:00
<*> aopt textField (tagsfs MsgSubmissionTags) Nothing
2020-03-28 18:08:44 +01:00
<*> (RepoSpec <$> areq textField (bfs MsgSubmissionUrl) defaultUrl
<*> areq textField (bfs MsgSubmissionBranch) defBranch
<*> aopt textField (bfs MsgSubmissionGitAnnexRemote) (Just defaultGitAnnexRemote))
2015-09-06 15:33:37 +02:00
2015-09-29 22:31:56 +02:00
getChallengeMySubmissionsR :: Text -> Handler Html
2015-09-30 20:42:25 +02:00
getChallengeMySubmissionsR name = do
userId <- requireAuthId
getChallengeSubmissions (\(Entity _ submission) -> (submissionSubmitter submission == userId)) name
2015-09-29 22:31:56 +02:00
getChallengeAllSubmissionsR :: Text -> Handler Html
2015-09-30 20:42:25 +02:00
getChallengeAllSubmissionsR name = getChallengeSubmissions (\_ -> True) name
getChallengeSubmissions :: ((Entity Submission) -> Bool) -> Text -> Handler Html
getChallengeSubmissions condition name = do
Entity challengeId challenge <- runDB $ getBy404 $ UniqueName name
(evaluationMaps, tests') <- runDB $ getChallengeSubmissionInfos 1 condition (const True) id challengeId
2018-09-08 21:24:25 +02:00
let tests = sortBy testComparator tests'
2016-02-16 21:10:10 +01:00
mauth <- maybeAuth
let muserId = (\(Entity uid _) -> uid) <$> mauth
2015-09-29 22:31:56 +02:00
app <- getYesod
let scheme = appRepoScheme $ appSettings app
challengeRepo <- runDB $ get404 $ challengePublicRepo challenge
2018-09-01 14:23:41 +02:00
let params = getNumericalParams evaluationMaps
2018-07-28 17:04:27 +02:00
2018-07-28 17:30:00 +02:00
challengeLayout True challenge (challengeAllSubmissionsWidget muserId
challenge
scheme
challengeRepo
evaluationMaps
tests
params)
2018-09-01 14:23:41 +02:00
getNumericalParams :: [TableEntry] -> [Text]
getNumericalParams entries = filter (isNumericalParam entries) $ getAllParams entries
isNumericalParam :: [TableEntry] -> Text -> Bool
isNumericalParam entries param =
all doesTextRepresentNumber
$ concat
$ map ((map parameterValue)
. (filter (\p -> parameterName p == param))
. (map entityVal)
. tableEntryParams) entries
doesTextRepresentNumber :: Text -> Bool
doesTextRepresentNumber t = isJust $ ((TR.readMaybe $ T.unpack t) :: Maybe Double)
getAllParams :: [TableEntry] -> [Text]
getAllParams entries = sort
$ nub
$ concat
$ map (\entry -> map (parameterName . entityVal) (tableEntryParams entry)) entries
2018-07-28 17:30:00 +02:00
challengeAllSubmissionsWidget :: Maybe UserId
-> Challenge
-> RepoScheme
-> Repo
-> [TableEntry]
-> [Entity Test]
-> [Text]
-> WidgetFor App ()
2018-07-28 17:04:27 +02:00
challengeAllSubmissionsWidget muserId challenge scheme challengeRepo submissions tests params =
$(widgetFile "challenge-all-submissions")
2018-11-12 10:11:58 +01:00
where delta = Number 4
higherTheBetterArray = getIsHigherTheBetterArray $ map entityVal tests
2018-07-28 22:02:47 +02:00
paramGraphsWidget :: Challenge -> [Entity Test] -> [Text] -> WidgetFor App ()
paramGraphsWidget challenge tests params = $(widgetFile "param-graphs")
2018-09-01 14:01:17 +02:00
where chartJSs = getChartJss challenge selectedTests params
selectedTests = reverse $ getMainTests tests
2018-09-01 14:01:17 +02:00
getChartJss :: Challenge -> [Entity Test] -> [Text] -> JavascriptUrl (Route App)
getChartJss challenge tests params =
mconcat $ [(getChartJs challenge test param) | test <- tests, param <- params]
2018-07-28 17:04:27 +02:00
2018-07-28 17:30:00 +02:00
getChartJs :: Challenge
-> Entity Test
2018-07-28 17:30:00 +02:00
-> Text
-> JavascriptUrl (Route App)
getChartJs challenge (Entity testId test) param = [julius|
$.getJSON("@{ChallengeParamGraphDataR (challengeName challenge) testId param}", function(data) {
2018-07-28 17:04:27 +02:00
c3.generate({
bindto: '#chart-' + #{toJSON param} + '-' + #{toJSON testId},
2018-07-28 17:04:27 +02:00
data: data,
axis: {
x: {
label: #{toJSON param},
},
y: {
label: #{toJSON testFormatted},
}
}
}) });
|]
where testFormatted = formatTest test
2015-09-29 22:31:56 +02:00
2018-07-05 22:17:25 +02:00
challengeLayout :: Bool -> Challenge -> WidgetFor App () -> HandlerFor App Html
2015-09-06 14:24:49 +02:00
challengeLayout withHeader challenge widget = do
2017-09-27 19:38:42 +02:00
tagsAvailableAsJSON <- runDB $ getAvailableTagsAsJSON
2019-09-24 22:52:25 +02:00
version <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
2019-12-13 22:29:41 +01:00
let versionFormatted = formatVersion ((versionMajor $ entityVal version),
(versionMinor $ entityVal version),
(versionPatch $ entityVal version))
2016-05-03 12:29:56 +02:00
maybeUser <- maybeAuth
2015-09-06 14:24:49 +02:00
bc <- widgetToPageContent widget
2015-09-04 23:23:32 +02:00
defaultLayout $ do
2015-09-06 14:24:49 +02:00
setTitle "Challenge"
$(widgetFile "challenge")