rating-chgk-info-0.3.6.4: Client for rating.chgk.info API and CSV tables (documentation in Russian)

Copyright(c) Mansur Ziiatdinov 2018-2019
LicenseBSD-3
Maintainerchgk@pm.me
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

RatingChgkInfo.Types

Contents

Description

Типы в этом модуле практически совпадают с теми, которые возвращаются сайтом рейтинга. Поэтому и проблемы у них (такие, как использование строк вместо целых и т.п.) общие. Часть этих проблем задокументирована при помощи пометок API NOTE.

Возможно, в следующих версиях библиотеки будут какие-то способы обезопасить себя от ошибок, либо (надеюсь) в результате развития API сайта рейтинга, либо без этого.

Synopsis

Работа с API

В этом разделе описаны типы, используемые при запросах к предоставляемому сайтом рейтинга REST API

type RatingClient = ClientM Source #

Синоним типа для реэкспорта. Монада, в которой возможно выполнять запросы к REST API сайта рейтинга

Общие типы

data Items a Source #

Список элементов с общим количеством для разбиения на страницы

Constructors

Items 

Fields

  • total :: Int

    Общее количество

  • items :: [a]

    Сами элементы

Instances
Eq a => Eq (Items a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: Items a -> Items a -> Bool #

(/=) :: Items a -> Items a -> Bool #

Read a => Read (Items a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Show a => Show (Items a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

showsPrec :: Int -> Items a -> ShowS #

show :: Items a -> String #

showList :: [Items a] -> ShowS #

Generic (Items a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep (Items a) :: Type -> Type #

Methods

from :: Items a -> Rep (Items a) x #

to :: Rep (Items a) x -> Items a #

FromJSON a => FromJSON (Items a) Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep (Items a) Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep (Items a) = D1 (MetaData "Items" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "Items" PrefixI True) (S1 (MetaSel (Just "total") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "items") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [a])))

newtype SeasonMap a Source #

Отображение сезонов на элементы

API NOTE: пустое отображение должно обозначаться {} вместо []

Constructors

SeasonMap 

Fields

Instances
Eq a => Eq (SeasonMap a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: SeasonMap a -> SeasonMap a -> Bool #

(/=) :: SeasonMap a -> SeasonMap a -> Bool #

Read a => Read (SeasonMap a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Show a => Show (SeasonMap a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic (SeasonMap a) Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep (SeasonMap a) :: Type -> Type #

Methods

from :: SeasonMap a -> Rep (SeasonMap a) x #

to :: Rep (SeasonMap a) x -> SeasonMap a #

FromJSON a => FromJSON (SeasonMap a) Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep (SeasonMap a) Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep (SeasonMap a) = D1 (MetaData "SeasonMap" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" True) (C1 (MetaCons "SeasonMap" PrefixI True) (S1 (MetaSel (Just "unSeasonMap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int a))))

type RatingApi = ("players" :> (QueryParam "page" Int :> Get '[JSON] (Items Player))) :<|> (("players" :> (Capture "idplayer" PlayerId :> Get '[JSON] [Player])) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("teams" :> Get '[JSON] [PlayerTeam]))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("teams" :> ("last" :> Get '[JSON] [PlayerTeam])))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("teams" :> (Capture "idseason" Int :> Get '[JSON] [PlayerTeam])))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("tournaments" :> Get '[JSON] (SeasonMap PlayerSeason)))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("tournaments" :> ("last" :> Get '[JSON] PlayerSeason)))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("tournaments" :> (Capture "idseason" Int :> Get '[JSON] PlayerSeason)))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("rating" :> Get '[JSON] [PlayerRating]))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("rating" :> ("last" :> Get '[JSON] PlayerRating)))) :<|> (("players" :> (Capture "idplayer" PlayerId :> ("rating" :> (Capture "idrelease" Int :> Get '[JSON] PlayerRating)))) :<|> (("teams" :> (QueryParam "page" Int :> Get '[JSON] (Items Team))) :<|> (("teams" :> (Capture "idteam" TeamId :> Get '[JSON] [Team])) :<|> (("teams" :> (Capture "idteam" TeamId :> ("recaps" :> Get '[JSON] (SeasonMap TeamBaseRecap)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("recaps" :> ("last" :> Get '[JSON] TeamBaseRecap)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("recaps" :> (Capture "idseason" Int :> Get '[JSON] TeamBaseRecap)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("tournaments" :> Get '[JSON] (SeasonMap TeamTournament)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("tournaments" :> ("last" :> Get '[JSON] TeamTournament)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("tournaments" :> (Capture "idseason" Int :> Get '[JSON] TeamTournament)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("rating" :> Get '[JSON] [TeamRating]))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("rating" :> ("a" :> Get '[JSON] TeamRating)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("rating" :> ("b" :> Get '[JSON] TeamRating)))) :<|> (("teams" :> (Capture "idteam" TeamId :> ("rating" :> (Capture "idrelease" Int :> Get '[JSON] TeamRating)))) :<|> (("tournaments" :> (QueryParam "page" Int :> Get '[JSON] (Items TournamentShort))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> Get '[JSON] [Tournament])) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("list" :> Get '[JSON] [TournamentResult]))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("list" :> ("town" :> (Capture "idtown" Int :> Get '[JSON] [TournamentResult]))))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("list" :> ("region" :> (Capture "idregion" Int :> Get '[JSON] [TournamentResult]))))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("list" :> ("country" :> (Capture "idcountry" Int :> Get '[JSON] [TournamentResult]))))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("recaps" :> Get '[JSON] [RecapTeam]))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("recaps" :> (Capture "idteam" TeamId :> Get '[JSON] [RecapPlayer])))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("results" :> (Capture "idteam" TeamId :> Get '[JSON] [TourResult])))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("controversials" :> Get '[JSON] [Controversial]))) :<|> (("tournaments" :> (Capture "idtournament" TournamentId :> ("appeals" :> Get '[JSON] [Appeal]))) :<|> (("teams" :> ("search" :> (QueryParam "name" Text :> (QueryParam "town" Text :> (QueryParam "region_name" Text :> (QueryParam "country_name" Text :> (QueryFlag "active_this_season" :> (QueryParam "page" Int :> Get '[JSON] (Items Team))))))))) :<|> (("players" :> ("search" :> (QueryParam "surname" Text :> (QueryParam "name" Text :> (QueryParam "patronymic" Text :> (QueryParam "page" Int :> Get '[JSON] (Items Player))))))) :<|> ("tournaments" :> ("search" :> (QueryParam "type_name" TournamentType :> (QueryParam "archive" Int :> (QueryParam "page" Int :> Get '[JSON] (Items TournamentShort))))))))))))))))))))))))))))))))))))))))) Source #

Тип, описывающий API сайта рейтинга. Функции, которые позволяют делать запросы к API, находятся в модуле RatingChgkInfo.Api

Некоторые замечания по общему дизайну API:

  • API NOTE: в запросах /players/:id, /tournaments/:id и некоторых других должен возвращаться единственный результат вместо списка из одного результата
  • API NOTE: в запросе /players/:id/teams и других запросах, возвращающие элементы по сезонам, следует возвращать список вместо отображения номера сезона на элемент (идентификатор сезона дублируется в самом элементе)
  • API NOTE: запросы, возвращающие элементы по сезонам, и запрос /tournaments/:tourn/results/:team устроены по-разному
  • API NOTE: запрос /teams/:id/rating/:formula, по-видимому, несколько сломан: для команды 1 он возвращает пустую строку (по состоянию на 2019-01-11)
  • API NOTE: запрос /players/:id/rating/last, по-видимому, нсколько сломан: для игрока 54345 он возвращает пустую строку (по состоянию на 2019-01-11)
  • API NOTE: запросы /tournament/:id/town/:town должны использовать QueryParam вместо параметров путей

Игрок

data Player Source #

Игрок

Constructors

Player 

Fields

  • idplayer :: PlayerId

    Идентификатор игрока. API NOTE: должен быть Int

  • surname :: Text

    Фамилия игрока

  • name :: Text

    Имя игрока (пустое, если нет имени)

  • patronymic :: Text

    Отчество игрока (пустое, если его нет)

  • db_chgk_info_tag :: Maybe Text

    Логин в Базе вопросов. Не возвращается в общем списке игроков, только при запросе отдельного игрока

Instances
Eq Player Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: Player -> Player -> Bool #

(/=) :: Player -> Player -> Bool #

Read Player Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Player Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic Player Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Player :: Type -> Type #

Methods

from :: Player -> Rep Player x #

to :: Rep Player x -> Player #

ToJSON Player Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON Player Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Player Source # 
Instance details

Defined in RatingChgkInfo.Types

data PlayerTeam Source #

Игрок в базовом составе команды

Constructors

PlayerTeam 

Fields

  • pt_idplayer :: PlayerId

    Идентификатор игрока. API NOTE: должен быть Int

  • pt_idteam :: TeamId

    Идентификатор команды. API NOTE: должен быть Int

  • pt_idseason :: Text

    Идентификатор сезона. API NOTE: должен быть Int

  • pt_is_captain :: Text

    Является ли игрок капитаном (0/1). API NOTE: должен быть Bool

  • pt_added_since :: Day

    С какого момента игрок в базовом составе

Instances
Eq PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Read PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Show PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep PlayerTeam :: Type -> Type #

ToJSON PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep PlayerTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

data PlayerSeason Source #

Турниры, сыгранные игроком в сезоне

Constructors

PlayerSeason 

Fields

Instances
Eq PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

Read PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

Show PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep PlayerSeason :: Type -> Type #

ToJSON PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep PlayerSeason Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep PlayerSeason = D1 (MetaData "PlayerSeason" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "PlayerSeason" PrefixI True) (S1 (MetaSel (Just "ps_idplayer") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PlayerId) :*: (S1 (MetaSel (Just "ps_idseason") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "ps_tournaments") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [PlayerTournament]))))

data PlayerTournament Source #

Турнир, сыгранный игроком

Constructors

PlayerTournament 

Fields

Instances
Eq PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Read PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Show PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep PlayerTournament :: Type -> Type #

ToJSON PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep PlayerTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep PlayerTournament = D1 (MetaData "PlayerTournament" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "PlayerTournament" PrefixI True) (S1 (MetaSel (Just "ptr_idtournament") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TournamentId) :*: (S1 (MetaSel (Just "ptr_idteam") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TeamId) :*: S1 (MetaSel (Just "ptr_in_base_team") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

data PlayerRating Source #

Рейтинг игрока

Constructors

PlayerRating 

Fields

Instances
Eq PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Read PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Show PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep PlayerRating :: Type -> Type #

ToJSON PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep PlayerRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Команда

data Team Source #

Команда

Constructors

Team 

Fields

Instances
Eq Team Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: Team -> Team -> Bool #

(/=) :: Team -> Team -> Bool #

Read Team Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Team Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

showsPrec :: Int -> Team -> ShowS #

show :: Team -> String #

showList :: [Team] -> ShowS #

Generic Team Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Team :: Type -> Type #

Methods

from :: Team -> Rep Team x #

to :: Rep Team x -> Team #

ToJSON Team Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON Team Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Team Source # 
Instance details

Defined in RatingChgkInfo.Types

data TeamBaseRecap Source #

Базовый состав команды

Constructors

TeamBaseRecap 

Fields

  • tbr_idteam :: TeamId

    Идентификатор команды. API NOTE: должен быть Int

  • tbr_idseason :: Text

    Идентификатор сезона. API NOTE: должен быть Int

  • tbr_players :: [Text]

    Список игроков (вместе с капитаном). TODO: должен быть Set Int

  • tbr_captain :: Text

    Капитан команды. API NOTE: должен быть Maybe Int

Instances
Eq TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TeamBaseRecap :: Type -> Type #

ToJSON TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TeamBaseRecap Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TeamBaseRecap = D1 (MetaData "TeamBaseRecap" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "TeamBaseRecap" PrefixI True) ((S1 (MetaSel (Just "tbr_idteam") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TeamId) :*: S1 (MetaSel (Just "tbr_idseason") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "tbr_players") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Just "tbr_captain") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

data TeamTournament Source #

Турниры, сыгранные командой в сезоне

Constructors

TeamTournament 

Fields

  • tt_idteam :: TeamId

    Идентификатор команды. API NOTE: должен быть Int

  • tt_idseason :: Text

    Идентификатор сезона. API NOTE: должен быть Int

  • tt_tournaments :: [Text]

    Список идентификаторов турниров. TODO: должен быть Set Int

Instances
Eq TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TeamTournament :: Type -> Type #

ToJSON TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TeamTournament Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TeamTournament = D1 (MetaData "TeamTournament" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "TeamTournament" PrefixI True) (S1 (MetaSel (Just "tt_idteam") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TeamId) :*: (S1 (MetaSel (Just "tt_idseason") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "tt_tournaments") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Text]))))

data TeamRating Source #

Рейтинг команды

Constructors

TeamRating 

Fields

  • rat_idteam :: TeamId

    Идентификатор команды. API NOTE: должен быть Int

  • rat_idrelease :: Text

    Идентификатор релиза. API NOTE: должен быть Int

  • rat_rating :: Text

    Рейтинг команды. API NOTE: должен быть Int

  • rat_rating_position :: Text

    Позиция в рейтинге. API NOTE: должен быть Int или Rational

  • rat_date :: Text

    Дата, на которую рассчитан рейтинг. API NOTE: должен быть Day (например, teams1/rating возвращает пустую строку для релиза 26; причём teams1rating26 возвращает пустой ответ)

  • rat_formula :: RatingFormula

    Формула подсчёта рейтинга

Instances
Eq TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TeamRating :: Type -> Type #

ToJSON TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TeamRating Source # 
Instance details

Defined in RatingChgkInfo.Types

Турнир

Общая информация о турнире

data TournamentShort Source #

Короткая информация о турнире (в списке турниров)

Constructors

TournamentShort 

Fields

  • trs_idtournament :: TournamentId

    Идентификатор турнира. API NOTE: должен быть Int

  • trs_name :: Text

    Название турнира

  • trs_dateStart :: LocalTime

    Дата начала турнира (в часовом поясе МСК)

  • trs_dateEnd :: LocalTime

    Дата окончания турнира (в часовом поясе МСК)

  • trs_typeName :: TournamentType

    Тип турнира

  • trs_archive :: Text

    Архивирован ли турнир (0 - нет, 1 - да, пустая строка - турнир слишком давний). API NOTE: должен быть Bool

    Since: 0.3.6.4

  • trs_dateArchivedAt :: Day

    Дата занесения в архив (может быть пустая строка). API NOTE: должен быть Maybe UTCTime

    Since: 0.3.6.4

Instances
Eq TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TournamentShort :: Type -> Type #

ToJSON TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TournamentShort Source # 
Instance details

Defined in RatingChgkInfo.Types

data Tournament Source #

Полная информация о турнире (по отдельному запросу)

Тип Tournament можно было бы объединить с TournamentShort, однако, в этом случае бóльшая часть полей имела бы тип Maybe x, что подразумевало бы другой смысл, с менее строгой проверкой типов (некоторые поля могут быть установлены, а некоторые нет). Поэтому было решено разделить эти два типа.

Сконвертировать Tournament в TournamentShort можно при помощи функции tournamentToShort.

В отличие от Tournament в типах Player и Team есть единственное поле, которое устанавливается в запросе более полной информации, поэтому эти типы не разделены на два.

Constructors

Tournament 

Fields

Instances
Eq Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Read Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Tournament :: Type -> Type #

ToJSON Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Tournament Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Tournament = D1 (MetaData "Tournament" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "Tournament" PrefixI True) ((((S1 (MetaSel (Just "trn_idtournament") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TournamentId) :*: S1 (MetaSel (Just "trn_name") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "trn_town") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "trn_longName") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "trn_dateStart") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 LocalTime)))) :*: ((S1 (MetaSel (Just "trn_dateEnd") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 LocalTime) :*: (S1 (MetaSel (Just "trn_tournamentInRating") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "trn_tourCount") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))) :*: (S1 (MetaSel (Just "trn_tourQuestions") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "trn_tourQuestPerTour") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "trn_questionsTotal") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))) :*: (((S1 (MetaSel (Just "trn_typeName") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TournamentType) :*: S1 (MetaSel (Just "trn_mainPaymentValue") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "trn_mainPaymentCurrency") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "trn_discountedPaymentValue") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "trn_discountedPaymentCurrency") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)))) :*: ((S1 (MetaSel (Just "trn_discountedPaymentReason") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "trn_dateRequestsAllowedTo") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "trn_comment") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))) :*: (S1 (MetaSel (Just "trn_siteUrl") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "trn_archive") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "trn_dateArchivedAt") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Day)))))))

