clean up some warnings

This commit is contained in:
Filip Gralinski 2018-07-05 22:17:25 +02:00
parent eedf1cd6fa
commit b572bf45d0

View File

@ -1,10 +1,9 @@
module Handler.ShowChallenge where module Handler.ShowChallenge where
import Import import Import
import Yesod.Form.Bootstrap3 (BootstrapFormLayout (..), renderBootstrap3, import Yesod.Form.Bootstrap3 (BootstrapFormLayout (..), renderBootstrap3, bfs)
withSmallInput, bfs)
import Data.Monoid
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
import Text.Markdown import Text.Markdown
@ -22,7 +21,6 @@ import Handler.TagUtils
import GEval.Core import GEval.Core
import GEval.OptionsParser import GEval.OptionsParser
import qualified Data.Map as Map
import PersistSHA1 import PersistSHA1
@ -286,18 +284,23 @@ getOuts chan submissionId = do
mapM_ (checkOrInsertEvaluation repoDir chan) outs mapM_ (checkOrInsertEvaluation repoDir chan) outs
return outs return outs
outFileName :: FilePath
outFileName = "out.tsv" outFileName = "out.tsv"
getOutFilePath :: FilePath -> Test -> FilePath
getOutFilePath repoDir test = repoDir </> (T.unpack $ testName test) </> outFileName getOutFilePath repoDir test = repoDir </> (T.unpack $ testName test) </> outFileName
findOutFile :: FilePath -> Test -> IO (Maybe FilePath)
findOutFile repoDir test = do findOutFile repoDir test = do
let baseOut = getOutFilePath repoDir test let baseOut = getOutFilePath repoDir test
findFilePossiblyCompressed baseOut findFilePossiblyCompressed baseOut
doesOutExist :: FilePath -> Entity Test -> IO Bool
doesOutExist repoDir (Entity _ test) = do doesOutExist repoDir (Entity _ test) = do
result <- findOutFile repoDir test result <- findOutFile repoDir test
return $ isJust result return $ isJust result
outForTest :: MonadIO m => FilePath -> Key Submission -> Key Variant -> Entity Test -> m Out
outForTest repoDir submissionId variantId (Entity testId test) = do outForTest repoDir submissionId variantId (Entity testId test) = do
(Just outF) <- liftIO $ findOutFile repoDir test (Just outF) <- liftIO $ findOutFile repoDir test
checksum <- liftIO $ gatherSHA1ForCollectionOfFiles [outF] checksum <- liftIO $ gatherSHA1ForCollectionOfFiles [outF]
@ -451,6 +454,7 @@ getChallengeSubmissions condition name = do
challengeAllSubmissionsWidget muserId challenge scheme challengeRepo submissions tests = $(widgetFile "challenge-all-submissions") challengeAllSubmissionsWidget muserId challenge scheme challengeRepo submissions tests = $(widgetFile "challenge-all-submissions")
challengeLayout :: Bool -> Challenge -> WidgetFor App () -> HandlerFor App Html
challengeLayout withHeader challenge widget = do challengeLayout withHeader challenge widget = do
tagsAvailableAsJSON <- runDB $ getAvailableTagsAsJSON tagsAvailableAsJSON <- runDB $ getAvailableTagsAsJSON
maybeUser <- maybeAuth maybeUser <- maybeAuth