battleplace-0.1.0.1: Core definitions for BattlePlace.io service

LicenseMIT
Safe HaskellNone
LanguageHaskell2010

BattlePlace.WebApi.Types

Description

 

Synopsis

Documentation

data Auth Source #

Instances

Generic Auth Source # 

Associated Types

type Rep Auth :: * -> * #

Methods

from :: Auth -> Rep Auth x #

to :: Rep Auth x -> Auth #

ToJSON Auth Source # 
FromJSON Auth Source # 
type Rep Auth Source # 
type Rep Auth = D1 * (MetaData "Auth" "BattlePlace.WebApi.Types" "battleplace-0.1.0.1-IU8z1o2jI2JOUpufR5zBo" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Auth_itchJwtToken" PrefixI True) (S1 * (MetaSel (Just Symbol "auth_itchJwtToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "Auth_itchApiKey" PrefixI True) (S1 * (MetaSel (Just Symbol "auth_itchApiKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:+:) * (C1 * (MetaCons "Auth_steamEncryptedTicket" PrefixI True) (S1 * (MetaSel (Just Symbol "auth_steamEncryptedTicket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) (C1 * (MetaCons "Auth_testKey" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "auth_testKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "auth_testId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * StrWord64))))))

data AuthType Source #

Auth type (for logging).

Instances

Eq AuthType Source # 
Generic AuthType Source # 

Associated Types

type Rep AuthType :: * -> * #

Methods

from :: AuthType -> Rep AuthType x #

to :: Rep AuthType x -> AuthType #

Hashable AuthType Source # 

Methods

hashWithSalt :: Int -> AuthType -> Int #

hash :: AuthType -> Int #

ToJSON AuthType Source # 
FromJSON AuthType Source # 
type Rep AuthType Source # 
type Rep AuthType = D1 * (MetaData "AuthType" "BattlePlace.WebApi.Types" "battleplace-0.1.0.1-IU8z1o2jI2JOUpufR5zBo" False) ((:+:) * ((:+:) * (C1 * (MetaCons "AuthType_itchJwtToken" PrefixI False) (U1 *)) (C1 * (MetaCons "AuthType_itchApiKey" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "AuthType_steamEncryptedTicket" PrefixI False) (U1 *)) (C1 * (MetaCons "AuthType_testKey" PrefixI False) (U1 *))))

data Client Source #

Instances

Eq Client Source # 

Methods

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

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

Generic Client Source # 

Associated Types

type Rep Client :: * -> * #

Methods

from :: Client -> Rep Client x #

to :: Rep Client x -> Client #

Hashable Client Source # 

Methods

hashWithSalt :: Int -> Client -> Int #

hash :: Client -> Int #

ToJSON Client Source # 
FromJSON Client Source # 
type Rep Client Source # 
type Rep Client = D1 * (MetaData "Client" "BattlePlace.WebApi.Types" "battleplace-0.1.0.1-IU8z1o2jI2JOUpufR5zBo" False) ((:+:) * (C1 * (MetaCons "Client_itch" PrefixI True) (S1 * (MetaSel (Just Symbol "client_itchUserId") SourceUnpack SourceStrict DecidedStrict) (Rec0 * StrWord64))) ((:+:) * (C1 * (MetaCons "Client_steam" PrefixI True) (S1 * (MetaSel (Just Symbol "client_steamId") SourceUnpack SourceStrict DecidedStrict) (Rec0 * StrWord64))) (C1 * (MetaCons "Client_test" PrefixI True) (S1 * (MetaSel (Just Symbol "client_testId") SourceUnpack SourceStrict DecidedStrict) (Rec0 * StrWord64)))))

data ClientType Source #

Type of the client. Must correspont to JSON field "type" of Client.

Instances

Eq ClientType Source # 
Generic ClientType Source # 

Associated Types

type Rep ClientType :: * -> * #

