{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.GameLift.AcceptMatch
(
AcceptMatch (..),
newAcceptMatch,
acceptMatch_ticketId,
acceptMatch_playerIds,
acceptMatch_acceptanceType,
AcceptMatchResponse (..),
newAcceptMatchResponse,
acceptMatchResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GameLift.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data AcceptMatch = AcceptMatch'
{
AcceptMatch -> Text
ticketId :: Prelude.Text,
AcceptMatch -> [Text]
playerIds :: [Prelude.Text],
AcceptMatch -> AcceptanceType
acceptanceType :: AcceptanceType
}
deriving (AcceptMatch -> AcceptMatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptMatch -> AcceptMatch -> Bool
$c/= :: AcceptMatch -> AcceptMatch -> Bool
== :: AcceptMatch -> AcceptMatch -> Bool
$c== :: AcceptMatch -> AcceptMatch -> Bool
Prelude.Eq, ReadPrec [AcceptMatch]
ReadPrec AcceptMatch
Int -> ReadS AcceptMatch
ReadS [AcceptMatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AcceptMatch]
$creadListPrec :: ReadPrec [AcceptMatch]
readPrec :: ReadPrec AcceptMatch
$creadPrec :: ReadPrec AcceptMatch
readList :: ReadS [AcceptMatch]
$creadList :: ReadS [AcceptMatch]
readsPrec :: Int -> ReadS AcceptMatch
$creadsPrec :: Int -> ReadS AcceptMatch
Prelude.Read, Int -> AcceptMatch -> ShowS
[AcceptMatch] -> ShowS
AcceptMatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptMatch] -> ShowS
$cshowList :: [AcceptMatch] -> ShowS
show :: AcceptMatch -> String
$cshow :: AcceptMatch -> String
showsPrec :: Int -> AcceptMatch -> ShowS
$cshowsPrec :: Int -> AcceptMatch -> ShowS
Prelude.Show, forall x. Rep AcceptMatch x -> AcceptMatch
forall x. AcceptMatch -> Rep AcceptMatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AcceptMatch x -> AcceptMatch
$cfrom :: forall x. AcceptMatch -> Rep AcceptMatch x
Prelude.Generic)
newAcceptMatch ::
Prelude.Text ->
AcceptanceType ->
AcceptMatch
newAcceptMatch :: Text -> AcceptanceType -> AcceptMatch
newAcceptMatch Text
pTicketId_ AcceptanceType
pAcceptanceType_ =
AcceptMatch'
{ $sel:ticketId:AcceptMatch' :: Text
ticketId = Text
pTicketId_,
$sel:playerIds:AcceptMatch' :: [Text]
playerIds = forall a. Monoid a => a
Prelude.mempty,
$sel:acceptanceType:AcceptMatch' :: AcceptanceType
acceptanceType = AcceptanceType
pAcceptanceType_
}
acceptMatch_ticketId :: Lens.Lens' AcceptMatch Prelude.Text
acceptMatch_ticketId :: Lens' AcceptMatch Text
acceptMatch_ticketId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptMatch' {Text
ticketId :: Text
$sel:ticketId:AcceptMatch' :: AcceptMatch -> Text
ticketId} -> Text
ticketId) (\s :: AcceptMatch
s@AcceptMatch' {} Text
a -> AcceptMatch
s {$sel:ticketId:AcceptMatch' :: Text
ticketId = Text
a} :: AcceptMatch)
acceptMatch_playerIds :: Lens.Lens' AcceptMatch [Prelude.Text]
acceptMatch_playerIds :: Lens' AcceptMatch [Text]
acceptMatch_playerIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptMatch' {[Text]
playerIds :: [Text]
$sel:playerIds:AcceptMatch' :: AcceptMatch -> [Text]
playerIds} -> [Text]
playerIds) (\s :: AcceptMatch
s@AcceptMatch' {} [Text]
a -> AcceptMatch
s {$sel:playerIds:AcceptMatch' :: [Text]
playerIds = [Text]
a} :: AcceptMatch) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
acceptMatch_acceptanceType :: Lens.Lens' AcceptMatch AcceptanceType
acceptMatch_acceptanceType :: Lens' AcceptMatch AcceptanceType
acceptMatch_acceptanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptMatch' {AcceptanceType
acceptanceType :: AcceptanceType
$sel:acceptanceType:AcceptMatch' :: AcceptMatch -> AcceptanceType
acceptanceType} -> AcceptanceType
acceptanceType) (\s :: AcceptMatch
s@AcceptMatch' {} AcceptanceType
a -> AcceptMatch
s {$sel:acceptanceType:AcceptMatch' :: AcceptanceType
acceptanceType = AcceptanceType
a} :: AcceptMatch)
instance Core.AWSRequest AcceptMatch where
type AWSResponse AcceptMatch = AcceptMatchResponse
request :: (Service -> Service) -> AcceptMatch -> Request AcceptMatch
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AcceptMatch
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AcceptMatch)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
( \Int
s ResponseHeaders
h ()
x ->
Int -> AcceptMatchResponse
AcceptMatchResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable AcceptMatch where
hashWithSalt :: Int -> AcceptMatch -> Int
hashWithSalt Int
_salt AcceptMatch' {[Text]
Text
AcceptanceType
acceptanceType :: AcceptanceType
playerIds :: [Text]
ticketId :: Text
$sel:acceptanceType:AcceptMatch' :: AcceptMatch -> AcceptanceType
$sel:playerIds:AcceptMatch' :: AcceptMatch -> [Text]
$sel:ticketId:AcceptMatch' :: AcceptMatch -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ticketId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
playerIds
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AcceptanceType
acceptanceType
instance Prelude.NFData AcceptMatch where
rnf :: AcceptMatch -> ()
rnf AcceptMatch' {[Text]
Text
AcceptanceType
acceptanceType :: AcceptanceType
playerIds :: [Text]
ticketId :: Text
$sel:acceptanceType:AcceptMatch' :: AcceptMatch -> AcceptanceType
$sel:playerIds:AcceptMatch' :: AcceptMatch -> [Text]
$sel:ticketId:AcceptMatch' :: AcceptMatch -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
ticketId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
playerIds
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AcceptanceType
acceptanceType
instance Data.ToHeaders AcceptMatch where
toHeaders :: AcceptMatch -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"GameLift.AcceptMatch" :: Prelude.ByteString),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON AcceptMatch where
toJSON :: AcceptMatch -> Value
toJSON AcceptMatch' {[Text]
Text
AcceptanceType
acceptanceType :: AcceptanceType
playerIds :: [Text]
ticketId :: Text
$sel:acceptanceType:AcceptMatch' :: AcceptMatch -> AcceptanceType
$sel:playerIds:AcceptMatch' :: AcceptMatch -> [Text]
$sel:ticketId:AcceptMatch' :: AcceptMatch -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just (Key
"TicketId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
ticketId),
forall a. a -> Maybe a
Prelude.Just (Key
"PlayerIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
playerIds),
forall a. a -> Maybe a
Prelude.Just
(Key
"AcceptanceType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AcceptanceType
acceptanceType)
]
)
instance Data.ToPath AcceptMatch where
toPath :: AcceptMatch -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery AcceptMatch where
toQuery :: AcceptMatch -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data AcceptMatchResponse = AcceptMatchResponse'
{
AcceptMatchResponse -> Int
httpStatus :: Prelude.Int
}
deriving (AcceptMatchResponse -> AcceptMatchResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptMatchResponse -> AcceptMatchResponse -> Bool
$c/= :: AcceptMatchResponse -> AcceptMatchResponse -> Bool
== :: AcceptMatchResponse -> AcceptMatchResponse -> Bool
$c== :: AcceptMatchResponse -> AcceptMatchResponse -> Bool
Prelude.Eq, ReadPrec [AcceptMatchResponse]
ReadPrec AcceptMatchResponse
Int -> ReadS AcceptMatchResponse
ReadS [AcceptMatchResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AcceptMatchResponse]
$creadListPrec :: ReadPrec [AcceptMatchResponse]
readPrec :: ReadPrec AcceptMatchResponse
$creadPrec :: ReadPrec AcceptMatchResponse
readList :: ReadS [AcceptMatchResponse]
$creadList :: ReadS [AcceptMatchResponse]
readsPrec :: Int -> ReadS AcceptMatchResponse
$creadsPrec :: Int -> ReadS AcceptMatchResponse
Prelude.Read, Int -> AcceptMatchResponse -> ShowS
[AcceptMatchResponse] -> ShowS
AcceptMatchResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptMatchResponse] -> ShowS
$cshowList :: [AcceptMatchResponse] -> ShowS
show :: AcceptMatchResponse -> String
$cshow :: AcceptMatchResponse -> String
showsPrec :: Int -> AcceptMatchResponse -> ShowS
$cshowsPrec :: Int -> AcceptMatchResponse -> ShowS
Prelude.Show, forall x. Rep AcceptMatchResponse x -> AcceptMatchResponse
forall x. AcceptMatchResponse -> Rep AcceptMatchResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AcceptMatchResponse x -> AcceptMatchResponse
$cfrom :: forall x. AcceptMatchResponse -> Rep AcceptMatchResponse x
Prelude.Generic)
newAcceptMatchResponse ::
Prelude.Int ->
AcceptMatchResponse
newAcceptMatchResponse :: Int -> AcceptMatchResponse
newAcceptMatchResponse Int
pHttpStatus_ =
AcceptMatchResponse' {$sel:httpStatus:AcceptMatchResponse' :: Int
httpStatus = Int
pHttpStatus_}
acceptMatchResponse_httpStatus :: Lens.Lens' AcceptMatchResponse Prelude.Int
acceptMatchResponse_httpStatus :: Lens' AcceptMatchResponse Int
acceptMatchResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptMatchResponse' {Int
httpStatus :: Int
$sel:httpStatus:AcceptMatchResponse' :: AcceptMatchResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AcceptMatchResponse
s@AcceptMatchResponse' {} Int
a -> AcceptMatchResponse
s {$sel:httpStatus:AcceptMatchResponse' :: Int
httpStatus = Int
a} :: AcceptMatchResponse)
instance Prelude.NFData AcceptMatchResponse where
rnf :: AcceptMatchResponse -> ()
rnf AcceptMatchResponse' {Int
httpStatus :: Int
$sel:httpStatus:AcceptMatchResponse' :: AcceptMatchResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus