forked from filipg/gonito
merge
This commit is contained in:
commit
c0190a2f43
3
CHANGELOG.md
Normal file
3
CHANGELOG.md
Normal file
@ -0,0 +1,3 @@
|
|||||||
|
## 1.0.0
|
||||||
|
|
||||||
|
Start CHANGELOG
|
@ -1,3 +1,4 @@
|
|||||||
|
|
||||||
{-# LANGUAGE InstanceSigs #-}
|
{-# LANGUAGE InstanceSigs #-}
|
||||||
|
|
||||||
module Foundation where
|
module Foundation where
|
||||||
@ -153,6 +154,7 @@ instance Yesod App where
|
|||||||
isAuthorized (QueryResultsR _) _ = regularAuthorization
|
isAuthorized (QueryResultsR _) _ = regularAuthorization
|
||||||
isAuthorized ListChallengesR _ = regularAuthorization
|
isAuthorized ListChallengesR _ = regularAuthorization
|
||||||
isAuthorized ListChallengesJsonR _ = regularAuthorization
|
isAuthorized ListChallengesJsonR _ = regularAuthorization
|
||||||
|
isAuthorized (ChallengeInfoJsonR _) _ = regularAuthorization
|
||||||
isAuthorized (LeaderboardJsonR _) _ = regularAuthorization
|
isAuthorized (LeaderboardJsonR _) _ = regularAuthorization
|
||||||
isAuthorized (ViewVariantR _ ) _ = regularAuthorization
|
isAuthorized (ViewVariantR _ ) _ = regularAuthorization
|
||||||
isAuthorized (ViewVariantTestR _ _) _ = regularAuthorization
|
isAuthorized (ViewVariantTestR _ _) _ = regularAuthorization
|
||||||
@ -174,6 +176,8 @@ instance Yesod App where
|
|||||||
isAuthorized AddUserR _ = return Authorized
|
isAuthorized AddUserR _ = return Authorized
|
||||||
isAuthorized UserInfoR _ = return Authorized
|
isAuthorized UserInfoR _ = return Authorized
|
||||||
isAuthorized (ChallengeSubmissionJsonR _) _ = return Authorized
|
isAuthorized (ChallengeSubmissionJsonR _) _ = return Authorized
|
||||||
|
isAuthorized (ChallengeReadmeInMarkdownR _) _ = regularAuthorization
|
||||||
|
isAuthorized (QueryJsonR _) _ = return Authorized
|
||||||
|
|
||||||
isAuthorized (ChallengeGraphDataR _) _ = regularAuthorization
|
isAuthorized (ChallengeGraphDataR _) _ = regularAuthorization
|
||||||
isAuthorized (ChallengeDiscussionR _) _ = regularAuthorization
|
isAuthorized (ChallengeDiscussionR _) _ = regularAuthorization
|
||||||
|
@ -8,10 +8,8 @@ import Import hiding (get, fromList, Proxy)
|
|||||||
import Data.HashMap.Strict.InsOrd (fromList)
|
import Data.HashMap.Strict.InsOrd (fromList)
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Data.Aeson
|
|
||||||
import Control.Lens hiding ((.=))
|
import Control.Lens hiding ((.=))
|
||||||
import Data.Swagger
|
import Data.Swagger
|
||||||
import Data.Swagger.Lens
|
|
||||||
import Data.Swagger.Declare
|
import Data.Swagger.Declare
|
||||||
|
|
||||||
mainCondition :: [Filter Challenge]
|
mainCondition :: [Filter Challenge]
|
||||||
@ -24,13 +22,26 @@ declareListChallengesSwagger :: Declare (Definitions Schema) Swagger
|
|||||||
declareListChallengesSwagger = do
|
declareListChallengesSwagger = do
|
||||||
-- param schemas
|
-- param schemas
|
||||||
listChallengesResponse <- declareResponse (Proxy :: Proxy [Entity Challenge])
|
listChallengesResponse <- declareResponse (Proxy :: Proxy [Entity Challenge])
|
||||||
|
challengeInfoResponse <- declareResponse (Proxy :: Proxy (Entity Challenge))
|
||||||
|
let challengeNameSchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
|
||||||
return $ mempty
|
return $ mempty
|
||||||
& paths .~
|
& paths .~
|
||||||
[ ("/api/list-challenges", mempty & get ?~ (mempty
|
[ ("/api/list-challenges", mempty & get ?~ (mempty
|
||||||
& produces ?~ MimeList ["application/json"]
|
& produces ?~ MimeList ["application/json"]
|
||||||
& description ?~ "Returns the list of all challenges"
|
& description ?~ "Returns the list of all challenges"
|
||||||
& at 200 ?~ Inline listChallengesResponse))
|
& at 200 ?~ Inline listChallengesResponse)),
|
||||||
|
("/api/challenge-info/{challengeName}",
|
||||||
|
mempty & get ?~ (mempty
|
||||||
|
& parameters .~ [ Inline $ mempty
|
||||||
|
& name .~ "challengeName"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamPath
|
||||||
|
& paramSchema .~ challengeNameSchema) ]
|
||||||
|
& produces ?~ MimeList ["application/json"]
|
||||||
|
& description ?~ "Returns metadata for a specific challenge"
|
||||||
|
& at 200 ?~ Inline challengeInfoResponse))
|
||||||
]
|
]
|
||||||
|
|
||||||
listChallengesApi :: Swagger
|
listChallengesApi :: Swagger
|
||||||
@ -44,13 +55,20 @@ getListChallengesJsonR = generalListChallengesJson mainCondition
|
|||||||
getListArchivedChallengesR :: Handler Html
|
getListArchivedChallengesR :: Handler Html
|
||||||
getListArchivedChallengesR = generalListChallenges [ChallengeArchived ==. Just True]
|
getListArchivedChallengesR = generalListChallenges [ChallengeArchived ==. Just True]
|
||||||
|
|
||||||
|
imageUrl :: Entity Challenge -> Maybe (Route App)
|
||||||
|
imageUrl (Entity challengeId challenge) =
|
||||||
|
case challengeImage challenge of
|
||||||
|
Just _ -> Just $ ChallengeImageR challengeId
|
||||||
|
Nothing -> Nothing
|
||||||
|
|
||||||
instance ToJSON (Entity Challenge) where
|
instance ToJSON (Entity Challenge) where
|
||||||
toJSON (Entity _ ch) = object
|
toJSON chEnt@(Entity _ ch) = object
|
||||||
[ "name" .= challengeName ch
|
[ "name" .= challengeName ch
|
||||||
, "title" .= challengeTitle ch
|
, "title" .= challengeTitle ch
|
||||||
, "description" .= challengeDescription ch
|
, "description" .= challengeDescription ch
|
||||||
, "starred" .= challengeStarred ch
|
, "starred" .= challengeStarred ch
|
||||||
, "archived" .= challengeArchived ch
|
, "archived" .= challengeArchived ch
|
||||||
|
, "imageUrl" .= (("/" <>) <$> intercalate "/" <$> fst <$> renderRoute <$> imageUrl chEnt)
|
||||||
]
|
]
|
||||||
|
|
||||||
instance ToSchema (Entity Challenge) where
|
instance ToSchema (Entity Challenge) where
|
||||||
@ -65,6 +83,7 @@ instance ToSchema (Entity Challenge) where
|
|||||||
, ("description", stringSchema)
|
, ("description", stringSchema)
|
||||||
, ("starred", booleanSchema)
|
, ("starred", booleanSchema)
|
||||||
, ("archived", booleanSchema)
|
, ("archived", booleanSchema)
|
||||||
|
, ("imageUrl", stringSchema)
|
||||||
]
|
]
|
||||||
& required .~ [ "name", "title", "description", "starred", "archived" ]
|
& required .~ [ "name", "title", "description", "starred", "archived" ]
|
||||||
|
|
||||||
@ -87,6 +106,11 @@ getChallenges filterExpr = runDB $ selectList filterExpr [Desc ChallengeStarred,
|
|||||||
listChallengesCore :: [Entity Challenge] -> Widget
|
listChallengesCore :: [Entity Challenge] -> Widget
|
||||||
listChallengesCore challenges = $(widgetFile "list-challenges-core")
|
listChallengesCore challenges = $(widgetFile "list-challenges-core")
|
||||||
|
|
||||||
|
getChallengeInfoJsonR :: Text -> Handler Value
|
||||||
|
getChallengeInfoJsonR challengeName = do
|
||||||
|
entCh <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
|
return $ toJSON entCh
|
||||||
|
|
||||||
getChallengeImageR :: ChallengeId -> Handler Html
|
getChallengeImageR :: ChallengeId -> Handler Html
|
||||||
getChallengeImageR challengeId = do
|
getChallengeImageR challengeId = do
|
||||||
challenge <- runDB $ get404 challengeId
|
challenge <- runDB $ get404 challengeId
|
||||||
|
152
Handler/Query.hs
152
Handler/Query.hs
@ -2,7 +2,7 @@
|
|||||||
|
|
||||||
module Handler.Query where
|
module Handler.Query where
|
||||||
|
|
||||||
import Import
|
import Import hiding (fromList, Proxy)
|
||||||
|
|
||||||
import Handler.SubmissionView
|
import Handler.SubmissionView
|
||||||
import Handler.Shared
|
import Handler.Shared
|
||||||
@ -43,6 +43,93 @@ import System.Directory (makeAbsolute)
|
|||||||
|
|
||||||
import Data.SplitIntoCrossTabs
|
import Data.SplitIntoCrossTabs
|
||||||
|
|
||||||
|
import Data.Swagger hiding (get)
|
||||||
|
import qualified Data.Swagger as DS
|
||||||
|
|
||||||
|
import Data.Swagger.Declare
|
||||||
|
import Control.Lens hiding ((.=), (^.), (<.>))
|
||||||
|
import Data.Proxy as DPR
|
||||||
|
import Data.HashMap.Strict.InsOrd (fromList)
|
||||||
|
|
||||||
|
import Handler.ShowChallenge
|
||||||
|
|
||||||
|
|
||||||
|
data VariantView = VariantView {
|
||||||
|
variantViewId :: Int64,
|
||||||
|
variantViewName :: Text,
|
||||||
|
variantViewRank :: Int,
|
||||||
|
variantViewEvaluations :: [EvaluationView],
|
||||||
|
variantViewParams :: [Parameter]
|
||||||
|
}
|
||||||
|
|
||||||
|
instance ToJSON Parameter where
|
||||||
|
toJSON entry = object
|
||||||
|
[ "name" .= parameterName entry,
|
||||||
|
"value" .= parameterValue entry
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToSchema Parameter where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
return $ NamedSchema (Just "Parameter") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("name", stringSchema),
|
||||||
|
("value", stringSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "name", "value" ]
|
||||||
|
|
||||||
|
instance ToJSON VariantView where
|
||||||
|
toJSON entry = object
|
||||||
|
[ "id" .= variantViewId entry,
|
||||||
|
"name" .= variantViewName entry,
|
||||||
|
"rank" .= variantViewRank entry,
|
||||||
|
"evaluations" .= variantViewEvaluations entry,
|
||||||
|
"params" .= variantViewParams entry
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToSchema VariantView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
intSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [Int64])
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [String])
|
||||||
|
evaluationsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [EvaluationView])
|
||||||
|
paramsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [Parameter])
|
||||||
|
return $ NamedSchema (Just "Variant") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("id", intSchema),
|
||||||
|
("name", stringSchema),
|
||||||
|
("rank", intSchema),
|
||||||
|
("evaluations", evaluationsSchema),
|
||||||
|
("params", paramsSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "evaluations" ]
|
||||||
|
|
||||||
|
data QueryResultView = QueryResultView {
|
||||||
|
queryResultViewSubmissionInfo :: FullSubmissionInfo,
|
||||||
|
queryResultViewVariants :: [VariantView]
|
||||||
|
}
|
||||||
|
|
||||||
|
instance ToJSON QueryResultView where
|
||||||
|
toJSON entry = object
|
||||||
|
[ "submissionInfo" .= queryResultViewSubmissionInfo entry,
|
||||||
|
"variants" .= queryResultViewVariants entry
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToSchema QueryResultView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
submissionInfoSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy FullSubmissionInfo)
|
||||||
|
variantViewsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [VariantView])
|
||||||
|
return $ NamedSchema (Just "QueryResult") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("submissionInfo", submissionInfoSchema),
|
||||||
|
("variants", variantViewsSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "submissionInfo", "variants" ]
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
rawCommitQuery :: (MonadIO m, RawSql a) => Text -> ReaderT SqlBackend m [a]
|
rawCommitQuery :: (MonadIO m, RawSql a) => Text -> ReaderT SqlBackend m [a]
|
||||||
rawCommitQuery sha1Prefix =
|
rawCommitQuery sha1Prefix =
|
||||||
rawSql "SELECT ?? FROM submission WHERE cast(commit as text) like ?" [PersistText $ "\\\\x" ++ sha1Prefix ++ "%"]
|
rawSql "SELECT ?? FROM submission WHERE cast(commit as text) like ?" [PersistText $ "\\\\x" ++ sha1Prefix ++ "%"]
|
||||||
@ -191,6 +278,69 @@ processQuery query = do
|
|||||||
setTitle "query results"
|
setTitle "query results"
|
||||||
$(widgetFile "query-results")
|
$(widgetFile "query-results")
|
||||||
|
|
||||||
|
toQueryResultView :: FullSubmissionInfo -> Handler QueryResultView
|
||||||
|
toQueryResultView fsi = do
|
||||||
|
let submissionId = fsiSubmissionId fsi
|
||||||
|
let submission = fsiSubmission fsi
|
||||||
|
(tableEntries, tests) <- runDB
|
||||||
|
$ getChallengeSubmissionInfos 2
|
||||||
|
(\s -> entityKey s == submissionId)
|
||||||
|
(const True)
|
||||||
|
id
|
||||||
|
(submissionChallenge submission)
|
||||||
|
|
||||||
|
|
||||||
|
let evaluations = map (\entry ->
|
||||||
|
VariantView {
|
||||||
|
variantViewId = fromSqlKey $ entityKey $ tableEntryVariant entry,
|
||||||
|
variantViewName = variantName $ entityVal $ tableEntryVariant entry,
|
||||||
|
variantViewRank = tableEntryRank entry,
|
||||||
|
variantViewEvaluations = catMaybes $ Import.map (convertEvaluationToView $ tableEntryMapping entry) tests,
|
||||||
|
variantViewParams = Import.map entityVal $ tableEntryParams entry
|
||||||
|
|
||||||
|
}) tableEntries
|
||||||
|
|
||||||
|
return $ QueryResultView {
|
||||||
|
queryResultViewSubmissionInfo = fsi,
|
||||||
|
queryResultViewVariants = evaluations }
|
||||||
|
|
||||||
|
getQueryJsonR :: Text -> Handler Value
|
||||||
|
getQueryJsonR query = do
|
||||||
|
submissions' <- findSubmissions query
|
||||||
|
let submissions = map fst submissions'
|
||||||
|
|
||||||
|
qrvs <- mapM toQueryResultView submissions
|
||||||
|
return $ array qrvs
|
||||||
|
|
||||||
|
declareQuerySwagger :: Declare (Definitions Schema) Swagger
|
||||||
|
declareQuerySwagger = do
|
||||||
|
-- param schemas
|
||||||
|
let querySchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
|
||||||
|
queryResponse <- declareResponse (Proxy :: Proxy [QueryResultView])
|
||||||
|
|
||||||
|
return $ mempty
|
||||||
|
& paths .~
|
||||||
|
fromList [ ("/api/query/{query}",
|
||||||
|
mempty & DS.get ?~ (mempty
|
||||||
|
& parameters .~ [ Inline $ mempty
|
||||||
|
& name .~ "query"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamPath
|
||||||
|
& paramSchema .~ querySchema) ]
|
||||||
|
& produces ?~ MimeList ["application/json"]
|
||||||
|
& description ?~ "For a SHA1 hash prefix returns all the submissions matching"
|
||||||
|
& at 200 ?~ Inline queryResponse))
|
||||||
|
]
|
||||||
|
|
||||||
|
|
||||||
|
queryApi :: Swagger
|
||||||
|
queryApi = spec & definitions .~ defs
|
||||||
|
where
|
||||||
|
(defs, spec) = runDeclare declareQuerySwagger mempty
|
||||||
|
|
||||||
|
|
||||||
priorityLimitForViewVariant :: Int
|
priorityLimitForViewVariant :: Int
|
||||||
priorityLimitForViewVariant = 4
|
priorityLimitForViewVariant = 4
|
||||||
|
|
||||||
|
@ -8,6 +8,8 @@ import Text.Markdown
|
|||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
|
|
||||||
|
import qualified Data.HashMap.Strict as HMS
|
||||||
|
|
||||||
import qualified Yesod.Table as Table
|
import qualified Yesod.Table as Table
|
||||||
|
|
||||||
import Handler.Extract
|
import Handler.Extract
|
||||||
@ -76,30 +78,15 @@ instance ToJSON LeaderboardEntry where
|
|||||||
(leaderboardBestVariant entry)
|
(leaderboardBestVariant entry)
|
||||||
(leaderboardParams entry)
|
(leaderboardParams entry)
|
||||||
, "times" .= leaderboardNumberOfSubmissions entry
|
, "times" .= leaderboardNumberOfSubmissions entry
|
||||||
|
, "hash" .= (fromSHA1ToText $ submissionCommit $ leaderboardBestSubmission entry)
|
||||||
]
|
]
|
||||||
|
|
||||||
instance ToSchema LeaderboardEntry where
|
|
||||||
declareNamedSchema _ = do
|
|
||||||
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
|
||||||
intSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Int)
|
|
||||||
return $ NamedSchema (Just "LeaderboardEntry") $ mempty
|
|
||||||
& type_ .~ SwaggerObject
|
|
||||||
& properties .~
|
|
||||||
fromList [ ("submitter", stringSchema)
|
|
||||||
, ("when", stringSchema)
|
|
||||||
, ("version", stringSchema)
|
|
||||||
, ("description", stringSchema)
|
|
||||||
, ("times", intSchema)
|
|
||||||
]
|
|
||||||
& required .~ [ "submitter", "when", "version", "description", "times" ]
|
|
||||||
|
|
||||||
|
|
||||||
declareLeaderboardSwagger :: Declare (Definitions Schema) Swagger
|
declareLeaderboardSwagger :: Declare (Definitions Schema) Swagger
|
||||||
declareLeaderboardSwagger = do
|
declareLeaderboardSwagger = do
|
||||||
-- param schemas
|
-- param schemas
|
||||||
let challengeNameSchema = toParamSchema (Proxy :: Proxy String)
|
let challengeNameSchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
|
||||||
leaderboardResponse <- declareResponse (Proxy :: Proxy [LeaderboardEntry])
|
leaderboardResponse <- declareResponse (Proxy :: Proxy LeaderboardView)
|
||||||
|
|
||||||
return $ mempty
|
return $ mempty
|
||||||
& paths .~
|
& paths .~
|
||||||
@ -122,31 +109,85 @@ leaderboardApi = spec & definitions .~ defs
|
|||||||
where
|
where
|
||||||
(defs, spec) = runDeclare declareLeaderboardSwagger mempty
|
(defs, spec) = runDeclare declareLeaderboardSwagger mempty
|
||||||
|
|
||||||
|
data LeaderboardView = LeaderboardView {
|
||||||
|
leaderboardViewTests :: [Entity Test],
|
||||||
|
leaderboardViewEntries :: [LeaderboardEntryView]
|
||||||
|
}
|
||||||
|
|
||||||
|
instance ToJSON LeaderboardView where
|
||||||
|
toJSON v = object
|
||||||
|
[ "tests" .= (map getTestReference $ leaderboardViewTests v)
|
||||||
|
, "entries" .= leaderboardViewEntries v
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToSchema LeaderboardView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
testsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [TestReference])
|
||||||
|
entriesSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [LeaderboardEntryView])
|
||||||
|
return $ NamedSchema (Just "Leaderboard") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("tests", testsSchema)
|
||||||
|
, ("entries", entriesSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "tests", "entries" ]
|
||||||
|
|
||||||
getLeaderboardJsonR :: Text -> Handler Value
|
getLeaderboardJsonR :: Text -> Handler Value
|
||||||
getLeaderboardJsonR name = do
|
getLeaderboardJsonR challengeName = do
|
||||||
app <- getYesod
|
app <- getYesod
|
||||||
let leaderboardStyle = appLeaderboardStyle $ appSettings app
|
let leaderboardStyle = appLeaderboardStyle $ appSettings app
|
||||||
|
|
||||||
Entity challengeId _ <- runDB $ getBy404 $ UniqueName name
|
Entity challengeId _ <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
(leaderboard, (_, tests)) <- getLeaderboardEntries 1 leaderboardStyle challengeId
|
(leaderboard, (_, tests)) <- getLeaderboardEntries 1 leaderboardStyle challengeId
|
||||||
return $ array $ map (leaderboardEntryJson tests) leaderboard
|
return $ toJSON $ LeaderboardView {
|
||||||
|
leaderboardViewTests = tests,
|
||||||
|
leaderboardViewEntries = map (toLeaderboardEntryView tests) leaderboard }
|
||||||
|
|
||||||
leaderboardEntryJson :: (ToJSON (f Value), Functor f) => f (Entity Test) -> LeaderboardEntry -> Value
|
data LeaderboardEntryView = LeaderboardEntryView {
|
||||||
leaderboardEntryJson tests entry = object [
|
leaderboardEntryViewEntry :: LeaderboardEntry,
|
||||||
"metadata" .= entry,
|
leaderboardEntryViewEvaluations :: [EvaluationView]
|
||||||
"metrics" .=
|
}
|
||||||
map (\e@(Entity _ t) -> object [
|
|
||||||
"metric" .= testName t,
|
addJsonKey :: Text -> Value -> Value -> Value
|
||||||
"score" .= (formatTruncatedScore (getTestFormattingOpts t) $ extractScoreFromLeaderboardEntry (getTestReference e) entry)]) tests]
|
addJsonKey key val (Object xs) = Object $ HMS.insert key val xs
|
||||||
|
addJsonKey _ _ xs = xs
|
||||||
|
|
||||||
|
instance ToJSON LeaderboardEntryView where
|
||||||
|
toJSON v = addJsonKey "evaluations"
|
||||||
|
(toJSON $ leaderboardEntryViewEvaluations v)
|
||||||
|
(toJSON $ leaderboardEntryViewEntry v)
|
||||||
|
|
||||||
|
instance ToSchema LeaderboardEntryView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
intSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Int)
|
||||||
|
evaluationsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [EvaluationView])
|
||||||
|
return $ NamedSchema (Just "LeaderboardEntry") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("submitter", stringSchema)
|
||||||
|
, ("when", stringSchema)
|
||||||
|
, ("version", stringSchema)
|
||||||
|
, ("description", stringSchema)
|
||||||
|
, ("times", intSchema)
|
||||||
|
, ("hash", stringSchema)
|
||||||
|
, ("evaluations", evaluationsSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "submitter", "when", "version", "description", "times", "hash", "evaluations" ]
|
||||||
|
|
||||||
|
toLeaderboardEntryView :: [(Entity Test)] -> LeaderboardEntry -> LeaderboardEntryView
|
||||||
|
toLeaderboardEntryView tests entry = LeaderboardEntryView {
|
||||||
|
leaderboardEntryViewEntry = entry,
|
||||||
|
leaderboardEntryViewEvaluations = catMaybes $
|
||||||
|
map (convertEvaluationToView (leaderboardEvaluationMap entry)) tests
|
||||||
|
}
|
||||||
|
|
||||||
getShowChallengeR :: Text -> Handler Html
|
getShowChallengeR :: Text -> Handler Html
|
||||||
getShowChallengeR name = do
|
getShowChallengeR challengeName = do
|
||||||
app <- getYesod
|
app <- getYesod
|
||||||
let leaderboardStyle = appLeaderboardStyle $ appSettings app
|
let leaderboardStyle = appLeaderboardStyle $ appSettings app
|
||||||
|
|
||||||
challengeEnt@(Entity challengeId challenge) <- runDB $ getBy404 $ UniqueName name
|
challengeEnt@(Entity challengeId challenge) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
Just repo <- runDB $ get $ challengePublicRepo challenge
|
Just repo <- runDB $ get $ challengePublicRepo challenge
|
||||||
(leaderboard, (entries, tests)) <- getLeaderboardEntries 1 leaderboardStyle challengeId
|
(leaderboard, (entries, tests)) <- getLeaderboardEntries 1 leaderboardStyle challengeId
|
||||||
|
|
||||||
@ -187,19 +228,51 @@ hasMetricsOfSecondPriority challengeId = do
|
|||||||
|
|
||||||
|
|
||||||
getChallengeReadmeR :: Text -> Handler Html
|
getChallengeReadmeR :: Text -> Handler Html
|
||||||
getChallengeReadmeR name = do
|
getChallengeReadmeR challengeName = do
|
||||||
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
|
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
readme <- challengeReadme name
|
readme <- challengeReadme challengeName
|
||||||
challengeLayout False challenge $ toWidget readme
|
challengeLayout False challenge $ toWidget readme
|
||||||
|
|
||||||
challengeReadme :: Text -> HandlerFor App Html
|
challengeReadmeInMarkdownApi :: Swagger
|
||||||
challengeReadme name = do
|
challengeReadmeInMarkdownApi = spec & definitions .~ defs
|
||||||
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
|
where
|
||||||
|
(defs, spec) = runDeclare declareChallengeReadmeInMarkdownSwagger mempty
|
||||||
|
|
||||||
|
declareChallengeReadmeInMarkdownSwagger :: Declare (Definitions Schema) Swagger
|
||||||
|
declareChallengeReadmeInMarkdownSwagger = do
|
||||||
|
-- param schemas
|
||||||
|
let challengeNameSchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
|
||||||
|
return $ mempty
|
||||||
|
& paths .~
|
||||||
|
fromList [ ("/api/challenge-readme/{challengeName}/markdown",
|
||||||
|
mempty & DS.get ?~ (mempty
|
||||||
|
& parameters .~ [ Inline $ mempty
|
||||||
|
& name .~ "challengeName"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamPath
|
||||||
|
& paramSchema .~ challengeNameSchema) ]
|
||||||
|
& produces ?~ MimeList ["application/text"]
|
||||||
|
& description ?~ "Returns the challenge README in Markdown"))
|
||||||
|
]
|
||||||
|
|
||||||
|
getChallengeReadmeInMarkdownR :: Text -> Handler TL.Text
|
||||||
|
getChallengeReadmeInMarkdownR challengeName = doChallengeReadmeContents challengeName
|
||||||
|
|
||||||
|
challengeReadme :: Text -> Handler Html
|
||||||
|
challengeReadme challengeName = do
|
||||||
|
theContents <- doChallengeReadmeContents challengeName
|
||||||
|
return $ markdown def theContents
|
||||||
|
|
||||||
|
doChallengeReadmeContents :: Text -> Handler TL.Text
|
||||||
|
doChallengeReadmeContents challengeName = do
|
||||||
|
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
let repoId = challengePublicRepo challenge
|
let repoId = challengePublicRepo challenge
|
||||||
repoDir <- getRepoDir repoId
|
repoDir <- getRepoDir repoId
|
||||||
let readmeFilePath = repoDir </> readmeFile
|
let readmeFilePath = repoDir </> readmeFile
|
||||||
theContents <- liftIO $ System.IO.readFile readmeFilePath
|
theContents <- liftIO $ System.IO.readFile readmeFilePath
|
||||||
return $ markdown def $ TL.pack theContents
|
return $ TL.pack theContents
|
||||||
|
|
||||||
showChallengeWidget :: Maybe (Entity User)
|
showChallengeWidget :: Maybe (Entity User)
|
||||||
-> Entity Challenge
|
-> Entity Challenge
|
||||||
@ -232,16 +305,16 @@ showChallengeWidget mUserEnt
|
|||||||
|
|
||||||
getRepoLink :: Repo -> Maybe Text
|
getRepoLink :: Repo -> Maybe Text
|
||||||
getRepoLink repo
|
getRepoLink repo
|
||||||
| sitePrefix `isPrefixOf` url = Just $ (browsableGitRepo bareRepoName) ++ "/" ++ (repoBranch repo)
|
| sitePrefix `isPrefixOf` theUrl = Just $ (browsableGitRepo bareRepoName) ++ "/" ++ (repoBranch repo)
|
||||||
| otherwise = Nothing
|
| otherwise = Nothing
|
||||||
where sitePrefix = "git://gonito.net/" :: Text
|
where sitePrefix = "git://gonito.net/" :: Text
|
||||||
sitePrefixLen = length sitePrefix
|
sitePrefixLen = length sitePrefix
|
||||||
url = repoUrl repo
|
theUrl = repoUrl repo
|
||||||
bareRepoName = drop sitePrefixLen url
|
bareRepoName = drop sitePrefixLen theUrl
|
||||||
|
|
||||||
getChallengeHowToR :: Text -> Handler Html
|
getChallengeHowToR :: Text -> Handler Html
|
||||||
getChallengeHowToR name = do
|
getChallengeHowToR challengeName = do
|
||||||
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
|
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
maybeUser <- maybeAuth
|
maybeUser <- maybeAuth
|
||||||
|
|
||||||
app <- getYesod
|
app <- getYesod
|
||||||
@ -318,8 +391,8 @@ archiveForm :: ChallengeId -> Form ChallengeId
|
|||||||
archiveForm challengeId = renderBootstrap3 BootstrapBasicForm $ areq hiddenField "" (Just challengeId)
|
archiveForm challengeId = renderBootstrap3 BootstrapBasicForm $ areq hiddenField "" (Just challengeId)
|
||||||
|
|
||||||
getChallengeSubmissionR :: Text -> Handler Html
|
getChallengeSubmissionR :: Text -> Handler Html
|
||||||
getChallengeSubmissionR name = do
|
getChallengeSubmissionR challengeName = do
|
||||||
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName name
|
(Entity _ challenge) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
maybeUser <- maybeAuth
|
maybeUser <- maybeAuth
|
||||||
|
|
||||||
Just repo <- runDB $ get $ challengePublicRepo challenge
|
Just repo <- runDB $ get $ challengePublicRepo challenge
|
||||||
@ -328,16 +401,82 @@ getChallengeSubmissionR name = do
|
|||||||
let repoHost = appRepoHost $ appSettings app
|
let repoHost = appRepoHost $ appSettings app
|
||||||
|
|
||||||
let defaultUrl = fromMaybe (defaultRepo scheme repoHost challenge repo maybeUser)
|
let defaultUrl = fromMaybe (defaultRepo scheme repoHost challenge repo maybeUser)
|
||||||
((<> name) <$> (join $ userAltRepoScheme <$> entityVal <$> maybeUser))
|
((<> challengeName) <$> (join $ userAltRepoScheme <$> entityVal <$> maybeUser))
|
||||||
|
|
||||||
(formWidget, formEnctype) <- generateFormPost $ submissionForm (Just defaultUrl) (defaultBranch scheme) (repoGitAnnexRemote repo)
|
(formWidget, formEnctype) <- generateFormPost $ submissionForm (Just defaultUrl) (defaultBranch scheme) (repoGitAnnexRemote repo)
|
||||||
challengeLayout True challenge $ challengeSubmissionWidget formWidget formEnctype challenge
|
challengeLayout True challenge $ challengeSubmissionWidget formWidget formEnctype challenge
|
||||||
|
|
||||||
|
|
||||||
|
declareChallengeSubmissionSwagger :: Declare (Definitions Schema) Swagger
|
||||||
|
declareChallengeSubmissionSwagger = do
|
||||||
|
-- param schemas
|
||||||
|
let challengeNameSchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
let stringSchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
|
||||||
|
challengeSubmissionResponse <- declareResponse (Proxy :: Proxy Int)
|
||||||
|
|
||||||
|
return $ mempty
|
||||||
|
& paths .~
|
||||||
|
fromList [ ("/api/challenge-submission/{challengeName}",
|
||||||
|
mempty & DS.post ?~ (mempty
|
||||||
|
& parameters .~ [ Inline $ mempty
|
||||||
|
& name .~ "challengeName"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamPath
|
||||||
|
& paramSchema .~ challengeNameSchema),
|
||||||
|
Inline $ mempty
|
||||||
|
& name .~ "f1"
|
||||||
|
& description .~ Just "submission description"
|
||||||
|
& required ?~ False
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamFormData
|
||||||
|
& paramSchema .~ stringSchema),
|
||||||
|
Inline $ mempty
|
||||||
|
& name .~ "f2"
|
||||||
|
& description .~ Just "submission tags"
|
||||||
|
& required ?~ False
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamFormData
|
||||||
|
& paramSchema .~ stringSchema),
|
||||||
|
Inline $ mempty
|
||||||
|
& name .~ "f3"
|
||||||
|
& description .~ Just "repo URL"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamFormData
|
||||||
|
& paramSchema .~ stringSchema),
|
||||||
|
Inline $ mempty
|
||||||
|
& name .~ "f4"
|
||||||
|
& description .~ Just "repo branch"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamFormData
|
||||||
|
& paramSchema .~ stringSchema),
|
||||||
|
|
||||||
|
Inline $ mempty
|
||||||
|
& name .~ "f5"
|
||||||
|
& description .~ Just "git-annex remote specification"
|
||||||
|
& required ?~ False
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamFormData
|
||||||
|
& paramSchema .~ stringSchema)]
|
||||||
|
& produces ?~ MimeList ["application/json"]
|
||||||
|
& description ?~ "Initiates a submission based on a given repo URL/branch. Returns an asynchrous job ID."
|
||||||
|
& at 200 ?~ Inline challengeSubmissionResponse))
|
||||||
|
]
|
||||||
|
|
||||||
|
challengeSubmissionApi :: Swagger
|
||||||
|
challengeSubmissionApi = spec & definitions .~ defs
|
||||||
|
where
|
||||||
|
(defs, spec) = runDeclare declareChallengeSubmissionSwagger mempty
|
||||||
|
|
||||||
|
|
||||||
postChallengeSubmissionJsonR :: Text -> Handler Value
|
postChallengeSubmissionJsonR :: Text -> Handler Value
|
||||||
postChallengeSubmissionJsonR name = do
|
postChallengeSubmissionJsonR challengeName = do
|
||||||
Entity userId _ <- requireAuthPossiblyByToken
|
Entity userId _ <- requireAuthPossiblyByToken
|
||||||
|
|
||||||
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName name
|
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
((result, _), _) <- runFormPost $ submissionForm Nothing Nothing Nothing
|
((result, _), _) <- runFormPost $ submissionForm Nothing Nothing Nothing
|
||||||
let submissionData' = case result of
|
let submissionData' = case result of
|
||||||
FormSuccess res -> Just res
|
FormSuccess res -> Just res
|
||||||
@ -347,10 +486,10 @@ postChallengeSubmissionJsonR name = do
|
|||||||
runViewProgressAsynchronously $ doCreateSubmission userId challengeId submissionData
|
runViewProgressAsynchronously $ doCreateSubmission userId challengeId submissionData
|
||||||
|
|
||||||
postChallengeSubmissionR :: Text -> Handler TypedContent
|
postChallengeSubmissionR :: Text -> Handler TypedContent
|
||||||
postChallengeSubmissionR name = do
|
postChallengeSubmissionR challengeName = do
|
||||||
userId <- requireAuthId
|
userId <- requireAuthId
|
||||||
|
|
||||||
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName name
|
(Entity challengeId _) <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
((result, _), _) <- runFormPost $ submissionForm Nothing Nothing Nothing
|
((result, _), _) <- runFormPost $ submissionForm Nothing Nothing Nothing
|
||||||
let submissionData' = case result of
|
let submissionData' = case result of
|
||||||
FormSuccess res -> Just res
|
FormSuccess res -> Just res
|
||||||
@ -376,19 +515,19 @@ postTriggerLocallyR = do
|
|||||||
postTriggerRemotelyR :: Handler TypedContent
|
postTriggerRemotelyR :: Handler TypedContent
|
||||||
postTriggerRemotelyR = do
|
postTriggerRemotelyR = do
|
||||||
(Just challengeName) <- lookupPostParam "challenge"
|
(Just challengeName) <- lookupPostParam "challenge"
|
||||||
(Just url) <- lookupPostParam "url"
|
(Just theUrl) <- lookupPostParam "url"
|
||||||
(Just token) <- lookupPostParam "token"
|
(Just token) <- lookupPostParam "token"
|
||||||
mBranch <- lookupPostParam "branch"
|
mBranch <- lookupPostParam "branch"
|
||||||
mGitAnnexRemote <- lookupPostParam "git-annex-remote"
|
mGitAnnexRemote <- lookupPostParam "git-annex-remote"
|
||||||
doTrigger token challengeName url mBranch mGitAnnexRemote
|
doTrigger token challengeName theUrl mBranch mGitAnnexRemote
|
||||||
|
|
||||||
postTriggerRemotelySimpleR :: Text -> Text -> Text -> Text -> Handler TypedContent
|
postTriggerRemotelySimpleR :: Text -> Text -> Text -> Text -> Handler TypedContent
|
||||||
postTriggerRemotelySimpleR token challengeName url branch =
|
postTriggerRemotelySimpleR token challengeName theUrl branch =
|
||||||
doTrigger token challengeName (decodeSlash url) (Just branch) Nothing
|
doTrigger token challengeName (decodeSlash theUrl) (Just branch) Nothing
|
||||||
|
|
||||||
getTriggerRemotelySimpleR :: Text -> Text -> Text -> Text -> Handler TypedContent
|
getTriggerRemotelySimpleR :: Text -> Text -> Text -> Text -> Handler TypedContent
|
||||||
getTriggerRemotelySimpleR token challengeName url branch =
|
getTriggerRemotelySimpleR token challengeName theUrl branch =
|
||||||
doTrigger token challengeName (decodeSlash url) (Just branch) Nothing
|
doTrigger token challengeName (decodeSlash theUrl) (Just branch) Nothing
|
||||||
|
|
||||||
data GitServerPayload = GitServerPayload {
|
data GitServerPayload = GitServerPayload {
|
||||||
gitServerPayloadRef :: Text,
|
gitServerPayloadRef :: Text,
|
||||||
@ -415,20 +554,20 @@ postTriggerByWebhookR token challengeName = do
|
|||||||
then
|
then
|
||||||
do
|
do
|
||||||
let branch = T.replace refPrefix "" ref
|
let branch = T.replace refPrefix "" ref
|
||||||
let url = fromMaybe (fromJust $ gitServerPayloadGitSshUrl payload)
|
let theUrl = fromMaybe (fromJust $ gitServerPayloadGitSshUrl payload)
|
||||||
(gitServerPayloadSshUrl payload)
|
(gitServerPayloadSshUrl payload)
|
||||||
doTrigger token challengeName url (Just branch) Nothing
|
doTrigger token challengeName theUrl (Just branch) Nothing
|
||||||
else
|
else
|
||||||
error $ "unexpected ref `" ++ (T.unpack ref) ++ "`"
|
error $ "unexpected ref `" ++ (T.unpack ref) ++ "`"
|
||||||
|
|
||||||
|
|
||||||
doTrigger :: Text -> Text -> Text -> Maybe Text -> Maybe Text -> Handler TypedContent
|
doTrigger :: Text -> Text -> Text -> Maybe Text -> Maybe Text -> Handler TypedContent
|
||||||
doTrigger token challengeName url mBranch mGitAnnexRemote = do
|
doTrigger token challengeName theUrl mBranch mGitAnnexRemote = do
|
||||||
[Entity userId _] <- runDB $ selectList [UserTriggerToken ==. Just token] []
|
[Entity userId _] <- runDB $ selectList [UserTriggerToken ==. Just token] []
|
||||||
trigger userId challengeName url mBranch mGitAnnexRemote
|
trigger userId challengeName theUrl mBranch mGitAnnexRemote
|
||||||
|
|
||||||
trigger :: UserId -> Text -> Text -> Maybe Text -> Maybe Text -> Handler TypedContent
|
trigger :: UserId -> Text -> Text -> Maybe Text -> Maybe Text -> Handler TypedContent
|
||||||
trigger userId challengeName url mBranch mGitAnnexRemote = do
|
trigger userId challengeName theUrl mBranch mGitAnnexRemote = do
|
||||||
let branch = fromMaybe "master" mBranch
|
let branch = fromMaybe "master" mBranch
|
||||||
mChallengeEnt <- runDB $ getBy $ UniqueName challengeName
|
mChallengeEnt <- runDB $ getBy $ UniqueName challengeName
|
||||||
|
|
||||||
@ -436,7 +575,7 @@ trigger userId challengeName url mBranch mGitAnnexRemote = do
|
|||||||
challengeSubmissionDataDescription = Nothing,
|
challengeSubmissionDataDescription = Nothing,
|
||||||
challengeSubmissionDataTags = Nothing,
|
challengeSubmissionDataTags = Nothing,
|
||||||
challengeSubmissionDataRepo = RepoSpec {
|
challengeSubmissionDataRepo = RepoSpec {
|
||||||
repoSpecUrl=url,
|
repoSpecUrl=theUrl,
|
||||||
repoSpecBranch=branch,
|
repoSpecBranch=branch,
|
||||||
repoSpecGitAnnexRemote=mGitAnnexRemote}
|
repoSpecGitAnnexRemote=mGitAnnexRemote}
|
||||||
}
|
}
|
||||||
@ -453,8 +592,8 @@ isBefore moment (Just deadline) = moment <= deadline
|
|||||||
-- the submission repo, just by looking at the metadata)
|
-- the submission repo, just by looking at the metadata)
|
||||||
willClone :: Challenge -> ChallengeSubmissionData -> Bool
|
willClone :: Challenge -> ChallengeSubmissionData -> Bool
|
||||||
willClone challenge submissionData =
|
willClone challenge submissionData =
|
||||||
(challengeName challenge) `isInfixOf` url && branch /= dontPeek && not (dontPeek `isInfixOf` url)
|
(challengeName challenge) `isInfixOf` theUrl && branch /= dontPeek && not (dontPeek `isInfixOf` theUrl)
|
||||||
where url = repoSpecUrl $ challengeSubmissionDataRepo submissionData
|
where theUrl = repoSpecUrl $ challengeSubmissionDataRepo submissionData
|
||||||
branch = repoSpecBranch $ challengeSubmissionDataRepo submissionData
|
branch = repoSpecBranch $ challengeSubmissionDataRepo submissionData
|
||||||
dontPeek = "dont-peek"
|
dontPeek = "dont-peek"
|
||||||
|
|
||||||
@ -464,10 +603,10 @@ doCreateSubmission :: UserId -> Key Challenge -> ChallengeSubmissionData -> Chan
|
|||||||
doCreateSubmission userId challengeId challengeSubmissionData chan = do
|
doCreateSubmission userId challengeId challengeSubmissionData chan = do
|
||||||
challenge <- runDB $ get404 challengeId
|
challenge <- runDB $ get404 challengeId
|
||||||
|
|
||||||
version <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
|
theVersion <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
|
||||||
theNow <- liftIO getCurrentTime
|
theNow <- liftIO getCurrentTime
|
||||||
|
|
||||||
if theNow `isBefore` (versionDeadline $ entityVal version)
|
if theNow `isBefore` (versionDeadline $ entityVal theVersion)
|
||||||
then
|
then
|
||||||
do
|
do
|
||||||
let wanted = willClone challenge challengeSubmissionData
|
let wanted = willClone challenge challengeSubmissionData
|
||||||
@ -504,7 +643,7 @@ doCreateSubmission' _ userId challengeId challengeSubmissionData chan = do
|
|||||||
TheHigherTheBetter -> E.desc
|
TheHigherTheBetter -> E.desc
|
||||||
TheLowerTheBetter -> E.asc
|
TheLowerTheBetter -> E.asc
|
||||||
|
|
||||||
bestResultSoFar <- runDB $ E.select $ E.from $ \(evaluation, submission, variant, out, test, version) -> do
|
bestResultSoFar <- runDB $ E.select $ E.from $ \(evaluation, submission, variant, out, test, theVersion) -> do
|
||||||
E.where_ (submission ^. SubmissionChallenge E.==. E.val challengeId
|
E.where_ (submission ^. SubmissionChallenge E.==. E.val challengeId
|
||||||
E.&&. submission ^. SubmissionIsHidden E.==. E.val False
|
E.&&. submission ^. SubmissionIsHidden E.==. E.val False
|
||||||
E.&&. variant ^. VariantSubmission E.==. submission ^. SubmissionId
|
E.&&. variant ^. VariantSubmission E.==. submission ^. SubmissionId
|
||||||
@ -516,10 +655,10 @@ doCreateSubmission' _ userId challengeId challengeSubmissionData chan = do
|
|||||||
E.&&. test ^. TestName E.==. E.val (testName mainTest)
|
E.&&. test ^. TestName E.==. E.val (testName mainTest)
|
||||||
E.&&. test ^. TestMetric E.==. E.val (testMetric mainTest)
|
E.&&. test ^. TestMetric E.==. E.val (testMetric mainTest)
|
||||||
E.&&. test ^. TestActive
|
E.&&. test ^. TestActive
|
||||||
E.&&. (evaluation ^. EvaluationVersion E.==. E.just (version ^. VersionCommit)
|
E.&&. (evaluation ^. EvaluationVersion E.==. E.just (theVersion ^. VersionCommit)
|
||||||
E.||. E.isNothing (evaluation ^. EvaluationVersion))
|
E.||. E.isNothing (evaluation ^. EvaluationVersion))
|
||||||
E.&&. version ^. VersionCommit E.==. test ^. TestCommit
|
E.&&. theVersion ^. VersionCommit E.==. test ^. TestCommit
|
||||||
E.&&. version ^. VersionMajor E.>=. E.val submittedMajorVersion)
|
E.&&. theVersion ^. VersionMajor E.>=. E.val submittedMajorVersion)
|
||||||
E.orderBy [orderDirection (evaluation ^. EvaluationScore)]
|
E.orderBy [orderDirection (evaluation ^. EvaluationScore)]
|
||||||
E.limit 1
|
E.limit 1
|
||||||
return evaluation
|
return evaluation
|
||||||
@ -671,7 +810,7 @@ getScoreForOut mainTestId out = do
|
|||||||
Nothing -> Nothing
|
Nothing -> Nothing
|
||||||
|
|
||||||
getSubmission :: UserId -> Key Repo -> SHA1 -> Key Challenge -> Text -> Channel -> Handler (Key Submission)
|
getSubmission :: UserId -> Key Repo -> SHA1 -> Key Challenge -> Text -> Channel -> Handler (Key Submission)
|
||||||
getSubmission userId repoId commit challengeId description chan = do
|
getSubmission userId repoId commit challengeId subDescription chan = do
|
||||||
challenge <- runDB $ get404 challengeId
|
challenge <- runDB $ get404 challengeId
|
||||||
maybeSubmission <- runDB $ getBy $ UniqueSubmissionRepoCommitChallenge repoId commit challengeId
|
maybeSubmission <- runDB $ getBy $ UniqueSubmissionRepoCommitChallenge repoId commit challengeId
|
||||||
case maybeSubmission of
|
case maybeSubmission of
|
||||||
@ -685,7 +824,7 @@ getSubmission userId repoId commit challengeId description chan = do
|
|||||||
submissionRepo=repoId,
|
submissionRepo=repoId,
|
||||||
submissionCommit=commit,
|
submissionCommit=commit,
|
||||||
submissionChallenge=challengeId,
|
submissionChallenge=challengeId,
|
||||||
submissionDescription=description,
|
submissionDescription=subDescription,
|
||||||
submissionStamp=time,
|
submissionStamp=time,
|
||||||
submissionSubmitter=userId,
|
submissionSubmitter=userId,
|
||||||
submissionIsPublic=False,
|
submissionIsPublic=False,
|
||||||
@ -756,7 +895,7 @@ authorizationTokenAuth = do
|
|||||||
let token = BS.filter (/= 32) token'
|
let token = BS.filter (/= 32) token'
|
||||||
einfo <- liftIO $ JWT.decode [jwk] (Just (JWT.JwsEncoding JWA.RS256)) token
|
einfo <- liftIO $ JWT.decode [jwk] (Just (JWT.JwsEncoding JWA.RS256)) token
|
||||||
return $ case einfo of
|
return $ case einfo of
|
||||||
Right (JWT.Jws (_, info)) -> decode $ fromStrict info
|
Right (JWT.Jws (_, infos)) -> decode $ fromStrict infos
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
| otherwise -> return Nothing
|
| otherwise -> return Nothing
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
@ -765,8 +904,8 @@ maybeAuthPossiblyByToken :: Handler (Maybe (Entity User))
|
|||||||
maybeAuthPossiblyByToken = do
|
maybeAuthPossiblyByToken = do
|
||||||
mInfo <- authorizationTokenAuth
|
mInfo <- authorizationTokenAuth
|
||||||
case mInfo of
|
case mInfo of
|
||||||
Just info -> do
|
Just infos -> do
|
||||||
x <- runDB $ getBy $ UniqueUser $ jwtAuthInfoIdent info
|
x <- runDB $ getBy $ UniqueUser $ jwtAuthInfoIdent infos
|
||||||
case x of
|
case x of
|
||||||
Just entUser -> return $ Just entUser
|
Just entUser -> return $ Just entUser
|
||||||
Nothing -> maybeAuth
|
Nothing -> maybeAuth
|
||||||
@ -777,8 +916,8 @@ requireAuthPossiblyByToken :: Handler (Entity User)
|
|||||||
requireAuthPossiblyByToken = do
|
requireAuthPossiblyByToken = do
|
||||||
mInfo <- authorizationTokenAuth
|
mInfo <- authorizationTokenAuth
|
||||||
case mInfo of
|
case mInfo of
|
||||||
Just info -> do
|
Just infos -> do
|
||||||
x <- runDB $ getBy $ UniqueUser $ jwtAuthInfoIdent info
|
x <- runDB $ getBy $ UniqueUser $ jwtAuthInfoIdent infos
|
||||||
case x of
|
case x of
|
||||||
Just entUser -> return entUser
|
Just entUser -> return entUser
|
||||||
Nothing -> requireAuth
|
Nothing -> requireAuth
|
||||||
@ -793,8 +932,8 @@ getAddUserR :: Handler Value
|
|||||||
getAddUserR = do
|
getAddUserR = do
|
||||||
mInfo <- authorizationTokenAuth
|
mInfo <- authorizationTokenAuth
|
||||||
case mInfo of
|
case mInfo of
|
||||||
Just info -> do
|
Just infos -> do
|
||||||
let ident = jwtAuthInfoIdent info
|
let ident = jwtAuthInfoIdent infos
|
||||||
x <- runDB $ getBy $ UniqueUser ident
|
x <- runDB $ getBy $ UniqueUser ident
|
||||||
case x of
|
case x of
|
||||||
Just _ -> return $ Bool False
|
Just _ -> return $ Bool False
|
||||||
@ -815,24 +954,57 @@ getAddUserR = do
|
|||||||
return $ Bool True
|
return $ Bool True
|
||||||
Nothing -> return $ Bool False
|
Nothing -> return $ Bool False
|
||||||
|
|
||||||
|
declareAllSubmissionsApi :: String -> String -> Declare (Definitions Schema) Swagger
|
||||||
|
declareAllSubmissionsApi q d = do
|
||||||
|
-- param schemas
|
||||||
|
let challengeNameSchema = toParamSchema (Proxy :: Proxy String)
|
||||||
|
|
||||||
|
allSubmissionsResponse <- declareResponse (Proxy :: Proxy SubmissionsView)
|
||||||
|
|
||||||
|
return $ mempty
|
||||||
|
& paths .~
|
||||||
|
fromList [ ("/api/" ++ q ++ "/{challengeName}",
|
||||||
|
mempty & DS.get ?~ (mempty
|
||||||
|
& parameters .~ [ Inline $ mempty
|
||||||
|
& name .~ "challengeName"
|
||||||
|
& required ?~ True
|
||||||
|
& schema .~ ParamOther (mempty
|
||||||
|
& in_ .~ ParamPath
|
||||||
|
& paramSchema .~ challengeNameSchema) ]
|
||||||
|
& produces ?~ MimeList ["application/json"]
|
||||||
|
& description ?~ T.pack d
|
||||||
|
& at 200 ?~ Inline allSubmissionsResponse))
|
||||||
|
]
|
||||||
|
|
||||||
|
|
||||||
|
allSubmissionsApi :: Swagger
|
||||||
|
allSubmissionsApi = spec & definitions .~ defs
|
||||||
|
where
|
||||||
|
(defs, spec) = runDeclare (declareAllSubmissionsApi "challenge-all-submissions" "Returns all submissions for a challenge") mempty
|
||||||
|
|
||||||
|
mySubmissionsApi :: Swagger
|
||||||
|
mySubmissionsApi = spec & definitions .~ defs
|
||||||
|
where
|
||||||
|
(defs, spec) = runDeclare (declareAllSubmissionsApi "challenge-my-submissions" "Returns all submissions for a challenge for the user") mempty
|
||||||
|
|
||||||
getChallengeAllSubmissionsJsonR :: Text -> Handler Value
|
getChallengeAllSubmissionsJsonR :: Text -> Handler Value
|
||||||
getChallengeAllSubmissionsJsonR name = do
|
getChallengeAllSubmissionsJsonR challengeName = do
|
||||||
v <- fetchAllSubmissionsView name
|
v <- fetchAllSubmissionsView challengeName
|
||||||
return $ toJSON v
|
return $ toJSON v
|
||||||
|
|
||||||
getChallengeMySubmissionsJsonR :: Text -> Handler Value
|
getChallengeMySubmissionsJsonR :: Text -> Handler Value
|
||||||
getChallengeMySubmissionsJsonR name = do
|
getChallengeMySubmissionsJsonR challengeName = do
|
||||||
v <- fetchMySubmissionsView name
|
v <- fetchMySubmissionsView challengeName
|
||||||
return $ toJSON v
|
return $ toJSON v
|
||||||
|
|
||||||
fetchAllSubmissionsView :: Text -> Handler SubmissionsView
|
fetchAllSubmissionsView :: Text -> Handler SubmissionsView
|
||||||
fetchAllSubmissionsView name = do
|
fetchAllSubmissionsView challengeName = do
|
||||||
fetchChallengeSubmissionsView (const True) name
|
fetchChallengeSubmissionsView (const True) challengeName
|
||||||
|
|
||||||
fetchMySubmissionsView :: Text -> Handler SubmissionsView
|
fetchMySubmissionsView :: Text -> Handler SubmissionsView
|
||||||
fetchMySubmissionsView name = do
|
fetchMySubmissionsView challengeName = do
|
||||||
Entity userId _ <- requireAuthPossiblyByToken
|
Entity userId _ <- requireAuthPossiblyByToken
|
||||||
fetchChallengeSubmissionsView (\(Entity _ submission) -> (submissionSubmitter submission == userId)) name
|
fetchChallengeSubmissionsView (\(Entity _ submission) -> (submissionSubmitter submission == userId)) challengeName
|
||||||
|
|
||||||
convertTagInfoToView :: (Entity Import.Tag, Entity SubmissionTag) -> TagView
|
convertTagInfoToView :: (Entity Import.Tag, Entity SubmissionTag) -> TagView
|
||||||
convertTagInfoToView tagInfo =
|
convertTagInfoToView tagInfo =
|
||||||
@ -843,7 +1015,7 @@ convertTagInfoToView tagInfo =
|
|||||||
}
|
}
|
||||||
|
|
||||||
convertEvaluationToView :: Map TestReference Evaluation -> Entity Test -> Maybe EvaluationView
|
convertEvaluationToView :: Map TestReference Evaluation -> Entity Test -> Maybe EvaluationView
|
||||||
convertEvaluationToView mapping entTest =
|
convertEvaluationToView theMapping entTest =
|
||||||
case join $ evaluationScore <$> mEvaluation of
|
case join $ evaluationScore <$> mEvaluation of
|
||||||
Just s ->
|
Just s ->
|
||||||
Just $ EvaluationView {
|
Just $ EvaluationView {
|
||||||
@ -852,7 +1024,7 @@ convertEvaluationToView mapping entTest =
|
|||||||
evaluationViewTest = testRef
|
evaluationViewTest = testRef
|
||||||
}
|
}
|
||||||
Nothing -> Nothing
|
Nothing -> Nothing
|
||||||
where mEvaluation = Map.lookup testRef mapping
|
where mEvaluation = Map.lookup testRef theMapping
|
||||||
formattingOps = getTestFormattingOpts $ entityVal entTest
|
formattingOps = getTestFormattingOpts $ entityVal entTest
|
||||||
testRef = getTestReference entTest
|
testRef = getTestReference entTest
|
||||||
|
|
||||||
@ -883,8 +1055,8 @@ convertTableEntryToView tests entry = do
|
|||||||
where submission = entityVal $ tableEntrySubmission entry
|
where submission = entityVal $ tableEntrySubmission entry
|
||||||
|
|
||||||
fetchChallengeSubmissionsView :: ((Entity Submission) -> Bool) -> Text -> Handler SubmissionsView
|
fetchChallengeSubmissionsView :: ((Entity Submission) -> Bool) -> Text -> Handler SubmissionsView
|
||||||
fetchChallengeSubmissionsView condition name = do
|
fetchChallengeSubmissionsView condition challengeName = do
|
||||||
Entity challengeId _ <- runDB $ getBy404 $ UniqueName name
|
Entity challengeId _ <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
(evaluationMaps, tests') <- runDB $ getChallengeSubmissionInfos 1 condition (const True) id challengeId
|
(evaluationMaps, tests') <- runDB $ getChallengeSubmissionInfos 1 condition (const True) id challengeId
|
||||||
let tests = sortBy testComparator tests'
|
let tests = sortBy testComparator tests'
|
||||||
|
|
||||||
@ -898,12 +1070,12 @@ fetchChallengeSubmissionsView condition name = do
|
|||||||
|
|
||||||
-- TODO switch to fetchChallengeSubmissionSview
|
-- TODO switch to fetchChallengeSubmissionSview
|
||||||
getChallengeMySubmissionsR :: Text -> Handler Html
|
getChallengeMySubmissionsR :: Text -> Handler Html
|
||||||
getChallengeMySubmissionsR name = do
|
getChallengeMySubmissionsR challengeName = do
|
||||||
userId <- requireAuthId
|
userId <- requireAuthId
|
||||||
getChallengeSubmissions (\(Entity _ submission) -> (submissionSubmitter submission == userId)) name
|
getChallengeSubmissions (\(Entity _ submission) -> (submissionSubmitter submission == userId)) challengeName
|
||||||
|
|
||||||
getChallengeAllSubmissionsR :: Text -> Handler Html
|
getChallengeAllSubmissionsR :: Text -> Handler Html
|
||||||
getChallengeAllSubmissionsR name = getChallengeSubmissions (\_ -> True) name
|
getChallengeAllSubmissionsR challengeName = getChallengeSubmissions (\_ -> True) challengeName
|
||||||
|
|
||||||
data EvaluationView = EvaluationView {
|
data EvaluationView = EvaluationView {
|
||||||
evaluationViewScore :: Text,
|
evaluationViewScore :: Text,
|
||||||
@ -918,6 +1090,21 @@ instance ToJSON EvaluationView where
|
|||||||
, "test" .= evaluationViewTest e
|
, "test" .= evaluationViewTest e
|
||||||
]
|
]
|
||||||
|
|
||||||
|
instance ToSchema EvaluationView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
doubleSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Double)
|
||||||
|
testRefSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy TestReference)
|
||||||
|
return $ NamedSchema (Just "Evaluation") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("score", stringSchema)
|
||||||
|
, ("full-score", doubleSchema)
|
||||||
|
, ("test", testRefSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "score", "full-score", "test" ]
|
||||||
|
|
||||||
|
|
||||||
data TagView = TagView {
|
data TagView = TagView {
|
||||||
tagViewName :: Text,
|
tagViewName :: Text,
|
||||||
tagViewDescription :: Maybe Text,
|
tagViewDescription :: Maybe Text,
|
||||||
@ -930,6 +1117,20 @@ instance ToJSON TagView where
|
|||||||
, "accepted" .= tagViewAccepted t
|
, "accepted" .= tagViewAccepted t
|
||||||
]
|
]
|
||||||
|
|
||||||
|
instance ToSchema TagView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
boolSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Bool)
|
||||||
|
return $ NamedSchema (Just "Tag") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("name", stringSchema)
|
||||||
|
, ("description", stringSchema)
|
||||||
|
, ("accepted", boolSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "name", "description" ]
|
||||||
|
|
||||||
|
|
||||||
data SubmissionView = SubmissionView {
|
data SubmissionView = SubmissionView {
|
||||||
submissionViewId :: Int64,
|
submissionViewId :: Int64,
|
||||||
submissionViewVariantId :: Int64,
|
submissionViewVariantId :: Int64,
|
||||||
@ -965,6 +1166,36 @@ instance ToJSON SubmissionView where
|
|||||||
, "isPublic" .= submissionViewIsPublic s
|
, "isPublic" .= submissionViewIsPublic s
|
||||||
]
|
]
|
||||||
|
|
||||||
|
instance ToSchema SubmissionView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
boolSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Bool)
|
||||||
|
intSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Int)
|
||||||
|
intsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [Int])
|
||||||
|
tagsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [TagView])
|
||||||
|
evalsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [EvaluationView])
|
||||||
|
return $ NamedSchema (Just "SubmissionView") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("id", intSchema)
|
||||||
|
, ("variant", intSchema)
|
||||||
|
, ("rank", intSchema)
|
||||||
|
, ("submitter", stringSchema)
|
||||||
|
, ("when", stringSchema)
|
||||||
|
, ("version", intsSchema)
|
||||||
|
, ("description", stringSchema)
|
||||||
|
, ("tags", tagsSchema)
|
||||||
|
, ("hash", stringSchema)
|
||||||
|
, ("evaluations", evalsSchema)
|
||||||
|
, ("isOwner", boolSchema)
|
||||||
|
, ("isReevaluable", boolSchema)
|
||||||
|
, ("isVisible", boolSchema)
|
||||||
|
, ("isPublic", boolSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "id", "variant", "rank", "submitter", "when", "version",
|
||||||
|
"description", "tags", "hash", "evaluations",
|
||||||
|
"isOwner", "isReevaluable", "isVisible", "isPublic" ]
|
||||||
|
|
||||||
data SubmissionsView = SubmissionsView {
|
data SubmissionsView = SubmissionsView {
|
||||||
submissionsViewSubmissions :: [SubmissionView],
|
submissionsViewSubmissions :: [SubmissionView],
|
||||||
submissionsViewTests :: [TestReference]
|
submissionsViewTests :: [TestReference]
|
||||||
@ -976,9 +1207,21 @@ instance ToJSON SubmissionsView where
|
|||||||
"submissions" .= submissionsViewSubmissions ss
|
"submissions" .= submissionsViewSubmissions ss
|
||||||
]
|
]
|
||||||
|
|
||||||
|
instance ToSchema SubmissionsView where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
submissionViewsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [SubmissionView])
|
||||||
|
testRefsSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy [TestReference])
|
||||||
|
return $ NamedSchema (Just "Tag") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("submissions", submissionViewsSchema)
|
||||||
|
, ("tests", testRefsSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "tests", "submission" ]
|
||||||
|
|
||||||
getChallengeSubmissions :: ((Entity Submission) -> Bool) -> Text -> Handler Html
|
getChallengeSubmissions :: ((Entity Submission) -> Bool) -> Text -> Handler Html
|
||||||
getChallengeSubmissions condition name = do
|
getChallengeSubmissions condition challengeName = do
|
||||||
Entity challengeId challenge <- runDB $ getBy404 $ UniqueName name
|
Entity challengeId challenge <- runDB $ getBy404 $ UniqueName challengeName
|
||||||
(evaluationMaps, tests') <- runDB $ getChallengeSubmissionInfos 1 condition (const True) id challengeId
|
(evaluationMaps, tests') <- runDB $ getChallengeSubmissionInfos 1 condition (const True) id challengeId
|
||||||
let tests = sortBy testComparator tests'
|
let tests = sortBy testComparator tests'
|
||||||
mauth <- maybeAuth
|
mauth <- maybeAuth
|
||||||
@ -1068,10 +1311,10 @@ $.getJSON("@{ChallengeParamGraphDataR (challengeName challenge) testId param}",
|
|||||||
challengeLayout :: Bool -> Challenge -> WidgetFor App () -> HandlerFor App Html
|
challengeLayout :: Bool -> Challenge -> WidgetFor App () -> HandlerFor App Html
|
||||||
challengeLayout withHeader challenge widget = do
|
challengeLayout withHeader challenge widget = do
|
||||||
tagsAvailableAsJSON <- runDB $ getAvailableTagsAsJSON
|
tagsAvailableAsJSON <- runDB $ getAvailableTagsAsJSON
|
||||||
version <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
|
theVersion <- runDB $ getBy404 $ UniqueVersionByCommit $ challengeVersion challenge
|
||||||
let versionFormatted = formatVersion ((versionMajor $ entityVal version),
|
let versionFormatted = formatVersion ((versionMajor $ entityVal theVersion),
|
||||||
(versionMinor $ entityVal version),
|
(versionMinor $ entityVal theVersion),
|
||||||
(versionPatch $ entityVal version))
|
(versionPatch $ entityVal theVersion))
|
||||||
maybeUser <- maybeAuth
|
maybeUser <- maybeAuth
|
||||||
bc <- widgetToPageContent widget
|
bc <- widgetToPageContent widget
|
||||||
defaultLayout $ do
|
defaultLayout $ do
|
||||||
|
@ -1,10 +1,18 @@
|
|||||||
module Handler.SubmissionView where
|
module Handler.SubmissionView where
|
||||||
|
|
||||||
import Import
|
import Import hiding (fromList)
|
||||||
|
|
||||||
import qualified Database.Esqueleto as E
|
import qualified Database.Esqueleto as E
|
||||||
import Database.Esqueleto ((^.))
|
import Database.Esqueleto ((^.))
|
||||||
|
|
||||||
|
import Handler.Shared
|
||||||
|
import PersistSHA1
|
||||||
|
|
||||||
|
import Data.Swagger hiding (get)
|
||||||
|
import Control.Lens hiding ((.=), (^.))
|
||||||
|
import Data.Proxy as DPR
|
||||||
|
import Data.HashMap.Strict.InsOrd (fromList)
|
||||||
|
|
||||||
data FullSubmissionInfo = FullSubmissionInfo {
|
data FullSubmissionInfo = FullSubmissionInfo {
|
||||||
fsiSubmissionId :: SubmissionId,
|
fsiSubmissionId :: SubmissionId,
|
||||||
fsiSubmission :: Submission,
|
fsiSubmission :: Submission,
|
||||||
@ -13,10 +21,31 @@ data FullSubmissionInfo = FullSubmissionInfo {
|
|||||||
fsiChallenge :: Challenge,
|
fsiChallenge :: Challenge,
|
||||||
fsiChallengeRepo :: Repo,
|
fsiChallengeRepo :: Repo,
|
||||||
fsiScheme :: RepoScheme,
|
fsiScheme :: RepoScheme,
|
||||||
fsiTags :: [(Entity Tag, Entity SubmissionTag)],
|
fsiTags :: [(Entity Import.Tag, Entity SubmissionTag)],
|
||||||
fsiExternalLinks :: [Entity ExternalLink],
|
fsiExternalLinks :: [Entity ExternalLink],
|
||||||
fsiSuperSubmissions :: [FullSubmissionInfo] }
|
fsiSuperSubmissions :: [FullSubmissionInfo] }
|
||||||
|
|
||||||
|
instance ToJSON FullSubmissionInfo where
|
||||||
|
toJSON entry = object
|
||||||
|
[ "hash" .= (fromSHA1ToText $ submissionCommit $ fsiSubmission entry),
|
||||||
|
"submitter" .= (formatSubmitter $ fsiUser entry),
|
||||||
|
"challenge" .= (challengeName $ fsiChallenge entry)
|
||||||
|
]
|
||||||
|
|
||||||
|
instance ToSchema FullSubmissionInfo where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
return $ NamedSchema (Just "SubmissionInfo") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
fromList [ ("hash", stringSchema)
|
||||||
|
, ("submitter", stringSchema)
|
||||||
|
, ("challenge", stringSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "hash", "submitter", "challenge" ]
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
getFullInfo :: Entity Submission -> Handler FullSubmissionInfo
|
getFullInfo :: Entity Submission -> Handler FullSubmissionInfo
|
||||||
getFullInfo (Entity submissionId submission) = do
|
getFullInfo (Entity submissionId submission) = do
|
||||||
repo <- runDB $ get404 $ submissionRepo submission
|
repo <- runDB $ get404 $ submissionRepo submission
|
||||||
@ -50,7 +79,7 @@ getFullInfo (Entity submissionId submission) = do
|
|||||||
fsiExternalLinks = links,
|
fsiExternalLinks = links,
|
||||||
fsiSuperSubmissions = superSubmissionFsis }
|
fsiSuperSubmissions = superSubmissionFsis }
|
||||||
|
|
||||||
getTags :: (BaseBackend backend ~ SqlBackend, MonadIO m, PersistQueryRead backend) => Key Submission -> ReaderT backend m [(Entity Tag, Entity SubmissionTag)]
|
getTags :: (BaseBackend backend ~ SqlBackend, MonadIO m, PersistQueryRead backend) => Key Submission -> ReaderT backend m [(Entity Import.Tag, Entity SubmissionTag)]
|
||||||
getTags submissionId = do
|
getTags submissionId = do
|
||||||
sts <- selectList [SubmissionTagSubmission ==. submissionId] []
|
sts <- selectList [SubmissionTagSubmission ==. submissionId] []
|
||||||
let tagIds = Import.map (submissionTagTag . entityVal) sts
|
let tagIds = Import.map (submissionTagTag . entityVal) sts
|
||||||
|
@ -5,6 +5,7 @@ import Import
|
|||||||
import Data.Swagger
|
import Data.Swagger
|
||||||
import Handler.ListChallenges
|
import Handler.ListChallenges
|
||||||
import Handler.ShowChallenge
|
import Handler.ShowChallenge
|
||||||
|
import Handler.Query
|
||||||
|
|
||||||
import Control.Lens hiding ((.=))
|
import Control.Lens hiding ((.=))
|
||||||
|
|
||||||
@ -12,9 +13,17 @@ getSwaggerR :: Handler Value
|
|||||||
getSwaggerR = return $ toJSON apiDescription
|
getSwaggerR = return $ toJSON apiDescription
|
||||||
|
|
||||||
apiDescription :: Swagger
|
apiDescription :: Swagger
|
||||||
apiDescription = generalApi <> listChallengesApi <> leaderboardApi
|
apiDescription = generalApi
|
||||||
|
<> listChallengesApi
|
||||||
|
<> leaderboardApi
|
||||||
|
<> allSubmissionsApi
|
||||||
|
<> mySubmissionsApi
|
||||||
|
<> challengeReadmeInMarkdownApi
|
||||||
|
<> queryApi
|
||||||
|
<> challengeSubmissionApi
|
||||||
|
|
||||||
generalApi :: Swagger
|
generalApi :: Swagger
|
||||||
generalApi = (mempty :: Swagger)
|
generalApi = (mempty :: Swagger)
|
||||||
& info .~ (mempty &
|
& info .~ (mempty &
|
||||||
title .~ "Gonito API")
|
title .~ "Gonito API" &
|
||||||
|
version .~ "1.0.0")
|
||||||
|
@ -29,6 +29,13 @@ import GEval.EvaluationScheme
|
|||||||
|
|
||||||
import GEval.ParseParams (parseParamsFromFilePath, OutputFileParsed(..))
|
import GEval.ParseParams (parseParamsFromFilePath, OutputFileParsed(..))
|
||||||
|
|
||||||
|
import Data.Swagger hiding (get)
|
||||||
|
import qualified Data.Swagger as DS
|
||||||
|
import Data.Swagger.Declare
|
||||||
|
import Data.Proxy as DPR
|
||||||
|
import Control.Lens hiding ((.=), (^.))
|
||||||
|
import Data.HashMap.Strict.InsOrd (fromList)
|
||||||
|
|
||||||
data TestReference = TestReference Text Text
|
data TestReference = TestReference Text Text
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
@ -38,6 +45,16 @@ instance ToJSON TestReference where
|
|||||||
"metric" .= metric
|
"metric" .= metric
|
||||||
]
|
]
|
||||||
|
|
||||||
|
instance ToSchema TestReference where
|
||||||
|
declareNamedSchema _ = do
|
||||||
|
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
|
||||||
|
return $ NamedSchema (Just "TestReference") $ mempty
|
||||||
|
& type_ .~ SwaggerObject
|
||||||
|
& properties .~
|
||||||
|
Data.HashMap.Strict.InsOrd.fromList [ ("name", stringSchema)
|
||||||
|
, ("metric", stringSchema)
|
||||||
|
]
|
||||||
|
& required .~ [ "name", "metric" ]
|
||||||
|
|
||||||
getTestReference :: Entity Test -> TestReference
|
getTestReference :: Entity Test -> TestReference
|
||||||
getTestReference (Entity _ test) = TestReference (Data.Text.pack $ show $ testMetric test) (testName test)
|
getTestReference (Entity _ test) = TestReference (Data.Text.pack $ show $ testMetric test) (testName test)
|
||||||
@ -51,7 +68,7 @@ data LeaderboardEntry = LeaderboardEntry {
|
|||||||
leaderboardBestVariantId :: VariantId,
|
leaderboardBestVariantId :: VariantId,
|
||||||
leaderboardEvaluationMap :: Map TestReference Evaluation,
|
leaderboardEvaluationMap :: Map TestReference Evaluation,
|
||||||
leaderboardNumberOfSubmissions :: Int,
|
leaderboardNumberOfSubmissions :: Int,
|
||||||
leaderboardTags :: [(Entity Tag, Entity SubmissionTag)],
|
leaderboardTags :: [(Entity Import.Tag, Entity SubmissionTag)],
|
||||||
leaderboardParams :: [Parameter],
|
leaderboardParams :: [Parameter],
|
||||||
leaderboardVersion :: (Int, Int, Int)
|
leaderboardVersion :: (Int, Int, Int)
|
||||||
}
|
}
|
||||||
@ -61,7 +78,7 @@ data TableEntry = TableEntry {
|
|||||||
tableEntryVariant :: Entity Variant,
|
tableEntryVariant :: Entity Variant,
|
||||||
tableEntrySubmitter :: Entity User,
|
tableEntrySubmitter :: Entity User,
|
||||||
tableEntryMapping :: Map TestReference Evaluation,
|
tableEntryMapping :: Map TestReference Evaluation,
|
||||||
tableEntryTagsInfo :: [(Entity Tag, Entity SubmissionTag)],
|
tableEntryTagsInfo :: [(Entity Import.Tag, Entity SubmissionTag)],
|
||||||
tableEntryParams :: [Entity Parameter],
|
tableEntryParams :: [Entity Parameter],
|
||||||
tableEntryRank :: Int,
|
tableEntryRank :: Int,
|
||||||
tableEntryVersion :: (Int, Int, Int) }
|
tableEntryVersion :: (Int, Int, Int) }
|
||||||
@ -456,7 +473,7 @@ getScore testId variantId = do
|
|||||||
|
|
||||||
data BasicSubmissionInfo = BasicSubmissionInfo {
|
data BasicSubmissionInfo = BasicSubmissionInfo {
|
||||||
basicSubmissionInfoUser :: User,
|
basicSubmissionInfoUser :: User,
|
||||||
basicSubmissionInfoTagEnts :: [(Entity Tag, Entity SubmissionTag)],
|
basicSubmissionInfoTagEnts :: [(Entity Import.Tag, Entity SubmissionTag)],
|
||||||
basicSubmissionInfoVersion :: Version }
|
basicSubmissionInfoVersion :: Version }
|
||||||
|
|
||||||
getBasicSubmissionInfo :: (MonadIO m, PersistQueryRead backend,
|
getBasicSubmissionInfo :: (MonadIO m, PersistQueryRead backend,
|
||||||
|
@ -8,7 +8,7 @@ neither affiliated with nor endorsed by [Kaggle](https://www.kaggle.com)).
|
|||||||
|
|
||||||
What's so special about Gonito:
|
What's so special about Gonito:
|
||||||
|
|
||||||
* free & open-source (AGPL), you can use it your own, in your
|
* free & open-source (GPL), you can use it your own, in your
|
||||||
company, at your university, etc.
|
company, at your university, etc.
|
||||||
* git-based (challenges and solutions are submitted only with git).
|
* git-based (challenges and solutions are submitted only with git).
|
||||||
|
|
||||||
|
@ -18,8 +18,11 @@
|
|||||||
/api/user-info UserInfoR GET
|
/api/user-info UserInfoR GET
|
||||||
/api/add-user AddUserR GET
|
/api/add-user AddUserR GET
|
||||||
/api/challenge-submission/#Text ChallengeSubmissionJsonR POST
|
/api/challenge-submission/#Text ChallengeSubmissionJsonR POST
|
||||||
|
/api/challenge-readme/#Text/markdown ChallengeReadmeInMarkdownR GET
|
||||||
|
/api/challenge-image/#ChallengeId ChallengeImageR GET
|
||||||
|
/api/query/#Text QueryJsonR GET
|
||||||
|
/api/challenge-info/#Text ChallengeInfoJsonR GET
|
||||||
/list-archived-challenges ListArchivedChallengesR GET
|
/list-archived-challenges ListArchivedChallengesR GET
|
||||||
/challenge-image/#ChallengeId ChallengeImageR GET
|
|
||||||
|
|
||||||
/challenge/#Text ShowChallengeR GET
|
/challenge/#Text ShowChallengeR GET
|
||||||
/challenge-readme/#Text ChallengeReadmeR GET
|
/challenge-readme/#Text ChallengeReadmeR GET
|
||||||
|
@ -1,10 +1,10 @@
|
|||||||
name: gonito
|
name: gonito
|
||||||
version: 0.1.1
|
version: 1.0.0
|
||||||
cabal-version: >= 1.8
|
cabal-version: >= 1.8
|
||||||
build-type: Simple
|
build-type: Simple
|
||||||
homepage: http://gonito.net
|
homepage: http://gonito.net
|
||||||
license: AGPL-3
|
license: GPL-3
|
||||||
license-file: agpl-3.0.txt
|
license-file: gpl-3.0.txt
|
||||||
author: Filip Graliński
|
author: Filip Graliński
|
||||||
maintainer: filipg@amu.edu.pl
|
maintainer: filipg@amu.edu.pl
|
||||||
|
|
||||||
|
@ -1,21 +1,23 @@
|
|||||||
GNU AFFERO GENERAL PUBLIC LICENSE
|
GNU GENERAL PUBLIC LICENSE
|
||||||
Version 3, 19 November 2007
|
Version 3, 29 June 2007
|
||||||
|
|
||||||
Copyright (C) 2007 Free Software Foundation, Inc. <http://fsf.org/>
|
Copyright (C) 2007 Free Software Foundation, Inc. <https://fsf.org/>
|
||||||
Everyone is permitted to copy and distribute verbatim copies
|
Everyone is permitted to copy and distribute verbatim copies
|
||||||
of this license document, but changing it is not allowed.
|
of this license document, but changing it is not allowed.
|
||||||
|
|
||||||
Preamble
|
Preamble
|
||||||
|
|
||||||
The GNU Affero General Public License is a free, copyleft license for
|
The GNU General Public License is a free, copyleft license for
|
||||||
software and other kinds of works, specifically designed to ensure
|
software and other kinds of works.
|
||||||
cooperation with the community in the case of network server software.
|
|
||||||
|
|
||||||
The licenses for most software and other practical works are designed
|
The licenses for most software and other practical works are designed
|
||||||
to take away your freedom to share and change the works. By contrast,
|
to take away your freedom to share and change the works. By contrast,
|
||||||
our General Public Licenses are intended to guarantee your freedom to
|
the GNU General Public License is intended to guarantee your freedom to
|
||||||
share and change all versions of a program--to make sure it remains free
|
share and change all versions of a program--to make sure it remains free
|
||||||
software for all its users.
|
software for all its users. We, the Free Software Foundation, use the
|
||||||
|
GNU General Public License for most of our software; it applies also to
|
||||||
|
any other work released this way by its authors. You can apply it to
|
||||||
|
your programs, too.
|
||||||
|
|
||||||
When we speak of free software, we are referring to freedom, not
|
When we speak of free software, we are referring to freedom, not
|
||||||
price. Our General Public Licenses are designed to make sure that you
|
price. Our General Public Licenses are designed to make sure that you
|
||||||
@ -24,34 +26,44 @@ them if you wish), that you receive source code or can get it if you
|
|||||||
want it, that you can change the software or use pieces of it in new
|
want it, that you can change the software or use pieces of it in new
|
||||||
free programs, and that you know you can do these things.
|
free programs, and that you know you can do these things.
|
||||||
|
|
||||||
Developers that use our General Public Licenses protect your rights
|
To protect your rights, we need to prevent others from denying you
|
||||||
with two steps: (1) assert copyright on the software, and (2) offer
|
these rights or asking you to surrender the rights. Therefore, you have
|
||||||
you this License which gives you legal permission to copy, distribute
|
certain responsibilities if you distribute copies of the software, or if
|
||||||
and/or modify the software.
|
you modify it: responsibilities to respect the freedom of others.
|
||||||
|
|
||||||
A secondary benefit of defending all users' freedom is that
|
For example, if you distribute copies of such a program, whether
|
||||||
improvements made in alternate versions of the program, if they
|
gratis or for a fee, you must pass on to the recipients the same
|
||||||
receive widespread use, become available for other developers to
|
freedoms that you received. You must make sure that they, too, receive
|
||||||
incorporate. Many developers of free software are heartened and
|
or can get the source code. And you must show them these terms so they
|
||||||
encouraged by the resulting cooperation. However, in the case of
|
know their rights.
|
||||||
software used on network servers, this result may fail to come about.
|
|
||||||
The GNU General Public License permits making a modified version and
|
|
||||||
letting the public access it on a server without ever releasing its
|
|
||||||
source code to the public.
|
|
||||||
|
|
||||||
The GNU Affero General Public License is designed specifically to
|
Developers that use the GNU GPL protect your rights with two steps:
|
||||||
ensure that, in such cases, the modified source code becomes available
|
(1) assert copyright on the software, and (2) offer you this License
|
||||||
to the community. It requires the operator of a network server to
|
giving you legal permission to copy, distribute and/or modify it.
|
||||||
provide the source code of the modified version running there to the
|
|
||||||
users of that server. Therefore, public use of a modified version, on
|
|
||||||
a publicly accessible server, gives the public access to the source
|
|
||||||
code of the modified version.
|
|
||||||
|
|
||||||
An older license, called the Affero General Public License and
|
For the developers' and authors' protection, the GPL clearly explains
|
||||||
published by Affero, was designed to accomplish similar goals. This is
|
that there is no warranty for this free software. For both users' and
|
||||||
a different license, not a version of the Affero GPL, but Affero has
|
authors' sake, the GPL requires that modified versions be marked as
|
||||||
released a new version of the Affero GPL which permits relicensing under
|
changed, so that their problems will not be attributed erroneously to
|
||||||
this license.
|
authors of previous versions.
|
||||||
|
|
||||||
|
Some devices are designed to deny users access to install or run
|
||||||
|
modified versions of the software inside them, although the manufacturer
|
||||||
|
can do so. This is fundamentally incompatible with the aim of
|
||||||
|
protecting users' freedom to change the software. The systematic
|
||||||
|
pattern of such abuse occurs in the area of products for individuals to
|
||||||
|
use, which is precisely where it is most unacceptable. Therefore, we
|
||||||
|
have designed this version of the GPL to prohibit the practice for those
|
||||||
|
products. If such problems arise substantially in other domains, we
|
||||||
|
stand ready to extend this provision to those domains in future versions
|
||||||
|
of the GPL, as needed to protect the freedom of users.
|
||||||
|
|
||||||
|
Finally, every program is threatened constantly by software patents.
|
||||||
|
States should not allow patents to restrict development and use of
|
||||||
|
software on general-purpose computers, but in those that do, we wish to
|
||||||
|
avoid the special danger that patents applied to a free program could
|
||||||
|
make it effectively proprietary. To prevent this, the GPL assures that
|
||||||
|
patents cannot be used to render the program non-free.
|
||||||
|
|
||||||
The precise terms and conditions for copying, distribution and
|
The precise terms and conditions for copying, distribution and
|
||||||
modification follow.
|
modification follow.
|
||||||
@ -60,7 +72,7 @@ modification follow.
|
|||||||
|
|
||||||
0. Definitions.
|
0. Definitions.
|
||||||
|
|
||||||
"This License" refers to version 3 of the GNU Affero General Public License.
|
"This License" refers to version 3 of the GNU General Public License.
|
||||||
|
|
||||||
"Copyright" also means copyright-like laws that apply to other kinds of
|
"Copyright" also means copyright-like laws that apply to other kinds of
|
||||||
works, such as semiconductor masks.
|
works, such as semiconductor masks.
|
||||||
@ -537,45 +549,35 @@ to collect a royalty for further conveying from those to whom you convey
|
|||||||
the Program, the only way you could satisfy both those terms and this
|
the Program, the only way you could satisfy both those terms and this
|
||||||
License would be to refrain entirely from conveying the Program.
|
License would be to refrain entirely from conveying the Program.
|
||||||
|
|
||||||
13. Remote Network Interaction; Use with the GNU General Public License.
|
13. Use with the GNU Affero General Public License.
|
||||||
|
|
||||||
Notwithstanding any other provision of this License, if you modify the
|
|
||||||
Program, your modified version must prominently offer all users
|
|
||||||
interacting with it remotely through a computer network (if your version
|
|
||||||
supports such interaction) an opportunity to receive the Corresponding
|
|
||||||
Source of your version by providing access to the Corresponding Source
|
|
||||||
from a network server at no charge, through some standard or customary
|
|
||||||
means of facilitating copying of software. This Corresponding Source
|
|
||||||
shall include the Corresponding Source for any work covered by version 3
|
|
||||||
of the GNU General Public License that is incorporated pursuant to the
|
|
||||||
following paragraph.
|
|
||||||
|
|
||||||
Notwithstanding any other provision of this License, you have
|
Notwithstanding any other provision of this License, you have
|
||||||
permission to link or combine any covered work with a work licensed
|
permission to link or combine any covered work with a work licensed
|
||||||
under version 3 of the GNU General Public License into a single
|
under version 3 of the GNU Affero General Public License into a single
|
||||||
combined work, and to convey the resulting work. The terms of this
|
combined work, and to convey the resulting work. The terms of this
|
||||||
License will continue to apply to the part which is the covered work,
|
License will continue to apply to the part which is the covered work,
|
||||||
but the work with which it is combined will remain governed by version
|
but the special requirements of the GNU Affero General Public License,
|
||||||
3 of the GNU General Public License.
|
section 13, concerning interaction through a network will apply to the
|
||||||
|
combination as such.
|
||||||
|
|
||||||
14. Revised Versions of this License.
|
14. Revised Versions of this License.
|
||||||
|
|
||||||
The Free Software Foundation may publish revised and/or new versions of
|
The Free Software Foundation may publish revised and/or new versions of
|
||||||
the GNU Affero General Public License from time to time. Such new versions
|
the GNU General Public License from time to time. Such new versions will
|
||||||
will be similar in spirit to the present version, but may differ in detail to
|
be similar in spirit to the present version, but may differ in detail to
|
||||||
address new problems or concerns.
|
address new problems or concerns.
|
||||||
|
|
||||||
Each version is given a distinguishing version number. If the
|
Each version is given a distinguishing version number. If the
|
||||||
Program specifies that a certain numbered version of the GNU Affero General
|
Program specifies that a certain numbered version of the GNU General
|
||||||
Public License "or any later version" applies to it, you have the
|
Public License "or any later version" applies to it, you have the
|
||||||
option of following the terms and conditions either of that numbered
|
option of following the terms and conditions either of that numbered
|
||||||
version or of any later version published by the Free Software
|
version or of any later version published by the Free Software
|
||||||
Foundation. If the Program does not specify a version number of the
|
Foundation. If the Program does not specify a version number of the
|
||||||
GNU Affero General Public License, you may choose any version ever published
|
GNU General Public License, you may choose any version ever published
|
||||||
by the Free Software Foundation.
|
by the Free Software Foundation.
|
||||||
|
|
||||||
If the Program specifies that a proxy can decide which future
|
If the Program specifies that a proxy can decide which future
|
||||||
versions of the GNU Affero General Public License can be used, that proxy's
|
versions of the GNU General Public License can be used, that proxy's
|
||||||
public statement of acceptance of a version permanently authorizes you
|
public statement of acceptance of a version permanently authorizes you
|
||||||
to choose that version for the Program.
|
to choose that version for the Program.
|
||||||
|
|
||||||
@ -633,29 +635,40 @@ the "copyright" line and a pointer to where the full notice is found.
|
|||||||
Copyright (C) <year> <name of author>
|
Copyright (C) <year> <name of author>
|
||||||
|
|
||||||
This program is free software: you can redistribute it and/or modify
|
This program is free software: you can redistribute it and/or modify
|
||||||
it under the terms of the GNU Affero General Public License as published by
|
it under the terms of the GNU General Public License as published by
|
||||||
the Free Software Foundation, either version 3 of the License, or
|
the Free Software Foundation, either version 3 of the License, or
|
||||||
(at your option) any later version.
|
(at your option) any later version.
|
||||||
|
|
||||||
This program is distributed in the hope that it will be useful,
|
This program is distributed in the hope that it will be useful,
|
||||||
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||||
GNU Affero General Public License for more details.
|
GNU General Public License for more details.
|
||||||
|
|
||||||
You should have received a copy of the GNU Affero General Public License
|
You should have received a copy of the GNU General Public License
|
||||||
along with this program. If not, see <http://www.gnu.org/licenses/>.
|
along with this program. If not, see <https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
Also add information on how to contact you by electronic and paper mail.
|
Also add information on how to contact you by electronic and paper mail.
|
||||||
|
|
||||||
If your software can interact with users remotely through a computer
|
If the program does terminal interaction, make it output a short
|
||||||
network, you should also make sure that it provides a way for users to
|
notice like this when it starts in an interactive mode:
|
||||||
get its source. For example, if your program is a web application, its
|
|
||||||
interface could display a "Source" link that leads users to an archive
|
<program> Copyright (C) <year> <name of author>
|
||||||
of the code. There are many ways you could offer source, and different
|
This program comes with ABSOLUTELY NO WARRANTY; for details type `show w'.
|
||||||
solutions will be better for different programs; see section 13 for the
|
This is free software, and you are welcome to redistribute it
|
||||||
specific requirements.
|
under certain conditions; type `show c' for details.
|
||||||
|
|
||||||
|
The hypothetical commands `show w' and `show c' should show the appropriate
|
||||||
|
parts of the General Public License. Of course, your program's commands
|
||||||
|
might be different; for a GUI interface, you would use an "about box".
|
||||||
|
|
||||||
You should also get your employer (if you work as a programmer) or school,
|
You should also get your employer (if you work as a programmer) or school,
|
||||||
if any, to sign a "copyright disclaimer" for the program, if necessary.
|
if any, to sign a "copyright disclaimer" for the program, if necessary.
|
||||||
For more information on this, and how to apply and follow the GNU AGPL, see
|
For more information on this, and how to apply and follow the GNU GPL, see
|
||||||
<http://www.gnu.org/licenses/>.
|
<https://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
|
The GNU General Public License does not permit incorporating your program
|
||||||
|
into proprietary programs. If your program is a subroutine library, you
|
||||||
|
may consider it more useful to permit linking proprietary applications with
|
||||||
|
the library. If this is what you want to do, use the GNU Lesser General
|
||||||
|
Public License instead of this License. But first, please read
|
||||||
|
<https://www.gnu.org/licenses/why-not-lgpl.html>.
|
@ -39,7 +39,7 @@
|
|||||||
window.onload = function() {
|
window.onload = function() {
|
||||||
// Begin Swagger UI call region
|
// Begin Swagger UI call region
|
||||||
const ui = SwaggerUIBundle({
|
const ui = SwaggerUIBundle({
|
||||||
url: "http://127.0.0.1:3000/swagger.json",
|
url: "/swagger.json",
|
||||||
dom_id: '#swagger-ui',
|
dom_id: '#swagger-ui',
|
||||||
deepLinking: true,
|
deepLinking: true,
|
||||||
presets: [
|
presets: [
|
||||||
|
@ -16,7 +16,7 @@
|
|||||||
$if withHeader
|
$if withHeader
|
||||||
<h1>#{challengeTitle challenge}
|
<h1>#{challengeTitle challenge}
|
||||||
<p>#{challengeDescription challenge} [ver. #{versionFormatted}]
|
<p>#{challengeDescription challenge} [ver. #{versionFormatted}]
|
||||||
$maybe deadline <- versionDeadline $ entityVal version
|
$maybe deadline <- versionDeadline $ entityVal theVersion
|
||||||
<p>Deadline: #{show deadline}
|
<p>Deadline: #{show deadline}
|
||||||
$nothing
|
$nothing
|
||||||
^{pageBody bc}
|
^{pageBody bc}
|
||||||
|
@ -10,7 +10,7 @@
|
|||||||
<div class="panel panel-default">
|
<div class="panel panel-default">
|
||||||
<div class="panel-heading">What's so special about Gonito:
|
<div class="panel-heading">What's so special about Gonito:
|
||||||
<ul class="list-group">
|
<ul class="list-group">
|
||||||
<li class="list-group-item">free & open-source (AGPL), you can use it your own, in your company, at your university, etc. (git repo: <tt><a href="#{browsableGitRepo "gonito"}">git://gonito.net/gonito</a></tt>),
|
<li class="list-group-item">free & open-source (GPL), you can use it your own, in your company, at your university, etc. (git repo: <tt><a href="#{browsableGitRepo "gonito"}">git://gonito.net/gonito</a></tt>),
|
||||||
<li class="list-group-item">git-based (challenges and solutions are submitted only with git),
|
<li class="list-group-item">git-based (challenges and solutions are submitted only with git),
|
||||||
<li class="list-group-item">geval — a companion stand-alone tool for evaluation (<tt><a href="#{browsableGitRepo "geval"}">git://gonito.net/geval</a></tt>),
|
<li class="list-group-item">geval — a companion stand-alone tool for evaluation (<tt><a href="#{browsableGitRepo "geval"}">git://gonito.net/geval</a></tt>),
|
||||||
<li class="list-group-item">special features for organizing classes in machine learning.
|
<li class="list-group-item">special features for organizing classes in machine learning.
|
||||||
|
Loading…
Reference in New Issue
Block a user