tournamentToShort :: Tournament -> TournamentShort Source #

Преобразует Tournament в TournamentShort, убирая лишние поля

Составы

data RecapTeam Source #

Состав команды на турнире

Constructors

RecapTeam 

Fields

Instances
Eq RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Read RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Show RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep RecapTeam :: Type -> Type #

ToJSON RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep RecapTeam Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep RecapTeam = D1 (MetaData "RecapTeam" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "RecapTeam" PrefixI True) (S1 (MetaSel (Just "rt_idteam") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TeamId) :*: S1 (MetaSel (Just "rt_recaps") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [RecapPlayer])))

data RecapPlayer Source #

Информация об игроке в составе команды на турнире

API NOTE. Так как игрок не может быть одновременно в базовом составе и легионером, нужно заменить эти два поля одним, либо описать, когда игрок может не быть ни базовым, ни легионером

Constructors

RecapPlayer 

Fields

  • rp_idplayer :: PlayerId

    Идентификатор игрока. API NOTE: должен быть Int

  • rp_is_captain :: Text

    Является ли игрок капитаном (К). API NOTE: должен быть Bool

  • rp_is_base :: Text

    Находится ли игрок в базовом составе (Б). API NOTE: должен быть Bool

  • rp_is_foreign :: Text

    Является ли игрок легионером (Л). API NOTE: должен быть Bool

