2015-12-12 18:53:20 +01:00
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
|
|
|
|
|
|
|
|
|
module Handler.Tables where
|
|
|
|
|
|
|
|
|
|
import Import
|
2016-02-16 21:26:57 +01:00
|
|
|
|
import Handler.Shared
|
2017-02-25 22:53:17 +01:00
|
|
|
|
import Handler.SubmissionView
|
2017-03-18 15:57:27 +01:00
|
|
|
|
import Handler.TagUtils
|
2015-12-12 18:53:20 +01:00
|
|
|
|
|
|
|
|
|
import qualified Yesod.Table as Table
|
|
|
|
|
import Yesod.Table (Table)
|
|
|
|
|
|
2018-11-12 10:11:58 +01:00
|
|
|
|
import qualified Database.Esqueleto as E
|
|
|
|
|
import Database.Esqueleto ((^.))
|
|
|
|
|
|
2015-12-12 18:53:20 +01:00
|
|
|
|
import qualified Data.Map as Map
|
|
|
|
|
|
2018-07-14 19:44:33 +02:00
|
|
|
|
import Data.Text (pack, unpack, unwords)
|
2016-02-16 19:00:26 +01:00
|
|
|
|
|
2016-02-16 21:10:10 +01:00
|
|
|
|
import PersistSHA1
|
|
|
|
|
|
2018-01-25 16:34:05 +01:00
|
|
|
|
import qualified Data.List as DL
|
|
|
|
|
|
2015-12-12 18:53:20 +01:00
|
|
|
|
import GEval.Core
|
|
|
|
|
|
2018-07-14 19:44:33 +02:00
|
|
|
|
import GEval.ParseParams (parseParamsFromFilePath, OutputFileParsed(..))
|
2016-02-17 09:34:34 +01:00
|
|
|
|
|
2015-12-12 18:53:20 +01:00
|
|
|
|
data LeaderboardEntry = LeaderboardEntry {
|
|
|
|
|
leaderboardUser :: User,
|
2016-02-16 21:10:10 +01:00
|
|
|
|
leaderboardUserId :: UserId,
|
2015-12-12 18:53:20 +01:00
|
|
|
|
leaderboardBestSubmission :: Submission,
|
2016-02-16 21:10:10 +01:00
|
|
|
|
leaderboardBestSubmissionId :: SubmissionId,
|
2018-07-24 14:08:47 +02:00
|
|
|
|
leaderboardBestVariant :: Variant,
|
|
|
|
|
leaderboardBestVariantId :: VariantId,
|
2018-09-08 19:21:06 +02:00
|
|
|
|
leaderboardEvaluationMap :: Map (Key Test) Evaluation,
|
2017-03-18 15:57:27 +01:00
|
|
|
|
leaderboardNumberOfSubmissions :: Int,
|
2018-07-24 14:08:47 +02:00
|
|
|
|
leaderboardTags :: [(Entity Tag, Entity SubmissionTag)],
|
|
|
|
|
leaderboardParams :: [Parameter]
|
2015-12-12 18:53:20 +01:00
|
|
|
|
}
|
|
|
|
|
|
2018-11-12 10:11:58 +01:00
|
|
|
|
data TableEntry = TableEntry {
|
|
|
|
|
tableEntrySubmission :: Entity Submission,
|
|
|
|
|
tableEntryVariant :: Entity Variant,
|
|
|
|
|
tableEntrySubmitter :: Entity User,
|
|
|
|
|
tableEntryMapping :: Map (Key Test) Evaluation,
|
|
|
|
|
tableEntryTagsInfo :: [(Entity Tag, Entity SubmissionTag)],
|
|
|
|
|
tableEntryParams :: [Entity Parameter],
|
|
|
|
|
tableEntryRank :: Int }
|
2018-07-28 17:04:27 +02:00
|
|
|
|
|
2018-09-21 17:55:00 +02:00
|
|
|
|
tableEntryStamp :: TableEntry -> UTCTime
|
2018-11-12 10:11:58 +01:00
|
|
|
|
tableEntryStamp = submissionStamp . entityVal . tableEntrySubmission
|
2018-09-21 17:55:00 +02:00
|
|
|
|
|
2018-07-14 17:02:30 +02:00
|
|
|
|
submissionsTable :: Maybe UserId -> Text -> RepoScheme -> Repo -> [Entity Test] -> Table App TableEntry
|
2018-06-06 13:43:17 +02:00
|
|
|
|
submissionsTable mauthId challengeName repoScheme challengeRepo tests = mempty
|
2018-11-12 10:11:58 +01:00
|
|
|
|
++ Table.int "#" tableEntryRank
|
|
|
|
|
++ Table.text "submitter" (formatSubmitter . entityVal . tableEntrySubmitter)
|
|
|
|
|
++ timestampCell "when" tableEntryStamp
|
2018-11-03 21:37:44 +01:00
|
|
|
|
++ descriptionCell mauthId
|
2016-02-17 09:43:25 +01:00
|
|
|
|
++ mconcat (map (\(Entity k t) -> resultCell t (extractScore k)) tests)
|
2018-11-12 10:11:58 +01:00
|
|
|
|
++ statusCell challengeName repoScheme challengeRepo (\tableEntry -> (entityKey $ tableEntrySubmission tableEntry,
|
|
|
|
|
entityVal $ tableEntrySubmission tableEntry,
|
|
|
|
|
entityKey $ tableEntryVariant tableEntry,
|
|
|
|
|
entityVal $ tableEntryVariant tableEntry,
|
|
|
|
|
entityKey $ tableEntrySubmitter tableEntry,
|
|
|
|
|
mauthId))
|
2017-02-25 22:53:17 +01:00
|
|
|
|
|
2018-11-12 14:12:51 +01:00
|
|
|
|
paramTable :: [Text] -> [Entity Test] -> Table App TableEntry
|
|
|
|
|
paramTable paramNames tests = mempty
|
|
|
|
|
++ Table.int "#" tableEntryRank
|
|
|
|
|
++ mconcat (map paramExtractor paramNames)
|
|
|
|
|
++ mconcat (map (\(Entity k t) -> resultCell t (extractScore k)) tests)
|
|
|
|
|
|
|
|
|
|
paramExtractor :: Text -> Table App TableEntry
|
|
|
|
|
paramExtractor paramName = Table.text paramName (\entry ->
|
|
|
|
|
fromMaybe ""
|
|
|
|
|
$ listToMaybe
|
|
|
|
|
$ map parameterValue
|
|
|
|
|
$ filter (\p -> parameterName p == paramName)
|
|
|
|
|
$ map entityVal
|
|
|
|
|
$ tableEntryParams entry)
|
|
|
|
|
|
2018-11-03 21:37:44 +01:00
|
|
|
|
descriptionCell :: Maybe UserId -> Table App TableEntry
|
|
|
|
|
descriptionCell mauthId = Table.widget "description" (
|
2018-11-12 10:11:58 +01:00
|
|
|
|
\(TableEntry (Entity _ s) (Entity _ v) (Entity u _) _ tagEnts paramEnts _) -> fragmentWithSubmissionTags
|
|
|
|
|
(descriptionToBeShown s v (map entityVal paramEnts))
|
|
|
|
|
(getInfoLink s u mauthId)
|
|
|
|
|
tagEnts)
|
2018-07-14 19:44:33 +02:00
|
|
|
|
|
|
|
|
|
|
|
|
|
|
descriptionToBeShown :: Submission -> Variant -> [Parameter] -> Text
|
|
|
|
|
descriptionToBeShown s v params = (submissionDescription s) ++ (Data.Text.pack vdescription) ++ " " ++ paramsShown
|
|
|
|
|
where (OutputFileParsed r _) = parseParamsFromFilePath (Data.Text.unpack $ variantName v)
|
|
|
|
|
vdescription = if r == "out"
|
|
|
|
|
then
|
|
|
|
|
""
|
|
|
|
|
else
|
|
|
|
|
" " ++ r
|
2018-07-28 17:04:27 +02:00
|
|
|
|
paramsShown = Data.Text.unwords $ map formatParameter params
|
2017-02-25 22:53:17 +01:00
|
|
|
|
|
2018-07-14 17:02:30 +02:00
|
|
|
|
extractScore :: Key Test -> TableEntry -> Maybe Evaluation
|
2018-11-12 10:11:58 +01:00
|
|
|
|
extractScore k tableEntry = lookup k $ tableEntryMapping tableEntry
|
2016-02-17 09:34:34 +01:00
|
|
|
|
|
2018-09-08 19:21:06 +02:00
|
|
|
|
leaderboardTable :: Maybe UserId -> Text -> RepoScheme -> Repo -> [Entity Test] -> Table App (Int, LeaderboardEntry)
|
|
|
|
|
leaderboardTable mauthId challengeName repoScheme challengeRepo tests = mempty
|
2016-02-17 09:43:25 +01:00
|
|
|
|
++ Table.int "#" fst
|
|
|
|
|
++ Table.text "submitter" (formatSubmitter . leaderboardUser . snd)
|
|
|
|
|
++ timestampCell "when" (submissionStamp . leaderboardBestSubmission . snd)
|
2018-11-03 21:37:44 +01:00
|
|
|
|
++ leaderboardDescriptionCell mauthId
|
2018-09-08 19:21:06 +02:00
|
|
|
|
++ mconcat (map (\(Entity k t) -> resultCell t (extractScoreFromLeaderboardEntry k . snd)) tests)
|
2016-02-17 09:43:25 +01:00
|
|
|
|
++ Table.int "×" (leaderboardNumberOfSubmissions . snd)
|
2018-06-06 13:43:17 +02:00
|
|
|
|
++ statusCell challengeName repoScheme challengeRepo (\(_, e) -> (leaderboardBestSubmissionId e,
|
2016-02-16 21:10:10 +01:00
|
|
|
|
leaderboardBestSubmission e,
|
2018-07-30 07:59:38 +02:00
|
|
|
|
leaderboardBestVariantId e,
|
|
|
|
|
leaderboardBestVariant e,
|
2016-02-16 21:10:10 +01:00
|
|
|
|
leaderboardUserId e,
|
|
|
|
|
mauthId))
|
2015-12-12 18:53:20 +01:00
|
|
|
|
|
2018-09-08 19:21:06 +02:00
|
|
|
|
extractScoreFromLeaderboardEntry :: Key Test -> LeaderboardEntry -> Maybe Evaluation
|
|
|
|
|
extractScoreFromLeaderboardEntry k entry = lookup k (leaderboardEvaluationMap entry)
|
|
|
|
|
|
2018-11-03 21:37:44 +01:00
|
|
|
|
leaderboardDescriptionCell :: Maybe UserId -> Table App (a, LeaderboardEntry)
|
|
|
|
|
leaderboardDescriptionCell mauthId = Table.widget "description" (
|
2018-07-24 14:08:47 +02:00
|
|
|
|
\(_,entry) -> fragmentWithSubmissionTags (descriptionToBeShown (leaderboardBestSubmission entry)
|
|
|
|
|
(leaderboardBestVariant entry)
|
|
|
|
|
(leaderboardParams entry))
|
2018-11-03 21:37:44 +01:00
|
|
|
|
(getInfoLink (leaderboardBestSubmission entry)
|
|
|
|
|
(leaderboardUserId entry)
|
|
|
|
|
mauthId)
|
2018-07-24 14:08:47 +02:00
|
|
|
|
(leaderboardTags entry)
|
|
|
|
|
)
|
2017-03-18 15:57:27 +01:00
|
|
|
|
|
|
|
|
|
|
2016-02-11 21:54:22 +01:00
|
|
|
|
|
2016-02-16 19:00:26 +01:00
|
|
|
|
hoverTextCell :: Text -> (a -> Text) -> (a -> Text) -> Table site a
|
|
|
|
|
hoverTextCell h mainTextFun hoverTextFun = Table.widget h (
|
|
|
|
|
\v -> [whamlet|<span title="#{hoverTextFun v}">#{mainTextFun v}|])
|
|
|
|
|
|
|
|
|
|
timestampCell :: Text -> (a -> UTCTime) -> Table site a
|
|
|
|
|
timestampCell h timestampFun = hoverTextCell h (Data.Text.pack . shorterFormat . timestampFun) (Data.Text.pack . show . timestampFun)
|
|
|
|
|
where shorterFormat = formatTime defaultTimeLocale "%Y-%m-%d %H:%M"
|
|
|
|
|
|
2018-07-30 07:59:38 +02:00
|
|
|
|
statusCell :: Text -> RepoScheme -> Repo -> (a -> (SubmissionId, Submission, VariantId, Variant, UserId, Maybe UserId)) -> Table App a
|
2018-06-06 13:43:17 +02:00
|
|
|
|
statusCell challengeName repoScheme challengeRepo fun = Table.widget "" (statusCellWidget challengeName repoScheme challengeRepo . fun)
|
2016-02-16 21:10:10 +01:00
|
|
|
|
|
2016-02-17 09:34:34 +01:00
|
|
|
|
resultCell :: Test -> (a -> Maybe Evaluation) -> Table App a
|
2018-09-01 10:46:39 +02:00
|
|
|
|
resultCell test fun = hoverTextCell (formatTestForHtml test) (formatTruncatedScore (testPrecision test) . fun) (formatFullScore . fun)
|
2016-02-17 09:34:34 +01:00
|
|
|
|
|
2018-11-03 21:37:44 +01:00
|
|
|
|
statusCellWidget :: Text -> RepoScheme -> Repo -> (SubmissionId, Submission, VariantId, Variant, UserId, Maybe UserId) -> WidgetFor App ()
|
2018-07-30 07:59:38 +02:00
|
|
|
|
statusCellWidget challengeName repoScheme challengeRepo (submissionId, submission, variantId, _, userId, mauthId) = $(widgetFile "submission-status")
|
2016-02-16 21:10:10 +01:00
|
|
|
|
where commitHash = fromSHA1ToText $ submissionCommit submission
|
|
|
|
|
isPublic = submissionIsPublic submission
|
|
|
|
|
isOwner = (mauthId == Just userId)
|
2018-11-03 21:37:44 +01:00
|
|
|
|
isVisible = checkWhetherVisible submission userId mauthId
|
2016-02-16 21:26:57 +01:00
|
|
|
|
publicSubmissionBranch = getPublicSubmissionBranch submissionId
|
|
|
|
|
maybeBrowsableUrl = if isPublic
|
|
|
|
|
then
|
2018-06-06 13:43:17 +02:00
|
|
|
|
Just $ browsableGitRepoBranch repoScheme challengeRepo challengeName publicSubmissionBranch
|
2016-02-16 21:26:57 +01:00
|
|
|
|
else
|
|
|
|
|
Nothing
|
2016-02-16 21:10:10 +01:00
|
|
|
|
|
2018-11-03 21:37:44 +01:00
|
|
|
|
getInfoLink :: Submission -> UserId -> Maybe UserId -> Maybe (Route App)
|
|
|
|
|
getInfoLink submission userId mauthId = if checkWhetherVisible submission userId mauthId
|
|
|
|
|
then Just $ QueryResultsR commitHash
|
|
|
|
|
else Nothing
|
|
|
|
|
where commitHash = fromSHA1ToText $ submissionCommit submission
|
|
|
|
|
|
|
|
|
|
checkWhetherVisible :: Submission -> UserId -> Maybe UserId -> Bool
|
|
|
|
|
checkWhetherVisible submission userId mauthId = isPublic || isOwner
|
|
|
|
|
where isPublic = submissionIsPublic submission
|
|
|
|
|
isOwner = (mauthId == Just userId)
|
|
|
|
|
|
2018-07-24 14:08:47 +02:00
|
|
|
|
getAuxSubmissionEnts :: Key Test -> [TableEntry] -> [(Key User, (User, [(Entity Submission, Entity Variant, Evaluation)]))]
|
2018-06-27 13:09:11 +02:00
|
|
|
|
getAuxSubmissionEnts testId evaluationMaps = map processEvaluationMap evaluationMaps
|
2018-11-12 10:11:58 +01:00
|
|
|
|
where processEvaluationMap (TableEntry s v (Entity ui u) m _ _ _) = (ui, (u, case Map.lookup testId m of
|
2018-07-24 14:08:47 +02:00
|
|
|
|
Just e -> [(s, v, e)]
|
2016-02-12 23:21:26 +01:00
|
|
|
|
Nothing -> []))
|
|
|
|
|
|
|
|
|
|
|
2018-07-28 21:53:13 +02:00
|
|
|
|
getLeaderboardEntriesByCriterion :: (Ord a) => Key Challenge
|
|
|
|
|
-> ((Entity Submission) -> Bool)
|
2018-09-08 21:21:21 +02:00
|
|
|
|
-> (TableEntry -> [a])
|
2018-09-08 19:21:06 +02:00
|
|
|
|
-> Handler ([LeaderboardEntry], ([TableEntry], [Entity Test]))
|
2018-07-24 15:21:20 +02:00
|
|
|
|
getLeaderboardEntriesByCriterion challengeId condition selector = do
|
2018-11-12 14:12:51 +01:00
|
|
|
|
(evaluationMaps, tests) <- runDB $ getChallengeSubmissionInfos condition challengeId
|
2018-09-08 19:21:06 +02:00
|
|
|
|
let mainTests = getMainTests tests
|
2016-02-11 21:54:22 +01:00
|
|
|
|
let mainTestEnt = getMainTest tests
|
2015-12-12 18:53:20 +01:00
|
|
|
|
let (Entity mainTestId mainTest) = mainTestEnt
|
2018-09-08 21:21:21 +02:00
|
|
|
|
let auxItems = concat
|
|
|
|
|
$ map (\i -> map (\s -> (s, [i])) (selector i))
|
2018-11-12 10:11:58 +01:00
|
|
|
|
$ filter (\entry -> member mainTestId $ tableEntryMapping entry)
|
2018-09-08 19:21:06 +02:00
|
|
|
|
$ evaluationMaps
|
2018-07-24 15:02:37 +02:00
|
|
|
|
let auxItemsMap = Map.fromListWith (++) auxItems
|
2018-09-08 19:21:06 +02:00
|
|
|
|
let entryComparator a b = (compareResult mainTest) (evaluationScore $ leaderboardEvaluationMap a Map.! mainTestId)
|
|
|
|
|
(evaluationScore $ leaderboardEvaluationMap b Map.! mainTestId)
|
|
|
|
|
entries' <- mapM (toLeaderboardEntry challengeId mainTests)
|
2018-07-28 21:53:13 +02:00
|
|
|
|
$ filter (\ll -> not (null ll))
|
|
|
|
|
$ map snd
|
|
|
|
|
$ Map.toList auxItemsMap
|
2018-09-08 21:21:21 +02:00
|
|
|
|
let entries = DL.nubBy (\a b -> leaderboardBestVariantId a == leaderboardBestVariantId b)
|
|
|
|
|
$ sortBy (flip entryComparator) entries'
|
2018-09-08 19:21:06 +02:00
|
|
|
|
return (entries, (evaluationMaps, mainTests))
|
2017-03-18 15:57:27 +01:00
|
|
|
|
|
2018-09-08 19:21:06 +02:00
|
|
|
|
toLeaderboardEntry :: (BaseBackend (YesodPersistBackend site) ~ SqlBackend, PersistQueryRead (YesodPersistBackend site), YesodPersist site, Foldable t) => Key Challenge -> [Entity Test] -> t TableEntry -> HandlerFor site LeaderboardEntry
|
|
|
|
|
toLeaderboardEntry challengeId tests ss = do
|
2018-06-27 13:09:11 +02:00
|
|
|
|
let bestOne = DL.maximumBy submissionComparator ss
|
2018-11-12 10:11:58 +01:00
|
|
|
|
let (TableEntry bestSubmission bestVariant user evals _ _ _) = bestOne
|
2018-07-24 14:08:47 +02:00
|
|
|
|
let submissionId = entityKey bestSubmission
|
2017-03-18 15:57:27 +01:00
|
|
|
|
tagEnts <- runDB $ getTags submissionId
|
2018-07-24 14:08:47 +02:00
|
|
|
|
|
|
|
|
|
parameters <- runDB $ selectList [ParameterVariant ==. (entityKey bestVariant)] [Asc ParameterName]
|
|
|
|
|
|
2018-06-27 13:09:11 +02:00
|
|
|
|
-- get all user submissions, including hidden ones
|
2018-07-28 21:53:13 +02:00
|
|
|
|
allUserSubmissions <- runDB $ selectList [SubmissionChallenge ==. challengeId,
|
|
|
|
|
SubmissionSubmitter ==. entityKey user]
|
|
|
|
|
[Desc SubmissionStamp]
|
2017-03-18 15:57:27 +01:00
|
|
|
|
return $ LeaderboardEntry {
|
2018-07-24 15:02:37 +02:00
|
|
|
|
leaderboardUser = entityVal user,
|
|
|
|
|
leaderboardUserId = entityKey user,
|
2018-07-24 14:08:47 +02:00
|
|
|
|
leaderboardBestSubmission = entityVal bestSubmission,
|
|
|
|
|
leaderboardBestSubmissionId = entityKey bestSubmission,
|
|
|
|
|
leaderboardBestVariant = entityVal bestVariant,
|
|
|
|
|
leaderboardBestVariantId = entityKey bestVariant,
|
2018-09-08 19:21:06 +02:00
|
|
|
|
leaderboardEvaluationMap = evals,
|
2018-06-27 13:09:11 +02:00
|
|
|
|
leaderboardNumberOfSubmissions = length allUserSubmissions,
|
2018-07-24 14:08:47 +02:00
|
|
|
|
leaderboardTags = tagEnts,
|
|
|
|
|
leaderboardParams = map entityVal parameters
|
2017-02-25 22:53:17 +01:00
|
|
|
|
}
|
2018-09-08 19:21:06 +02:00
|
|
|
|
where (Entity mainTestId mainTest) = getMainTest tests
|
2018-11-12 10:11:58 +01:00
|
|
|
|
submissionComparator (TableEntry _ _ _ em1 _ _ _) (TableEntry _ _ _ em2 _ _ _) =
|
2018-09-08 19:21:06 +02:00
|
|
|
|
(compareResult mainTest) (evaluationScore (em1 Map.! mainTestId))
|
|
|
|
|
(evaluationScore (em2 Map.! mainTestId))
|
2017-02-25 22:53:17 +01:00
|
|
|
|
|
2018-09-08 21:21:21 +02:00
|
|
|
|
getLeaderboardEntries :: LeaderboardStyle -> Key Challenge -> Handler ([LeaderboardEntry], ([TableEntry], [Entity Test]))
|
|
|
|
|
getLeaderboardEntries BySubmitter challengeId =
|
2018-07-28 21:53:13 +02:00
|
|
|
|
getLeaderboardEntriesByCriterion challengeId
|
|
|
|
|
(const True)
|
2018-11-12 10:11:58 +01:00
|
|
|
|
(\entry -> [entityKey $ tableEntrySubmitter entry])
|
2018-09-08 21:21:21 +02:00
|
|
|
|
getLeaderboardEntries ByTag challengeId =
|
|
|
|
|
getLeaderboardEntriesByCriterion challengeId
|
|
|
|
|
(const True)
|
|
|
|
|
(noEmptyList . (map (entityKey . fst)) . tableEntryTagsInfo)
|
|
|
|
|
where noEmptyList [] = [Nothing]
|
|
|
|
|
noEmptyList l = map Just l
|
2017-02-25 22:53:17 +01:00
|
|
|
|
|
2015-12-12 18:53:20 +01:00
|
|
|
|
compareResult :: Test -> Maybe Double -> Maybe Double -> Ordering
|
2015-12-20 21:00:00 +01:00
|
|
|
|
compareResult test (Just x) (Just y) = (compareFun $ getMetricOrdering $ testMetric test) x y
|
2015-12-12 18:53:20 +01:00
|
|
|
|
compareResult _ (Just _) Nothing = GT
|
|
|
|
|
compareResult _ Nothing (Just _) = LT
|
|
|
|
|
compareResult _ Nothing Nothing = EQ
|
|
|
|
|
|
|
|
|
|
getChallengeSubmissionInfos condition challengeId = do
|
2018-11-12 14:12:51 +01:00
|
|
|
|
tests <- selectList [TestChallenge ==. challengeId, TestActive ==. True] []
|
2018-11-12 10:11:58 +01:00
|
|
|
|
let mainTest = getMainTest tests
|
|
|
|
|
|
2018-11-12 14:12:51 +01:00
|
|
|
|
allSubmissionsVariants <- E.select $ E.from $ \(submission, variant) -> do
|
2018-11-12 10:11:58 +01:00
|
|
|
|
E.where_ (submission ^. SubmissionChallenge E.==. E.val challengeId
|
|
|
|
|
E.&&. submission ^. SubmissionIsHidden E.!=. E.val (Just True)
|
|
|
|
|
E.&&. variant ^. VariantSubmission E.==. submission ^. SubmissionId)
|
|
|
|
|
return (submission, variant)
|
|
|
|
|
|
2018-11-12 14:12:51 +01:00
|
|
|
|
scores <- mapM (getScore (entityKey mainTest)) $ map (entityKey . snd) allSubmissionsVariants
|
2018-11-12 10:11:58 +01:00
|
|
|
|
|
|
|
|
|
let allSubmissionsVariantsWithRanks =
|
|
|
|
|
sortBy (\(r1, (s1, _)) (r2, (s2, _)) -> (submissionStamp (entityVal s2) `compare` submissionStamp (entityVal s1))
|
|
|
|
|
`thenCmp`
|
|
|
|
|
(r2 `compare` r1))
|
|
|
|
|
$ filter (\(_, (s, _)) -> condition s)
|
|
|
|
|
$ map (\(rank, (_, sv)) -> (rank, sv))
|
|
|
|
|
$ zip [1..]
|
|
|
|
|
$ sortBy (\(s1, _) (s2, _) -> compareResult (entityVal mainTest) s2 s1)
|
|
|
|
|
$ zip scores allSubmissionsVariants
|
|
|
|
|
|
|
|
|
|
evaluationMaps <- mapM getEvaluationMap allSubmissionsVariantsWithRanks
|
|
|
|
|
return (evaluationMaps, tests)
|
|
|
|
|
|
|
|
|
|
getScore testId variantId = do
|
|
|
|
|
evaluations <- E.select $ E.from $ \(out, evaluation) -> do
|
|
|
|
|
E.where_ (out ^. OutVariant E.==. E.val variantId
|
|
|
|
|
E.&&. out ^. OutTest E.==. E.val testId
|
|
|
|
|
E.&&. out ^. OutChecksum E.==. evaluation ^. EvaluationChecksum
|
|
|
|
|
E.&&. evaluation ^. EvaluationTest E.==. E.val testId)
|
|
|
|
|
return evaluation
|
|
|
|
|
return $ case evaluations of
|
|
|
|
|
(e:_) -> evaluationScore $ entityVal e
|
|
|
|
|
[] -> Nothing
|
|
|
|
|
|
2018-11-12 14:12:51 +01:00
|
|
|
|
|
2018-11-12 10:11:58 +01:00
|
|
|
|
getEvaluationMap (rank, (s@(Entity submissionId submission), v@(Entity variantId _))) = do
|
2018-11-12 14:12:51 +01:00
|
|
|
|
outs <- selectList [OutVariant ==. variantId] []
|
|
|
|
|
user <- get404 $ submissionSubmitter submission
|
|
|
|
|
maybeEvaluations <- mapM (\(Entity _ o) -> getBy $ UniqueEvaluationTestChecksum (outTest o) (outChecksum o)) outs
|
2015-12-12 18:53:20 +01:00
|
|
|
|
let evaluations = catMaybes maybeEvaluations
|
|
|
|
|
let m = Map.fromList $ map (\(Entity _ e) -> (evaluationTest e, e)) evaluations
|
2018-11-12 14:12:51 +01:00
|
|
|
|
tagEnts <- getTags submissionId
|
2018-07-14 17:10:07 +02:00
|
|
|
|
|
2018-11-12 14:12:51 +01:00
|
|
|
|
parameters <- selectList [ParameterVariant ==. variantId] [Asc ParameterName]
|
2018-07-14 17:10:07 +02:00
|
|
|
|
|
2018-11-12 10:11:58 +01:00
|
|
|
|
return $ TableEntry s v (Entity (submissionSubmitter submission) user) m tagEnts parameters rank
|