License | MIT |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
BattlePlace.WebApi
Description
Documentation
type WebApi = "v1a" :> (("client" :> (("auth" :> (ReqBody '[JSON] ClientAuthRequest :> Post '[JSON] ClientAuthResponse)) :<|> (("match" :> ((AuthProtect ClientToken :> (ReqBody '[JSON] MatchRequest :> Post '[JSON] MatchResponse)) :<|> ((AuthProtect ClientToken :> (Capture "matchToken" (InternalToken MatchToken) :> Get '[JSON] MatchStatusResponse)) :<|> (AuthProtect ClientToken :> (Capture "matchToken" (InternalToken MatchToken) :> Delete '[JSON] MatchCancelResponse))))) :<|> (("session" :> (Capture "sessionToken" (InternalToken SessionToken) :> ("result" :> (AuthProtect ClientToken :> (ReqBody '[JSON] SessionResultRequest :> Post '[JSON] ()))))) :<|> ("info" :> ("stats" :> (AuthProtect ClientToken :> Get '[JSON] UserStats))))))) :<|> ("server" :> (("match" :> (ReqBody '[JSON] ServerMatchRequest :> Post '[JSON] ServerMatchResponse)) :<|> ("session" :> (Capture "serverSessionToken" (InternalToken ServerSessionToken) :> ("result" :> (ReqBody '[JSON] ServerSessionResultRequest :> Post '[JSON] ()))))))) Source #
data ClientAuthRequest Source #
Constructors
ClientAuthRequest | |
Fields |
Instances
data ClientAuthResponse Source #
Constructors
ClientAuthResponse_authenticated | |
ClientAuthResponse_notAuthenticated | |
Fields |
Instances
data MatchRequest Source #
Constructors
MatchRequest | |
Fields |
Instances
data MatchResponse Source #
Constructors
MatchResponse | |
Fields |
Instances
Generic MatchResponse Source # | |
Defined in BattlePlace.WebApi Associated Types type Rep MatchResponse :: * -> * # | |
ToJSON MatchResponse Source # | |
Defined in BattlePlace.WebApi Methods toJSON :: MatchResponse -> Value # toEncoding :: MatchResponse -> Encoding # toJSONList :: [MatchResponse] -> Value # toEncodingList :: [MatchResponse] -> Encoding # | |
FromJSON MatchResponse Source # | |
Defined in BattlePlace.WebApi Methods parseJSON :: Value -> Parser MatchResponse # parseJSONList :: Value -> Parser [MatchResponse] # | |
type Rep MatchResponse Source # | |
Defined in BattlePlace.WebApi type Rep MatchResponse = D1 (MetaData "MatchResponse" "BattlePlace.WebApi" "battleplace-0.1.0.6-EVfBQWt7RHd8mmLWazZmlN" False) (C1 (MetaCons "MatchResponse" PrefixI True) (S1 (MetaSel (Just "matchResponse_matchToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (InternalToken MatchToken)))) |
data MatchStatusResponse Source #
Constructors
MatchStatusResponse_notFound | |
MatchStatusResponse_inProgress | |
MatchStatusResponse_matched | |
MatchStatusResponse_failed | |
Fields | |
MatchStatusResponse_cleaned | Match status was cleaned. Normallly this status should not be visible to clients, it's here just in case. |
Instances
data MatchCancelResponse Source #
Instances
Generic MatchCancelResponse Source # | |
Defined in BattlePlace.WebApi Associated Types type Rep MatchCancelResponse :: * -> * # Methods from :: MatchCancelResponse -> Rep MatchCancelResponse x # to :: Rep MatchCancelResponse x -> MatchCancelResponse # | |
ToJSON MatchCancelResponse Source # | |
Defined in BattlePlace.WebApi Methods toJSON :: MatchCancelResponse -> Value # toEncoding :: MatchCancelResponse -> Encoding # toJSONList :: [MatchCancelResponse] -> Value # toEncodingList :: [MatchCancelResponse] -> Encoding # | |
FromJSON MatchCancelResponse Source # | |
Defined in BattlePlace.WebApi Methods parseJSON :: Value -> Parser MatchCancelResponse # parseJSONList :: Value -> Parser [MatchCancelResponse] # | |
type Rep MatchCancelResponse Source # | |
Defined in BattlePlace.WebApi |
Constructors
MatchTeam (Vector MatchPlayer) |
data MatchPlayer Source #
Constructors
MatchPlayer | |
Fields |
Instances
Generic MatchPlayer Source # | |
Defined in BattlePlace.WebApi Associated Types type Rep MatchPlayer :: * -> * # | |
ToJSON MatchPlayer Source # | |
Defined in BattlePlace.WebApi Methods toJSON :: MatchPlayer -> Value # toEncoding :: MatchPlayer -> Encoding # toJSONList :: [MatchPlayer] -> Value # toEncodingList :: [MatchPlayer] -> Encoding # | |
FromJSON MatchPlayer Source # | |
Defined in BattlePlace.WebApi | |
type Rep MatchPlayer Source # | |
Defined in BattlePlace.WebApi type Rep MatchPlayer = D1 (MetaData "MatchPlayer" "BattlePlace.WebApi" "battleplace-0.1.0.6-EVfBQWt7RHd8mmLWazZmlN" False) (C1 (MetaCons "MatchPlayer" PrefixI True) (S1 (MetaSel (Just "matchPlayer_info") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MatchPlayerInfo) :*: (S1 (MetaSel (Just "matchPlayer_ourTicket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Ticket)) :*: S1 (MetaSel (Just "matchPlayer_theirTicket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Ticket))))) |
data MatchServer Source #
Constructors
MatchServer | |
Fields |
Instances
Generic MatchServer Source # | |
Defined in BattlePlace.WebApi Associated Types type Rep MatchServer :: * -> * # | |
ToJSON MatchServer Source # | |
Defined in BattlePlace.WebApi Methods toJSON :: MatchServer -> Value # toEncoding :: MatchServer -> Encoding # toJSONList :: [MatchServer] -> Value # toEncodingList :: [MatchServer] -> Encoding # | |
FromJSON MatchServer Source # | |
Defined in BattlePlace.WebApi | |
type Rep MatchServer Source # | |
Defined in BattlePlace.WebApi type Rep MatchServer = D1 (MetaData "MatchServer" "BattlePlace.WebApi" "battleplace-0.1.0.6-EVfBQWt7RHd8mmLWazZmlN" False) (C1 (MetaCons "MatchServer" PrefixI True) (S1 (MetaSel (Just "matchServer_info") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MatchServerInfo) :*: (S1 (MetaSel (Just "matchServer_ourTicket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Ticket) :*: S1 (MetaSel (Just "matchServer_theirTicket") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Ticket)))) |
data SessionResultRequest Source #
Constructors
SessionResultRequest_finished | |
Fields | |
SessionResultRequest_cancelled |
Instances
data ServerMatchRequest Source #
Constructors
Instances
data ServerMatchResponse Source #
Constructors
ServerMatchResponse | |
Fields |
Instances
data ServerSessionResultRequest Source #
Constructors
ServerSessionResultRequest_finished | |
Fields | |
ServerSessionResultRequest_cancelled |
Instances
data ServerSession Source #
Constructors
ServerSession | |