Instances
Eq RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

Read RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

Show RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep RecapPlayer :: Type -> Type #

ToJSON RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep RecapPlayer Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep RecapPlayer = D1 (MetaData "RecapPlayer" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "RecapPlayer" PrefixI True) ((S1 (MetaSel (Just "rp_idplayer") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 PlayerId) :*: S1 (MetaSel (Just "rp_is_captain") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "rp_is_base") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "rp_is_foreign") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text))))

Результаты

data TournamentResult Source #

Результаты турнира для команды

Constructors

TournamentResult 

Fields

  • tr_idteam :: TeamId

    Идентификатор команды. API NOTE: должен быть Int

  • tr_current_name :: Text

    Название команды на турнире. Может совпадать с основным названием. Если название разовое, отличается от основного названия

  • tr_base_name :: Text

    Основное название команды.

  • tr_position :: Text

    Положение в турнирной таблице. API NOTE: должен быть Int or Rational

  • tr_questions_total :: Text

    Общее количество взятых вопросов. API NOTE: должен быть Int

  • tr_mask :: Text

    Расплюсовка команды (строка, где на каждый вопрос турнира указано: 0 - не взят; 1 - взят; X - вопрос снят). API NOTE: должен быть [Bool] or [Answer]

  • tr_tech_rating :: Text

    Технический рейтинг команды. API NOTE: должен быть Int

  • tr_predicted_position :: Text

    Предсказанное положение в турнирной таблице. API NOTE: должен быть Int or Rational

  • tr_bonus_a :: Text

    Бонус по формуле А (аддитивной). API NOTE: должен быть Int

  • tr_bonus_b :: Text

    Бонус по формуле Б (балансной). API NOTE: должен быть Int

  • tr_diff_bonus :: Text

    Разностный балл D. API NOTE: должен быть Int

  • tr_included_in_rating :: Text

    Результаты команды будут учтены в релизе. API NOTE: должен быть Bool