Hashable ClientType Source # 
ToJSON ClientType Source # 
FromJSON ClientType Source # 
type Rep ClientType Source # 
type Rep ClientType = D1 * (MetaData "ClientType" "BattlePlace.WebApi.Types" "battleplace-0.1.0.1-IU8z1o2jI2JOUpufR5zBo" False) ((:+:) * (C1 * (MetaCons "ClientType_itch" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ClientType_steam" PrefixI False) (U1 *)) (C1 * (MetaCons "ClientType_test" PrefixI False) (U1 *))))

type MatchTeamSize = Int Source #

Size of a team in match request.

data MatchToken Source #

Match token.

Instances

Generic MatchToken Source # 

Associated Types

type Rep MatchToken :: * -> * #

ToJSON MatchToken Source # 
FromJSON MatchToken Source # 
type Rep MatchToken Source # 
type Rep MatchToken = D1 * (MetaData "MatchToken" "BattlePlace.WebApi.Types" "battleplace-0.1.0.1-IU8z1o2jI2JOUpufR5zBo" False) (C1 * (MetaCons "MatchToken" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "matchToken_projectId") SourceUnpack SourceStrict DecidedStrict) (Rec0 * ProjectId)) (S1 * (MetaSel (Just Symbol "matchToken_client") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Client))))

data Identified i a Source #

Generic data type for id + object.

Constructors

Identified 

Fields

Instances

Generic (Identified i a) Source # 

Associated Types

type Rep (Identified i a) :: * -> * #

Methods

from :: Identified i a -> Rep (Identified i a) x #

to :: Rep (Identified i a) x -> Identified i a #

(ToJSON i, ToJSON a) => ToJSON (Identified i a) Source # 
(FromJSON i, FromJSON a) => FromJSON (Identified i a) Source # 
type Rep (Identified i a) Source # 
type Rep (Identified i a) = D1 * (MetaData "Identified" "BattlePlace.WebApi.Types" "battleplace-0.1.0.1-IU8z1o2jI2JOUpufR5zBo" False) (C1 * (MetaCons "Identified" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "identified_id") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * i)) (S1 * (MetaSel (Just Symbol "identified_info") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))))

newtype Base64ByteString Source #

ByteString which serializes to JSON as base64 string.

Instances

Eq Base64ByteString Source # 
Ord Base64ByteString Source # 
Monoid Base64ByteString Source # 
Hashable Base64ByteString Source # 
ToJSON Base64ByteString Source # 
FromJSON Base64ByteString Source # 
ByteArrayAccess Base64ByteString Source # 
ByteArray Base64ByteString Source # 

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Base64ByteString) #

newtype Base64Word64 Source #

Word64 which serializes to JSON as base64 string. Useful because 64-bit integer is not representable in javascript.

Constructors

Base64Word64 Word64 

Instances

Eq Base64Word64 Source # 
Num Base64Word64 Source # 
Ord Base64Word64 Source # 
Read Base64Word64 Source # 
Show Base64Word64 Source # 
IsString Base64Word64 Source # 
Hashable Base64Word64 Source # 
ToJSON Base64Word64 Source # 
ToJSONKey Base64Word64 Source # 
FromJSON Base64Word64 Source # 
FromJSONKey Base64Word64 Source # 
Storable Base64Word64 Source # 
Serialize Base64Word64 Source # 
FromHttpApiData Base64Word64 Source # 

newtype StrWord64 Source #

Word64 which serializes to JSON as decimal string. Useful because 64-bit integer is not representable in javascript.

Constructors

StrWord64 Word64 

Instances

Eq StrWord64 Source # 
Num StrWord64 Source # 
Ord StrWord64 Source # 
Read StrWord64 Source # 
Show StrWord64 Source # 
Hashable StrWord64 Source # 
ToJSON StrWord64 Source # 
FromJSON StrWord64 Source # 
Storable StrWord64 Source # 
Serialize StrWord64 Source # 
FromHttpApiData StrWord64 Source #