forked from filipg/gonito
Handle Slack hooks
This commit is contained in:
parent
484b98e699
commit
3447b29a82
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE RecordWildCards #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
||||
module Handler.Shared where
|
||||
|
||||
@ -10,6 +11,7 @@ import Handler.Runner
|
||||
import System.Exit
|
||||
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as DTE
|
||||
|
||||
import Database.Persist.Sql (fromSqlKey)
|
||||
|
||||
@ -37,11 +39,12 @@ import System.IO.Unsafe (unsafePerformIO)
|
||||
|
||||
import Text.Regex.TDFA
|
||||
|
||||
import Data.Aeson.Types
|
||||
import GEval.Core
|
||||
|
||||
import qualified Data.Vector as DV
|
||||
|
||||
import Network.HTTP.Req as R
|
||||
|
||||
arena :: Handler FilePath
|
||||
arena = do
|
||||
app <- getYesod
|
||||
@ -399,3 +402,16 @@ getIsHigherTheBetterArray = Array
|
||||
compareFun :: MetricOrdering -> Double -> Double -> Ordering
|
||||
compareFun TheLowerTheBetter = flip compare
|
||||
compareFun TheHigherTheBetter = compare
|
||||
|
||||
runSlackHook :: Text -> Text -> IO ()
|
||||
runSlackHook hook message = do
|
||||
let (Just (hookUrl, _)) = parseUrlHttps $ DTE.encodeUtf8 hook
|
||||
|
||||
R.runReq def $ do
|
||||
let payload = object [ "text" .= message ]
|
||||
(_ :: JsonResponse Value) <- R.req R.POST
|
||||
hookUrl
|
||||
(R.ReqBodyJson payload)
|
||||
R.jsonResponse
|
||||
mempty
|
||||
return ()
|
||||
|
@ -241,6 +241,8 @@ doCreateSubmission userId challengeId mDescription mTags repoSpec chan = do
|
||||
case maybeRepoKey of
|
||||
Just repoId -> do
|
||||
|
||||
challenge <- runDB $ get404 challengeId
|
||||
|
||||
activeTests <- runDB $ selectList [TestChallenge ==. challengeId, TestActive ==. True] []
|
||||
let (Entity mainTestId mainTest) = getMainTest activeTests
|
||||
|
||||
@ -253,7 +255,7 @@ doCreateSubmission userId challengeId mDescription mTags repoSpec chan = do
|
||||
E.&&. submission ^. SubmissionIsHidden E.!=. E.val (Just True)
|
||||
E.&&. variant ^. VariantSubmission E.==. submission ^. SubmissionId
|
||||
E.&&. evaluation ^. EvaluationChecksum E.==. out ^. OutChecksum
|
||||
E.&&. evaluation ^. EvaluationScore E.!=. E.val Nothing
|
||||
E.&&. (E.not_ (E.isNothing (evaluation ^. EvaluationScore)))
|
||||
E.&&. out ^. OutVariant E.==. variant ^. VariantId
|
||||
E.&&. evaluation ^. EvaluationTest E.==. E.val mainTestId)
|
||||
E.orderBy [orderDirection (evaluation ^. EvaluationScore)]
|
||||
@ -304,7 +306,26 @@ doCreateSubmission userId challengeId mDescription mTags repoSpec chan = do
|
||||
case bestScoreSoFar of
|
||||
Just b -> case newScores'' of
|
||||
(s:_) -> if compOp s b
|
||||
then msg chan "New record!"
|
||||
then
|
||||
do
|
||||
app <- getYesod
|
||||
let submissionLink = (appRoot $ appSettings app) ++ "/q/" ++ (fromSHA1ToText (repoCurrentCommit repo))
|
||||
let message = ("Whoa! New best result for '"
|
||||
++ (challengeName challenge)
|
||||
++ "' challenge, "
|
||||
++ (T.pack $ show $ testMetric mainTest)
|
||||
++ " ("
|
||||
++ (if s > b
|
||||
then "+"
|
||||
else "")
|
||||
++ (T.pack $ show $ s-b)
|
||||
++ ")"
|
||||
++ " See <" ++ submissionLink ++ "|Submission>")
|
||||
msg chan message
|
||||
case appNewBestResultSlackHook $ appSettings app of
|
||||
Just hook -> liftIO $ runSlackHook hook message
|
||||
|
||||
Nothing -> return ()
|
||||
else return ()
|
||||
[] -> return ()
|
||||
Nothing -> return ()
|
||||
|
@ -88,6 +88,7 @@ data AppSettings = AppSettings
|
||||
, appTagPermissions :: TagPermissions
|
||||
, appAutoOpening :: Bool
|
||||
, appLeaderboardStyle :: LeaderboardStyle
|
||||
, appNewBestResultSlackHook :: Maybe Text
|
||||
}
|
||||
|
||||
instance FromJSON AppSettings where
|
||||
@ -127,6 +128,8 @@ instance FromJSON AppSettings where
|
||||
appAutoOpening <- o .:? "auto-opening" .!= False
|
||||
appLeaderboardStyle <- toLeaderboardStyle <$> o .: "leaderboard-style"
|
||||
|
||||
appNewBestResultSlackHook <- o .:? "new-best-result-slack-hook"
|
||||
|
||||
return AppSettings {..}
|
||||
|
||||
-- | Settings for 'widgetFile', such as which template languages to support and
|
||||
|
@ -13,6 +13,7 @@ repo-scheme: "_env:REPO_SCHEME:selfhosted"
|
||||
tag-permissions: "_env:TAG_PERMISSIONS:only-admin-can-add-new-tags"
|
||||
auto-opening: "_env:AUTO_OPENING:false"
|
||||
leaderboard-style: "_env:LEADERBOARD_STYLE:by-submitter"
|
||||
new-best-result-slack-hook: "_env:NEW_BEST_RESULT_SLACK_HOOK:"
|
||||
|
||||
# Optional values with the following production defaults.
|
||||
# In development, they default to the inverse.
|
||||
|
@ -146,6 +146,7 @@ library
|
||||
, wai
|
||||
, megaparsec
|
||||
, Glob
|
||||
, req
|
||||
|
||||
executable gonito
|
||||
if flag(library-only)
|
||||
|
Loading…
Reference in New Issue
Block a user