End-point for listing tags

This commit is contained in:
Filip Gralinski 2021-03-11 21:23:18 +01:00
parent 602f4c39ca
commit 341d912ba8
4 changed files with 64 additions and 2 deletions

View File

@ -179,6 +179,7 @@ instance Yesod App where
isAuthorized (ChallengeSubmissionJsonR _) _ = return Authorized isAuthorized (ChallengeSubmissionJsonR _) _ = return Authorized
isAuthorized (ChallengeReadmeInMarkdownR _) _ = regularAuthorization isAuthorized (ChallengeReadmeInMarkdownR _) _ = regularAuthorization
isAuthorized (QueryJsonR _) _ = return Authorized isAuthorized (QueryJsonR _) _ = return Authorized
isAuthorized ListTagsJsonR _ = regularAuthorization
isAuthorized (ChallengeGraphDataR _) _ = regularAuthorization isAuthorized (ChallengeGraphDataR _) _ = regularAuthorization
isAuthorized (ChallengeDiscussionR _) _ = regularAuthorization isAuthorized (ChallengeDiscussionR _) _ = regularAuthorization

View File

@ -6,6 +6,8 @@ import Data.Swagger
import Handler.ListChallenges import Handler.ListChallenges
import Handler.ShowChallenge import Handler.ShowChallenge
import Handler.Query import Handler.Query
import Handler.Tags
import Control.Lens hiding ((.=)) import Control.Lens hiding ((.=))
@ -22,6 +24,7 @@ apiDescription = generalApi
<> queryApi <> queryApi
<> challengeSubmissionApi <> challengeSubmissionApi
<> versionInfoApi <> versionInfoApi
<> listTagsApi
generalApi :: Swagger generalApi :: Swagger
generalApi = (mempty :: Swagger) generalApi = (mempty :: Swagger)

View File

@ -1,6 +1,8 @@
{-# LANGUAGE OverloadedLists #-}
module Handler.Tags where module Handler.Tags where
import Import import Import hiding (fromList, get)
import Handler.Common (checkIfAdmin) import Handler.Common (checkIfAdmin)
import Yesod.Form.Bootstrap3 (BootstrapFormLayout (..), renderBootstrap3, bfs) import Yesod.Form.Bootstrap3 (BootstrapFormLayout (..), renderBootstrap3, bfs)
@ -8,6 +10,55 @@ import qualified Yesod.Table as Table
import Handler.TagUtils import Handler.TagUtils
import Data.Swagger.Declare
import Data.Swagger hiding (Tag, tags)
import Data.Proxy as DPR
import Control.Lens hiding ((.=))
import Data.HashMap.Strict.InsOrd (fromList)
instance ToJSON (Entity Tag) where
toJSON v = object
[ "name" .= (tagName $ entityVal v)
, "description" .= (tagDescription $ entityVal v)
, "id" .= (entityKey v)
]
instance ToSchema (Entity Tag) where
declareNamedSchema _ = do
stringSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy String)
intSchema <- declareSchemaRef (DPR.Proxy :: DPR.Proxy Int)
return $ NamedSchema (Just "Tag") $ mempty
& type_ .~ SwaggerObject
& properties .~
fromList [ ("name", stringSchema)
, ("description", stringSchema)
, ("id", intSchema)
]
& required .~ [ "name", "description", "id" ]
listTagsApi :: Swagger
listTagsApi = spec & definitions .~ defs
where
(defs, spec) = runDeclare declareListTagsSwagger mempty
declareListTagsSwagger :: Declare (Definitions Schema) Swagger
declareListTagsSwagger = do
listTagsResponse <- declareResponse (DPR.Proxy :: DPR.Proxy [Entity Tag])
return $ mempty
& paths .~
[ ("/api/list-tags", mempty & get ?~ (mempty
& produces ?~ MimeList ["application/json"]
& description ?~ "Returns the list of all tags"
& at 200 ?~ Inline listTagsResponse))
]
getListTagsJsonR :: Handler Value
getListTagsJsonR = do
allTags <- fetchAllTags
return $ toJSON allTags
getTagsR :: Handler Html getTagsR :: Handler Html
getTagsR = do getTagsR = do
(formWidget, formEnctype) <- generateFormPost tagForm (formWidget, formEnctype) <- generateFormPost tagForm
@ -39,8 +90,14 @@ canAddTags = do
EverybodyCanAddNewTags -> return $ isJust mUser EverybodyCanAddNewTags -> return $ isJust mUser
fetchAllTags :: (PersistQueryRead (YesodPersistBackend site),
YesodPersist site,
BaseBackend (YesodPersistBackend site) ~ SqlBackend)
=> HandlerFor site [Entity Tag]
fetchAllTags = runDB $ selectList [] [Asc TagName]
doTags formWidget formEnctype = do doTags formWidget formEnctype = do
tags <- runDB $ selectList [] [Asc TagName] tags <- fetchAllTags
canTagsBeAdded <- canAddTags canTagsBeAdded <- canAddTags
defaultLayout $ do defaultLayout $ do
setTitle "Tags" setTitle "Tags"

View File

@ -25,6 +25,7 @@
/api/query/#Text QueryJsonR GET /api/query/#Text QueryJsonR GET
/api/challenge-info/#Text ChallengeInfoJsonR GET /api/challenge-info/#Text ChallengeInfoJsonR GET
/api/version-info/#Text VersionInfoJsonR GET /api/version-info/#Text VersionInfoJsonR GET
/api/list-tags ListTagsJsonR GET
/list-archived-challenges ListArchivedChallengesR GET /list-archived-challenges ListArchivedChallengesR GET
/my-teams MyTeamsR GET /my-teams MyTeamsR GET