gonito/Handler/Graph.hs

83 lines
3.1 KiB
Haskell
Raw Normal View History

2016-02-11 21:54:22 +01:00
module Handler.Graph where
import Import
import Handler.Tables
2018-01-25 16:34:05 +01:00
import Handler.Shared
2016-02-11 21:54:22 +01:00
import Data.Maybe
import Data.List ((!!))
2016-02-12 23:21:26 +01:00
import Database.Persist.Sql
2016-02-11 21:54:22 +01:00
getChallengeGraphDataR :: Text -> Handler Value
getChallengeGraphDataR challengeName = submissionsToJSON (\_ -> True) challengeName
submissionsToJSON :: ((Entity Submission) -> Bool) -> Text -> Handler Value
submissionsToJSON condition challengeName = do
challengeEnt@(Entity challengeId challenge) <- runDB $ getBy404 $ UniqueName challengeName
(evaluationMaps, tests) <- getChallengeSubmissionInfos condition challengeId
let mainTestEnt = getMainTest tests
let (Entity mainTestId mainTest) = mainTestEnt
2016-02-12 23:21:26 +01:00
let auxSubmissions = getAuxSubmissionEnts mainTestId evaluationMaps
2016-02-11 21:54:22 +01:00
let naturalRange = getNaturalRange auxSubmissions
2016-02-12 23:21:26 +01:00
let submissionIds = map (\(Entity k _, _) -> k) $ concat $ map (\(_, (_, p)) -> p) auxSubmissions
forks <- runDB $ selectList [ForkSource <-. submissionIds, ForkTarget <-. submissionIds] []
return $ object [ "nodes" .= (Data.Maybe.catMaybes $ map (auxSubmissionToNode naturalRange) $ zip [0..] auxSubmissions),
"edges" .= map forkToEdge forks ]
2016-02-11 21:54:22 +01:00
getNaturalRange auxSubmissions = (2.0 * (interQuantile $ Data.Maybe.catMaybes $ map getScore auxSubmissions))
getScore (_, (_, [])) = Nothing
getScore (_, (_, [(_, evaluation)])) = evaluationScore evaluation
2016-02-12 23:21:26 +01:00
auxSubmissionToNode :: Double -> (Int, (Key User, (User, [(Entity Submission, Evaluation)]))) -> Maybe Value
2016-02-11 21:54:22 +01:00
auxSubmissionToNode _ (_, (_, (_, []))) = Nothing
2016-02-12 23:21:26 +01:00
auxSubmissionToNode naturalRange (n, (_, (_, [(Entity submissionId submission, evaluation)]))) = case evaluationScore evaluation of
2016-02-11 21:54:22 +01:00
Just score -> Just $ object [
2016-02-12 23:21:26 +01:00
"id" .= nodeId submissionId,
2016-02-11 21:54:22 +01:00
"x" .= (stampToX $ submissionStamp submission),
"y" .= (- ((score / naturalRange) * 100.0)),
2016-02-12 23:21:26 +01:00
"size" .= (2 :: Int),
2016-02-11 21:54:22 +01:00
"label" .= submissionDescription submission ]
Nothing -> Nothing
2016-02-12 23:21:26 +01:00
forkToEdge :: Entity Fork -> Value
forkToEdge (Entity forkId fork) = object [
"source" .= nodeId (forkSource fork),
"target" .= nodeId (forkTarget fork),
"id" .= edgeId forkId,
"type" .= ["arrow" :: String]
2016-02-11 21:54:22 +01:00
]
2016-02-12 23:21:26 +01:00
nodeId :: Key Submission -> String
nodeId = ("n" ++) . show . fromSqlKey
2016-02-11 21:54:22 +01:00
2016-02-12 23:21:26 +01:00
edgeId :: Key Fork -> String
edgeId = ("e" ++) . show . fromSqlKey
2016-02-11 21:54:22 +01:00
2016-02-12 23:21:26 +01:00
stampToX :: UTCTime -> Integer
stampToX = toModifiedJulianDay . utctDay
2016-02-11 21:54:22 +01:00
-- taken from Math.Statistics
interQuantile :: (Fractional b, Ord b) => [b] -> b
interQuantile [] = 10.0
interQuantile xs = (q' - q)
where q = quantile 0.25 xs
q' = quantile 0.75 xs
quantile :: (Fractional b, Ord b) => Double -> [b] -> b
quantile q = quantileAsc q . sort
quantileAsc :: (Fractional b, Ord b) => Double -> [b] -> b
quantileAsc _ [] = error "x"
quantileAsc q xs
| q < 0 || q > 1 = error "quantile out of range"
| otherwise = xs !! (quantIndex (length xs) q)
where quantIndex :: Int -> Double -> Int
quantIndex len q = case round $ q * (fromIntegral len - 1) of
idx | idx < 0 -> error "Quantile index too small"
| idx >= len -> error "Quantile index too large"
| otherwise -> idx