Instances
Eq TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TournamentResult :: Type -> Type #

ToJSON TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TournamentResult Source # 
Instance details

Defined in RatingChgkInfo.Types

data TourResult Source #

Результаты команды по турам

Constructors

TourResult 

Fields

  • tor_tour :: Text

    Номер тура. API NOTE: должен быть Int

  • tor_mask :: [Text]

    Расплюсовка команды (количество элементов списка совпадает с количеством вопросов в туре; каждый элемент списка либо 0 - не взят, либо 1 - взят, либо X - вопрос снят). API NOTE: должен быть [Int] or [Answer]

Instances
Eq TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TourResult :: Type -> Type #

ToJSON TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TourResult Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TourResult = D1 (MetaData "TourResult" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "TourResult" PrefixI True) (S1 (MetaSel (Just "tor_tour") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "tor_mask") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [Text])))

Спорные и апелляции

data Controversial Source #

Спорный

Constructors

Controversial 

Fields

Instances
Eq Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

Read Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Controversial :: Type -> Type #

ToJSON Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Controversial Source # 
Instance details

Defined in RatingChgkInfo.Types

data Appeal Source #

Апелляция

Constructors

Appeal 

Fields

  • appType :: AppealType

    Тип апелляции

  • appQuestionNumber :: Text

    Номер вопроса

  • appIssuedAt :: LocalTime

    Время создания. API NOTE: должен быть UTCTime

  • appStatus :: ClaimStatus

    Статус апелляции. Статус может быть "новая" и в том случае, если апелляция не рассмотрена, так как была зачтена другая апелляция

  • appAppeal :: Text

    Текст апелляции

  • appComment :: Text

    Вердикт АЖ

  • appResolvedAt :: Text

    Время публикации вердикта. API NOTE: должен быть UTCTime

  • appAnswer :: Text

    Ответ команды

