{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE QuasiQuotes #-} module Handler.Shared where import Import import qualified Data.IntMap as IntMap import Yesod.WebSockets import Handler.Runner import System.Exit import qualified Data.Text as T import Database.Persist.Sql (fromSqlKey) import Control.Concurrent.Lifted (threadDelay) import Control.Concurrent (forkIO) import qualified Crypto.Hash.SHA1 as CHS import qualified Data.List as DL import System.Random import System.Directory (doesFileExist, renameDirectory, doesDirectoryExist) import PersistSHA1 import Text.Printf import Yesod.Form.Bootstrap3 (bfs) import qualified Test.RandomStrings as RS import qualified Crypto.Nonce as Nonce import System.IO.Unsafe (unsafePerformIO) import Text.Regex.TDFA import Web.Announcements (formatLink, AnnouncementHook) import GEval.Core import GEval.Common import GEval.EvaluationScheme import GEval.Formatting (formatTheResultWithErrorBounds) import qualified Data.Vector as DV arena :: Handler FilePath arena = do app <- getYesod return $ (appVarDir $ appSettings app) > "arena" gitPath :: FilePath gitPath = "/usr/bin/git" browsableGitSite :: Text browsableGitSite = "https://gonito.net/gitlist/" serverAddress :: Text serverAddress = "gonito.net" gitServer :: Text gitServer = "ssh://gitolite@" ++ serverAddress ++ "/" gitReadOnlyServer :: Text gitReadOnlyServer = "git://" ++ serverAddress ++ "/" getPublicSubmissionBranch :: SubmissionId -> Text getPublicSubmissionBranch = T.pack . (printf "submission-%05d") . fromSqlKey getPublicSubmissionUrl :: RepoScheme -> Text -> Maybe Repo -> Text -> Text getPublicSubmissionUrl SelfHosted repoHost _ bareRepoName = repoHost ++ bareRepoName getPublicSubmissionUrl Branches _ (Just repo) _ = repoUrl repo getPublicSubmissionUrl NoInternalGitServer repoHost _ bareRepoName = repoHost ++ bareRepoName -- convert a git URL to a publicly available URL publicRepoUrl :: Text -> Text publicRepoUrl = T.replace "git@github.com:" "https://github.com/" . T.replace "git@gitlab.com:" "https://gitlab.com/" getReadOnlySubmissionUrl :: RepoScheme -> Text -> Repo -> Text -> Text getReadOnlySubmissionUrl SelfHosted _ _ bareRepoName = gitReadOnlyServer ++ bareRepoName getReadOnlySubmissionUrl Branches _ repo _ = repoUrl repo getReadOnlySubmissionUrl NoInternalGitServer repoHost _ bareRepoName = publicRepoUrl (repoHost ++ bareRepoName) browsableGitRepoBranch :: RepoScheme -> Text -> Repo -> Text -> Text -> Text browsableGitRepoBranch SelfHosted _ _ bareRepoName branch = (browsableGitRepo bareRepoName) ++ "/" ++ branch ++ "/" browsableGitRepoBranch Branches _ repo _ branch = sshToHttps (repoUrl repo) branch browsableGitRepoBranch NoInternalGitServer repoHost repo _ branch = sshToHttps (getPublicSubmissionUrl NoInternalGitServer repoHost (Just repo) branch) branch sshToHttps :: Text -> Text -> Text sshToHttps url branch = "https://" ++ (T.replace ".git" "" $ T.replace ":" "/" $ T.replace "ssh://" "" $ T.replace "git@" "" url) ++ "/tree/" ++ branch browsableGitRepo :: Text -> Text browsableGitRepo bareRepoName | ".git" `isSuffixOf` bareRepoName = browsableGitSite ++ bareRepoName | otherwise = browsableGitSite ++ bareRepoName ++ ".git" runViewProgress :: (Channel -> Handler ()) -> Handler TypedContent runViewProgress action = do app <- getYesod let viewingProgressStyle = appViewingProgressStyle $ appSettings app runViewProgress' (case viewingProgressStyle of WithWebSockets -> ViewProgressWithWebSocketsR WithPlainText -> ViewProgressR) action runOpenViewProgress :: (Channel -> Handler ()) -> Handler TypedContent runOpenViewProgress = runViewProgress' OpenViewProgressR runViewProgressWithWebSockets :: (Channel -> Handler ()) -> Handler TypedContent runViewProgressWithWebSockets = runViewProgress' ViewProgressWithWebSocketsR consoleApp :: Int -> WebSocketsT Handler () consoleApp jobId = do App {..} <- getYesod mchan <- liftIO $ atom $ do m <- readTVar jobs case IntMap.lookup jobId m of Nothing -> return Nothing Just chan -> fmap Just $ cloneTChan chan case mchan of Nothing -> do sendTextData ("CANNOT FIND THE OUTPUT (ALREADY SHOWN??)" :: Text) _ <- sendCloseE ("" :: Text) return () Just chan -> do let loop = do mtext <- liftIO $ atom $ readTChan chan case mtext of Nothing -> sendCloseE ("" :: Text) Just text -> do sendTextData text loop _ <- loop return () getViewProgressWithWebSocketsJsonR :: Int -> Handler Value getViewProgressWithWebSocketsJsonR jobId = do webSockets $ consoleApp jobId return $ String $ pack $ show jobId getViewProgressLogR :: Int -> Handler Html getViewProgressLogR jobId = do webSockets $ consoleApp jobId p <- widgetToPageContent logSelfContainedWidget hamletToRepHtml [hamlet|