{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
module RatingChgkInfo.Extra
( ExtraRatingApi
, extraRatingApiDesc
, extraRatingApiApp
) where
import qualified RatingChgkInfo.NoApi as NoApi
import RatingChgkInfo.Types (Request, TournamentId)
import Control.Lens
import qualified Data.ByteString.Lazy as LBS
import Data.Swagger
import Network.Wai (Application)
import Servant
import Servant.Swagger
type ExtraRatingApi
= "requests" :> Capture "tournament-id" TournamentId :> Get '[JSON] [Request]
extraRatingApiDesc :: Swagger
extraRatingApiDesc = toSwagger (Proxy :: Proxy ExtraRatingApi)
& info.title .~ "Дополнительный API для сайта рейтинга"
& info.version .~ "0.2"
& info.description ?~ "Вспомогательные функции API для работы с сайтом рейтинга."
& info.license ?~ "MIT"
& info.contact ?~ (mempty
& name ?~ "Мансур Зиятдинов"
& email ?~ "chgk@pm.me"
)
& host ?~ "extra.chgk.me"
& basePath ?~ "/api/v0.2.1"
extraRatingApiApp :: Application
extraRatingApiApp = serve (Proxy :: Proxy ExtraRatingApi) requests
where requests :: TournamentId -> Handler [Request]
requests tid = do
ers <- liftIO $ NoApi.requests tid
case ers of
Left "No such tournament, returned html" ->
throwError $ err404 { errBody = "Probably, no such tournament, rating.chgk.info returns html" }
Left "Not a synch, or no requests yet" ->
throwError $ err404 { errBody = "Not a synch, or no requests found" }
Left err ->
throwError $ err500 { errBody = LBS.fromStrict err }
Right rs ->
pure rs