Add format-as-local-time end-point

Also breaking change - version in version-info is a list instead
of string
This commit is contained in:
Filip Gralinski 2021-09-02 22:38:59 +02:00
parent 891c9645ab
commit ea96c9b177
6 changed files with 56 additions and 10 deletions

View File

@ -185,6 +185,7 @@ instance Yesod App where
isAuthorized (QueryJsonR _) _ = regularAuthorization isAuthorized (QueryJsonR _) _ = regularAuthorization
isAuthorized ListTagsJsonR _ = regularAuthorization isAuthorized ListTagsJsonR _ = regularAuthorization
isAuthorized CurrentTimeR _ = return Authorized isAuthorized CurrentTimeR _ = return Authorized
isAuthorized (FormatAsLocalTimeR _) _ = return Authorized
isAuthorized (ChallengeGraphDataR _) _ = regularAuthorization isAuthorized (ChallengeGraphDataR _) _ = regularAuthorization
isAuthorized (ChallengeDiscussionR _) _ = regularAuthorization isAuthorized (ChallengeDiscussionR _) _ = regularAuthorization

View File

@ -5,7 +5,6 @@ module Handler.ListChallenges where
import Import hiding (get, fromList, Proxy) import Import hiding (get, fromList, Proxy)
import Handler.Shared
import PersistSHA1 import PersistSHA1
import Data.HashMap.Strict.InsOrd (fromList) import Data.HashMap.Strict.InsOrd (fromList)
@ -121,16 +120,21 @@ versionInfoApi = spec & definitions .~ defs
instance ToJSON (Entity Version) where instance ToJSON (Entity Version) where
toJSON chEnt@(Entity _ ver) = object toJSON (Entity _ ver) = object
[ "deadline" .= versionDeadline ver [ "deadline" .= versionDeadline ver
, "version" .= (formatVersion (versionMajor ver, , "version" .= ((versionMajor ver),
versionMinor ver, (versionMinor ver),
versionPatch ver)) (versionPatch ver))
, "description" .= versionDescription ver , "description" .= versionDescription ver
, "when" .= versionStamp ver , "when" .= versionStamp ver
, "commit" .= (fromSHA1ToText $ versionCommit ver) , "commit" .= (fromSHA1ToText $ versionCommit ver)
] ]
versionSchema :: Referenced Schema
versionSchema = Inline $ toSchema (Proxy :: Proxy [Int])
& description .~ Just "Challenge version"
& example .~ Just (toJSON ([2, 0, 1] :: [Int]))
instance ToSchema (Entity Version) where instance ToSchema (Entity Version) where
declareNamedSchema _ = do declareNamedSchema _ = do
stringSchema <- declareSchemaRef (Proxy :: Proxy String) stringSchema <- declareSchemaRef (Proxy :: Proxy String)
@ -138,7 +142,7 @@ instance ToSchema (Entity Version) where
& type_ .~ SwaggerObject & type_ .~ SwaggerObject
& properties .~ & properties .~
fromList [ ("deadline", stringSchema) fromList [ ("deadline", stringSchema)
, ("version", stringSchema) , ("version", versionSchema)
, ("description", stringSchema) , ("description", stringSchema)
, ("when", stringSchema) , ("when", stringSchema)
, ("commit", stringSchema) , ("commit", stringSchema)

View File

@ -18,6 +18,9 @@ import qualified Yesod.Table as Table
import Control.Concurrent.Lifted (threadDelay) import Control.Concurrent.Lifted (threadDelay)
import Data.Time.LocalTime import Data.Time.LocalTime
import Data.Time.Clock
import qualified Data.List.Utils as DLU
import Handler.Extract import Handler.Extract
import Handler.Shared import Handler.Shared
@ -1142,8 +1145,14 @@ getUserInfoR = do
getCurrentTimeR :: Handler Value getCurrentTimeR :: Handler Value
getCurrentTimeR = do getCurrentTimeR = do
theNow <- liftIO $ getZonedTime theNow <- liftIO $ getCurrentTime
return $ toJSON $ zonedTimeToLocalTime theNow return $ toJSON theNow
getFormatAsLocalTimeR :: String -> Handler Value
getFormatAsLocalTimeR t = do
let ut = TR.read $ DLU.replace "T" " " $ DLU.replace "Z" " " t
tz <- liftIO $ getTimeZone ut
return $ toJSON $ utcToLocalTime tz ut
getMyEvaluationTriggerTokenJsonR :: Handler Value getMyEvaluationTriggerTokenJsonR :: Handler Value
@ -1278,6 +1287,35 @@ declareCurrentTimeApi = do
] ]
formatAsLocalTimeApi :: Swagger
formatAsLocalTimeApi = spec & definitions .~ defs
where
(defs, spec) = runDeclare declareFormatAsLocalTimeApi mempty
declareFormatAsLocalTimeApi :: Declare (Definitions Schema) Swagger
declareFormatAsLocalTimeApi = do
-- param schemas
response <- declareResponse (Proxy :: Proxy String)
let utcTimeSchema = toParamSchema (Proxy :: Proxy String)
return $ mempty
& paths .~
fromList [ ("/api/format-as-local-time/{utcTime}",
mempty & DS.get ?~ (mempty
& parameters .~ [ ]
& produces ?~ MimeList ["application/json"]
& description ?~ "Formats the given UTC time stamp as a local time"
& parameters .~ [ Inline $ mempty
& name .~ "utcTime"
& required ?~ True
& schema .~ ParamOther (mempty
& in_ .~ ParamPath
& paramSchema .~ utcTimeSchema) ]
& at 200 ?~ Inline response))
]
myEvaluationTriggerTokenApi :: Swagger myEvaluationTriggerTokenApi :: Swagger
myEvaluationTriggerTokenApi = spec & definitions .~ defs myEvaluationTriggerTokenApi = spec & definitions .~ defs
where where

View File

@ -35,7 +35,8 @@ apiDescription = generalApi
<> testProgressApi <> testProgressApi
<> viewProgressWithWebSockets <> viewProgressWithWebSockets
<> viewProgressLog <> viewProgressLog
<> currentTimeApi
<> formatAsLocalTimeApi
generalApi :: Swagger generalApi :: Swagger
generalApi = (mempty :: Swagger) generalApi = (mempty :: Swagger)

View File

@ -35,6 +35,7 @@
/api/my-teams MyTeamsJsonR GET /api/my-teams MyTeamsJsonR GET
/api/my-evaluation-trigger-token MyEvaluationTriggerTokenJsonR GET /api/my-evaluation-trigger-token MyEvaluationTriggerTokenJsonR GET
/api/current-time CurrentTimeR GET /api/current-time CurrentTimeR GET
/api/format-as-local-time/#String FormatAsLocalTimeR GET
/list-archived-challenges ListArchivedChallengesR GET /list-archived-challenges ListArchivedChallengesR GET
/my-teams MyTeamsR GET /my-teams MyTeamsR GET

View File

@ -165,6 +165,7 @@ library
, lens , lens
, insert-ordered-containers , insert-ordered-containers
, yesod-websockets , yesod-websockets
, MissingH
executable gonito executable gonito
if flag(library-only) if flag(library-only)