gonito/Handler/Shared.hs

342 lines
12 KiB
Haskell
Raw Normal View History

2015-08-29 18:24:01 +02:00
{-# LANGUAGE RecordWildCards #-}
module Handler.Shared where
import Import
import qualified Data.IntMap as IntMap
2018-06-05 08:22:51 +02:00
import Handler.Runner
import System.Exit
2015-08-29 22:19:44 +02:00
import qualified Data.Text as T
import Database.Persist.Sql (fromSqlKey)
2015-08-29 22:19:44 +02:00
import Control.Concurrent.Lifted (threadDelay)
2018-05-20 16:58:48 +02:00
import Control.Concurrent (forkIO)
2015-08-30 12:33:47 +02:00
2015-09-29 14:15:49 +02:00
import qualified Crypto.Hash.SHA1 as CHS
2018-01-25 16:34:05 +01:00
import qualified Data.List as DL
2015-09-04 06:47:49 +02:00
import System.Random
2018-06-09 15:35:31 +02:00
import System.Directory (doesFileExist, renameDirectory)
2015-09-04 10:51:53 +02:00
2015-09-04 06:47:49 +02:00
import PersistSHA1
2015-08-30 12:33:47 +02:00
import Text.Printf
import Yesod.Form.Bootstrap3 (bfs)
import qualified Test.RandomStrings as RS
2017-09-28 11:29:48 +02:00
import qualified Crypto.Nonce as Nonce
import System.IO.Unsafe (unsafePerformIO)
2016-01-08 21:57:29 +01:00
arena :: Handler FilePath
arena = do
app <- getYesod
return $ (appVarDir $ appSettings app) </> "arena"
2015-09-04 06:47:49 +02:00
gitPath :: FilePath
gitPath = "/usr/bin/git"
browsableGitSite :: Text
2017-09-23 10:33:39 +02:00
browsableGitSite = "https://gonito.net/gitlist/"
serverAddress :: Text
serverAddress = "gonito.net"
2016-02-15 11:43:47 +01:00
gitServer :: Text
gitServer = "ssh://gitolite@" ++ serverAddress ++ "/"
gitReadOnlyServer :: Text
gitReadOnlyServer = "git://" ++ serverAddress ++ "/"
getPublicSubmissionBranch :: SubmissionId -> Text
getPublicSubmissionBranch = T.pack . (printf "submission-%05d") . fromSqlKey
2018-06-06 13:08:38 +02:00
getPublicSubmissionUrl :: RepoScheme -> Maybe Repo -> Text -> Text
getPublicSubmissionUrl SelfHosted _ bareRepoName = gitServer ++ bareRepoName
getPublicSubmissionUrl Branches (Just repo) _ = repoUrl repo
getReadOnlySubmissionUrl :: RepoScheme -> Repo -> Text -> Text
getReadOnlySubmissionUrl SelfHosted _ bareRepoName = gitReadOnlyServer ++ bareRepoName
getReadOnlySubmissionUrl Branches repo _ = repoUrl repo
browsableGitRepoBranch :: RepoScheme -> Repo -> Text -> Text -> Text
browsableGitRepoBranch SelfHosted _ bareRepoName branch = (browsableGitRepo bareRepoName) ++ "/" ++ branch ++ "/"
browsableGitRepoBranch Branches repo _ branch = sshToHttps (repoUrl repo) branch
sshToHttps :: Text -> Text -> Text
2018-06-06 14:18:27 +02:00
sshToHttps url branch = "https://" ++ (T.replace ".git" "" $ T.replace ":" "/" $ T.replace "ssh://" "" $ T.replace "git@" "" url) ++ "/tree/" ++ branch
2016-02-15 11:43:47 +01:00
browsableGitRepo :: Text -> Text
browsableGitRepo bareRepoName
| ".git" `isSuffixOf` bareRepoName = browsableGitSite ++ bareRepoName
| otherwise = browsableGitSite ++ bareRepoName ++ ".git"
2017-09-28 11:29:48 +02:00
2015-08-30 12:33:47 +02:00
runViewProgress :: (Channel -> Handler ()) -> Handler TypedContent
2017-09-28 11:29:48 +02:00
runViewProgress = runViewProgress' ViewProgressR
runOpenViewProgress :: (Channel -> Handler ()) -> Handler TypedContent
runOpenViewProgress = runViewProgress' OpenViewProgressR
runViewProgress' :: (Int -> Route App) -> (Channel -> Handler ()) -> Handler TypedContent
runViewProgress' route action = do
2015-08-29 18:24:01 +02:00
App {..} <- getYesod
2015-09-04 06:47:49 +02:00
jobId <- randomInt
chan <- liftIO $ atom $ do
2015-08-29 18:24:01 +02:00
chan <- newBroadcastTChan
m <- readTVar jobs
writeTVar jobs $ IntMap.insert jobId chan m
2015-09-04 06:47:49 +02:00
return chan
2018-05-20 16:58:48 +02:00
runInnerHandler <- handlerToIO
_ <- liftIO $ forkIO $ runInnerHandler $ do
2015-08-30 12:33:47 +02:00
liftIO $ threadDelay 1000000
2015-08-29 18:24:01 +02:00
action chan
2015-08-30 12:33:47 +02:00
liftIO $ atom $ do
2015-08-29 18:24:01 +02:00
writeTChan chan $ Just "All done\n"
writeTChan chan Nothing
m <- readTVar jobs
writeTVar jobs $ IntMap.delete jobId m
2017-09-28 11:29:48 +02:00
redirect $ route jobId
2015-08-29 18:24:01 +02:00
2018-06-04 21:58:05 +02:00
data RepoCloningSpec = RepoCloningSpec {
2018-06-04 22:14:39 +02:00
cloningSpecRepo :: RepoSpec,
cloningSpecReferenceRepo :: RepoSpec
}
2018-06-01 22:52:49 +02:00
2018-06-04 22:14:39 +02:00
data RepoSpec = RepoSpec {
repoSpecUrl :: Text,
2018-06-05 07:46:42 +02:00
repoSpecBranch :: Text,
repoSpecGitAnnexRemote :: Maybe Text
2018-06-01 22:52:49 +02:00
}
2018-06-04 21:58:05 +02:00
cloneRepo :: RepoCloningSpec -> Channel -> Handler (Maybe (Key Repo))
2018-06-04 22:14:39 +02:00
cloneRepo repoCloningSpec chan = do
let url = repoSpecUrl $ cloningSpecRepo repoCloningSpec
let branch = repoSpecBranch $ cloningSpecRepo repoCloningSpec
2015-08-30 12:33:47 +02:00
maybeRepo <- runDB $ getBy $ UniqueUrlBranch url branch
2015-08-29 22:19:44 +02:00
case maybeRepo of
Just _ -> do
err chan "Repo already there"
return Nothing
2018-06-04 22:14:39 +02:00
Nothing -> cloneRepo' repoCloningSpec chan
2015-09-28 23:43:55 +02:00
updateRepo :: Key Repo -> Channel -> Handler Bool
updateRepo repoId chan = do
repo <- runDB $ get404 repoId
2016-01-08 21:57:29 +01:00
repoDir <- getRepoDir repoId
2016-02-11 22:25:07 +01:00
let branch = repoBranch repo
exitCode <- runWithChannel chan $ do
runProg (Just repoDir) gitPath ["fetch",
"origin",
T.unpack branch,
"--progress"]
runProg (Just repoDir) gitPath ["reset",
"--hard",
"FETCH_HEAD"]
getStuffUsingGitAnnex repoDir (repoGitAnnexRemote repo)
2015-09-28 23:43:55 +02:00
case exitCode of
ExitSuccess -> do
maybeHeadCommit <- getHeadCommit repoDir chan
case maybeHeadCommit of
Just headCommit -> do
runDB $ update repoId [RepoCurrentCommit =. headCommit]
return True
Nothing -> return False
_ -> return False
2015-09-28 23:43:55 +02:00
getHeadCommit :: FilePath -> Channel -> Handler (Maybe SHA1)
getHeadCommit repoDir chan = do
(exitCode, out) <- runProgram (Just repoDir) gitPath ["rev-parse", "HEAD"] chan
case exitCode of
ExitSuccess -> do
msg chan $ concat ["HEAD commit is ", commitId]
return $ Just commitRaw
where commitId = T.replace "\n" "" out
commitRaw = fromTextToSHA1 commitId
ExitFailure _ -> do
err chan "cannot determine HEAD commit"
return Nothing
getLastCommitMessage :: FilePath -> Channel -> Handler (Maybe Text)
getLastCommitMessage repoDir chan = do
(exitCode, out) <- runProgram (Just repoDir) gitPath ["log", "-1", "--pretty=%B"] chan
return $ case exitCode of
ExitSuccess -> Just out
ExitFailure _ -> Nothing
2018-06-04 21:58:05 +02:00
cloneRepo' :: RepoCloningSpec -> Channel -> Handler (Maybe (Key Repo))
2018-06-04 22:14:39 +02:00
cloneRepo' repoCloningSpec chan = do
let url = repoSpecUrl $ cloningSpecRepo repoCloningSpec
2015-08-29 22:19:44 +02:00
msg chan $ concat ["Preparing to clone repo ", url]
msg chan "Cloning..."
r <- randomInt
arenaDir <- arena
let tmpRepoDir = arenaDir </> ("t" ++ show r)
exitCode <- rawClone tmpRepoDir repoCloningSpec chan
case exitCode of
2015-09-04 06:47:49 +02:00
ExitSuccess -> do
2015-09-28 23:43:55 +02:00
maybeHeadCommit <- getHeadCommit tmpRepoDir chan
case maybeHeadCommit of
Just commitRaw -> do
2015-09-04 06:47:49 +02:00
userId <- requireAuthId
time <- liftIO getCurrentTime
repoId <- runDB $ insert $ Repo {
repoUrl=url,
2018-06-04 22:14:39 +02:00
repoBranch=repoSpecBranch $ cloningSpecRepo repoCloningSpec,
2018-06-05 07:46:42 +02:00
repoGitAnnexRemote=repoSpecGitAnnexRemote $ cloningSpecRepo repoCloningSpec,
2015-09-04 10:02:33 +02:00
repoCurrentCommit=commitRaw,
2015-09-04 06:47:49 +02:00
repoOwner=userId,
repoReady=True,
repoStamp=time }
2016-01-08 21:57:29 +01:00
repoDir <- getRepoDir repoId
2015-09-04 10:51:53 +02:00
liftIO $ renameDirectory tmpRepoDir repoDir
msg chan $ concat ["Repo is in ", (T.pack repoDir)]
2015-09-04 06:47:49 +02:00
return $ Just repoId
2015-09-28 23:43:55 +02:00
Nothing -> do
2015-09-04 06:47:49 +02:00
return Nothing
ExitFailure _ -> do
err chan "git failed"
return Nothing
2015-08-29 22:19:44 +02:00
2018-06-05 09:36:48 +02:00
rawClone :: FilePath -> RepoCloningSpec -> Channel -> Handler ExitCode
rawClone tmpRepoDir repoCloningSpec chan = runWithChannel chan $ do
2018-06-04 22:14:39 +02:00
let url = repoSpecUrl $ cloningSpecRepo repoCloningSpec
let branch = repoSpecBranch $ cloningSpecRepo repoCloningSpec
let referenceUrl = repoSpecUrl $ cloningSpecReferenceRepo repoCloningSpec
let referenceBranch = repoSpecBranch $ cloningSpecReferenceRepo repoCloningSpec
2018-06-05 09:36:48 +02:00
runProg Nothing gitPath ["clone",
"--progress",
"--branch",
T.unpack referenceBranch,
T.unpack referenceUrl,
tmpRepoDir]
2015-11-11 09:50:32 +01:00
if url /= referenceUrl || branch /= referenceBranch
then
do
2018-06-05 09:36:48 +02:00
runProg (Just tmpRepoDir) gitPath ["remote",
"set-url",
"origin",
T.unpack url]
runProg (Just tmpRepoDir) gitPath ["fetch",
"origin",
T.unpack branch]
runProg (Just tmpRepoDir) gitPath ["reset",
"--hard",
"FETCH_HEAD"]
2018-06-05 16:23:16 +02:00
getStuffUsingGitAnnex tmpRepoDir (repoSpecGitAnnexRemote $ cloningSpecRepo repoCloningSpec)
2015-11-11 09:50:32 +01:00
else
2018-06-05 09:36:48 +02:00
return ()
2015-09-28 23:43:55 +02:00
2018-06-05 16:23:16 +02:00
getStuffUsingGitAnnex :: FilePath -> Maybe Text -> Runner ()
getStuffUsingGitAnnex _ Nothing = return ()
getStuffUsingGitAnnex tmpRepoDir (Just gitAnnexRemote) = do
let randomRemoteNameLen = 10
remoteName <- liftIO $ RS.randomString (RS.onlyAlpha RS.randomASCII) randomRemoteNameLen
2018-06-05 16:23:16 +02:00
runGitAnnex tmpRepoDir ["init"]
2018-06-05 16:57:44 +02:00
runGitAnnex tmpRepoDir (["initremote", remoteName] ++ (words $ T.unpack gitAnnexRemote))
2018-06-05 16:23:16 +02:00
runGitAnnex tmpRepoDir ["get", "--from", remoteName]
runGitAnnex :: FilePath -> [String] -> Runner ()
runGitAnnex tmpRepoDir args = runProg (Just tmpRepoDir) gitPath ("annex":args)
2016-01-08 21:57:29 +01:00
getRepoDir :: Key Repo -> Handler FilePath
getRepoDir repoId = do
arenaDir <- arena
return $ arenaDir </> ("r" ++ repoIdAsString)
where repoIdAsString = show $ fromSqlKey repoId
2015-09-04 10:51:53 +02:00
2017-09-28 11:29:48 +02:00
getOpenViewProgressR :: Int -> Handler TypedContent
getOpenViewProgressR = getViewProgressR
2015-08-29 18:24:01 +02:00
getViewProgressR :: Int -> Handler TypedContent
getViewProgressR jobId = do
App {..} <- getYesod
mchan <- liftIO $ atom $ do
m <- readTVar jobs
case IntMap.lookup jobId m of
Nothing -> return Nothing
Just chan -> fmap Just $ dupTChan chan
case mchan of
Nothing -> notFound
Just chan -> respondSource typePlain $ do
let loop = do
mtext <- liftIO $ atom $ readTChan chan
case mtext of
Nothing -> return ()
Just text -> do
sendChunkText text
sendFlush
loop
loop
2015-08-30 12:33:47 +02:00
2015-09-04 06:47:49 +02:00
randomInt :: Handler Int
randomInt = liftIO $ randomIO
2015-09-29 14:15:49 +02:00
gatherSHA1ForCollectionOfFiles :: [FilePath] -> IO ByteString
gatherSHA1ForCollectionOfFiles files = do
contentss <- mapM readFile $ sort files
return $ CHS.finalize $ foldl' CHS.update CHS.init contentss
2016-05-03 08:46:10 +02:00
formatSubmitter :: User -> Text
formatSubmitter user = if userIsAnonymous user
then
"[anonymised]"
else
case userName user of
Just name -> name
Nothing -> "[name not given]"
fieldWithTooltip :: forall master msg msg1. (RenderMessage master msg, RenderMessage master msg1) => msg -> msg1 -> FieldSettings master
fieldWithTooltip name tooltip = (bfs name) { fsTooltip = Just $ SomeMessage tooltip }
2017-09-28 11:29:48 +02:00
nonceGen :: Nonce.Generator
nonceGen = unsafePerformIO Nonce.new
{-# NOINLINE nonceGen #-}
-- | Randomly create a new verification key.
newToken :: MonadIO m => m Text
newToken = Nonce.nonce128urlT nonceGen
2017-09-28 16:51:10 +02:00
enableTriggerToken :: (BaseBackend (YesodPersistBackend site) ~ SqlBackend, YesodPersist site, PersistStoreWrite (YesodPersistBackend site)) => Key User -> Maybe a -> HandlerFor site ()
2017-09-28 16:51:10 +02:00
enableTriggerToken _ (Just _) = return ()
enableTriggerToken userId Nothing = do
token <- newToken
runDB $ update userId [UserTriggerToken =. Just token]
2018-01-25 16:34:05 +01:00
thenCmp :: Ordering -> Ordering -> Ordering
thenCmp EQ o2 = o2
thenCmp o1 _ = o1
2018-01-25 16:34:05 +01:00
getMainTest :: [Entity Test] -> Entity Test
getMainTest tests = DL.maximumBy (\(Entity _ a) (Entity _ b) -> ( ((testName a) `compare` (testName b))
`thenCmp`
((fromMaybe 9999 $ testPriority b) `compare` (fromMaybe 9999 $ testPriority a)) ) ) tests
2018-01-25 16:34:05 +01:00
formatFullScore :: Maybe Evaluation -> Text
formatFullScore (Just evaluation) = fromMaybe "???" (T.pack <$> show <$> evaluationScore evaluation)
formatFullScore Nothing = "N/A"
formatTruncatedScore :: Maybe Int -> Maybe Evaluation -> Text
formatTruncatedScore Nothing e = formatFullScore e
formatTruncatedScore _ Nothing = formatFullScore Nothing
formatTruncatedScore (Just precision) (Just evaluation) = case evaluationScore evaluation of
Just score -> T.pack $ printf "%0.*f" precision score
Nothing -> formatFullScore Nothing
2018-06-09 15:35:31 +02:00
findFilePossiblyCompressed :: FilePath -> IO (Maybe FilePath)
findFilePossiblyCompressed baseFilePath = do
let possibleFiles = [baseFilePath] ++ (map (baseFilePath <.>) ["gz", "bz2", "xz"])
foundFiles <- filterM doesFileExist possibleFiles
return $ case foundFiles of
[] -> Nothing
(h:_) -> Just h