Instances
Eq Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: Appeal -> Appeal -> Bool #

(/=) :: Appeal -> Appeal -> Bool #

Read Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Appeal :: Type -> Type #

Methods

from :: Appeal -> Rep Appeal x #

to :: Rep Appeal x -> Appeal #

ToJSON Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Appeal Source # 
Instance details

Defined in RatingChgkInfo.Types

Типы-перечисления

data RatingFormula Source #

Формула рейтинга

Constructors

FormulaA

Рейтинг А (аддитивный)

FormulaB

Рейтинг Б (балансный)

Instances
Eq RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

Read RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

Show RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep RatingFormula :: Type -> Type #

ToJSON RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep RatingFormula Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep RatingFormula = D1 (MetaData "RatingFormula" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "FormulaA" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FormulaB" PrefixI False) (U1 :: Type -> Type))

data TournamentType Source #

Тип турнира

API NOTE: типа "" (пустая строка) быть не должно. На данный момент (2019-01-13) таких турниров три: 2864, 2937, 2995. Типа Неизвестный тоже быть не должно. Такой один: 2186

Constructors

Synchronous

Синхрон

StrictlySynchronous

Строго синхронный

Asynchronous

Асинхрон

Casual

Обычный

Regional

Региональный

Marathon

Марафон

TotalScore

Общий зачёт

TypeUnknown

Неизвестный

TypeEmpty

(пустая строка)

Instances
Eq TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TournamentType :: Type -> Type #

ToJSON TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

ToHttpApiData TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TournamentType Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TournamentType = D1 (MetaData "TournamentType" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (((C1 (MetaCons "Synchronous" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StrictlySynchronous" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Asynchronous" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Casual" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Regional" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Marathon" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "TotalScore" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TypeUnknown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TypeEmpty" PrefixI False) (U1 :: Type -> Type)))))

data ClaimStatus Source #

Статус спорного или апелляции

Constructors

ClaimNew

Новый (N)

ClaimAccepted

Принят (A)

ClaimRejected

Отклонён (D)

Instances
Eq ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

Read ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

Show ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep ClaimStatus :: Type -> Type #

ToJSON ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep ClaimStatus Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep ClaimStatus = D1 (MetaData "ClaimStatus" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "ClaimNew" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ClaimAccepted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ClaimRejected" PrefixI False) (U1 :: Type -> Type)))

data AppealType Source #

Вид апелляции

Constructors

AppealApprove

Апелляция на зачёт ответа (A)

AppealRemove

Апелляция на снятие вопроса (R)

AppealNarrator

Апелляция на снятие из-за ошибки ведущего (N)

Instances
Eq AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

Read AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

Show AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep AppealType :: Type -> Type #

ToJSON AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

FromJSON AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep AppealType Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep AppealType = D1 (MetaData "AppealType" "RatingChgkInfo.Types" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" False) (C1 (MetaCons "AppealApprove" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AppealRemove" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AppealNarrator" PrefixI False) (U1 :: Type -> Type)))

Типы для идентификаторов

Экспортируются без функций, позволяющих вытащить данные из типа, поскольку предполагается, что идентификаторы получаются только из запросов к серверу. Это должно помочь избежать ошибок, когда идентификатор одного типа (например, id игрока) ошибочно передаётся туда, где ожидается идентификатор другого типа (например, id турнира). Если вам совершенно точно без этого не обойтись, используйте модуль RatingChgkInfo.Types.Unsafe.

data PlayerId Source #

Идентификатор игрока. В API на самом деле возвращается строка, но во всех функциях работы с игроками используется этот тип. Чтобы получить значение этого типа следует получить данные из API

Instances
Eq PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Read PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Show PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Generic PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Associated Types

type Rep PlayerId :: Type -> Type #

Methods

from :: PlayerId -> Rep PlayerId x #

to :: Rep PlayerId x -> PlayerId #

ToJSON PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

FromJSON PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToHttpApiData PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

FromHttpApiData PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToSchema PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToParamSchema PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Methods

toParamSchema :: proxy PlayerId -> ParamSchema t #

type Rep PlayerId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

type Rep PlayerId = D1 (MetaData "PlayerId" "RatingChgkInfo.Types.Unsafe" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" True) (C1 (MetaCons "PlayerId" PrefixI True) (S1 (MetaSel (Just "unPlayerId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data TeamId Source #

Идентификатор команды. В API на самом деле возвращается строка, но во всех функциях работы с командами используется этот тип. Чтобы получить значение этого типа следует получить данные из API

Instances
Eq TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Methods

(==) :: TeamId -> TeamId -> Bool #

(/=) :: TeamId -> TeamId -> Bool #

Read TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Show TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Generic TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Associated Types

type Rep TeamId :: Type -> Type #

Methods

from :: TeamId -> Rep TeamId x #

to :: Rep TeamId x -> TeamId #

ToJSON TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

FromJSON TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToHttpApiData TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

FromHttpApiData TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToSchema TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToParamSchema TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Methods

toParamSchema :: proxy TeamId -> ParamSchema t #

type Rep TeamId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

type Rep TeamId = D1 (MetaData "TeamId" "RatingChgkInfo.Types.Unsafe" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" True) (C1 (MetaCons "TeamId" PrefixI True) (S1 (MetaSel (Just "unTeamId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data TournamentId Source #

Идентификатор турнира. В API на самом деле возвращается строка, но во всех функциях работы с турнирами используется этот тип. Чтобы получить значение этого типа следует получить данные из API

Instances
Eq TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Read TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Show TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Generic TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

Associated Types

type Rep TournamentId :: Type -> Type #

ToJSON TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

FromJSON TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToHttpApiData TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

FromHttpApiData TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToSchema TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

ToParamSchema TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

type Rep TournamentId Source # 
Instance details

Defined in RatingChgkInfo.Types.Unsafe

type Rep TournamentId = D1 (MetaData "TournamentId" "RatingChgkInfo.Types.Unsafe" "rating-chgk-info-0.3.6.4-Fp762Pc22xKKduMxsaB6eL" True) (C1 (MetaCons "TournamentId" PrefixI True) (S1 (MetaSel (Just "unTournamentId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Работа без API

В этом разделе - типы, которые используются при запросах к CSV-таблицам на сайте рейтинга для функциональности, которая (надеюсь, пока) не предоставляется через REST API

Функции для работы с этими типами находятся в модуле RatingChgkInfo.NoApi

  • * Заявки на турниры

data Request Source #

Заявка на проведение

Constructors

Request 

Fields

Instances
Eq Request Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: Request -> Request -> Bool #

(/=) :: Request -> Request -> Bool #

Read Request Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Request Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic Request Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Request :: Type -> Type #

Methods

from :: Request -> Rep Request x #

to :: Rep Request x -> Request #

ToJSON Request Source # 
Instance details

Defined in RatingChgkInfo.Types

ToSchema Request Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Request Source # 
Instance details

Defined in RatingChgkInfo.Types

data TeamName Source #

Название команды на турнире

Constructors

TeamName 

Fields

  • tnTeamId :: Int

    Идентификатор команды

  • tnCurrentName :: Text

    Название на турнире (может совпадать с основным)

  • tnCurrentTown :: Text

    Город приписки на турнире (может совпадать с основным)

  • tnBaseName :: Text

    Основное название

  • tnBaseTown :: Text

    Основной город прописки

Instances
Eq TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

Read TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

Show TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep TeamName :: Type -> Type #

Methods

from :: TeamName -> Rep TeamName x #

to :: Rep TeamName x -> TeamName #

ToJSON TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

ToSchema TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep TeamName Source # 
Instance details

Defined in RatingChgkInfo.Types

География

data Town Source #

Город

Constructors

Town 

Fields

Instances
Eq Town Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

(==) :: Town -> Town -> Bool #

(/=) :: Town -> Town -> Bool #

Read Town Source # 
Instance details

Defined in RatingChgkInfo.Types

Show Town Source # 
Instance details

Defined in RatingChgkInfo.Types

Methods

showsPrec :: Int -> Town -> ShowS #

show :: Town -> String #

showList :: [Town] -> ShowS #

Generic Town Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep Town :: Type -> Type #

Methods

from :: Town -> Rep Town x #

to :: Rep Town x -> Town #

ToJSON Town Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Town Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep Town

Синхроны в городе

data SynchTown Source #

Синхрон, проводимый в городе

Constructors

SynchTown 

Fields

Instances
Eq SynchTown Source # 
Instance details

Defined in RatingChgkInfo.Types

Read SynchTown Source # 
Instance details

Defined in RatingChgkInfo.Types

Show SynchTown Source # 
Instance details

Defined in RatingChgkInfo.Types

Generic SynchTown Source # 
Instance details

Defined in RatingChgkInfo.Types

Associated Types

type Rep SynchTown :: Type -> Type #

ToJSON SynchTown Source # 
Instance details

Defined in RatingChgkInfo.Types

type Rep SynchTown Source # 
Instance details

Defined in RatingChgkInfo.Types