{-# 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.DescribeMatchmaking
(
DescribeMatchmaking (..),
newDescribeMatchmaking,
describeMatchmaking_ticketIds,
DescribeMatchmakingResponse (..),
newDescribeMatchmakingResponse,
describeMatchmakingResponse_ticketList,
describeMatchmakingResponse_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 DescribeMatchmaking = DescribeMatchmaking'
{
DescribeMatchmaking -> [Text]
ticketIds :: [Prelude.Text]
}
deriving (DescribeMatchmaking -> DescribeMatchmaking -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeMatchmaking -> DescribeMatchmaking -> Bool
$c/= :: DescribeMatchmaking -> DescribeMatchmaking -> Bool
== :: DescribeMatchmaking -> DescribeMatchmaking -> Bool
$c== :: DescribeMatchmaking -> DescribeMatchmaking -> Bool
Prelude.Eq, ReadPrec [DescribeMatchmaking]
ReadPrec DescribeMatchmaking
Int -> ReadS DescribeMatchmaking
ReadS [DescribeMatchmaking]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeMatchmaking]
$creadListPrec :: ReadPrec [DescribeMatchmaking]
readPrec :: ReadPrec DescribeMatchmaking
$creadPrec :: ReadPrec DescribeMatchmaking
readList :: ReadS [DescribeMatchmaking]
$creadList :: ReadS [DescribeMatchmaking]
readsPrec :: Int -> ReadS DescribeMatchmaking
$creadsPrec :: Int -> ReadS DescribeMatchmaking
Prelude.Read, Int -> DescribeMatchmaking -> ShowS
[DescribeMatchmaking] -> ShowS
DescribeMatchmaking -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeMatchmaking] -> ShowS
$cshowList :: [DescribeMatchmaking] -> ShowS
show :: DescribeMatchmaking -> String
$cshow :: DescribeMatchmaking -> String
showsPrec :: Int -> DescribeMatchmaking -> ShowS
$cshowsPrec :: Int -> DescribeMatchmaking -> ShowS
Prelude.Show, forall x. Rep DescribeMatchmaking x -> DescribeMatchmaking
forall x. DescribeMatchmaking -> Rep DescribeMatchmaking x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeMatchmaking x -> DescribeMatchmaking
$cfrom :: forall x. DescribeMatchmaking -> Rep DescribeMatchmaking x
Prelude.Generic)
newDescribeMatchmaking ::
DescribeMatchmaking
newDescribeMatchmaking :: DescribeMatchmaking
newDescribeMatchmaking =
DescribeMatchmaking' {$sel:ticketIds:DescribeMatchmaking' :: [Text]
ticketIds = forall a. Monoid a => a
Prelude.mempty}
describeMatchmaking_ticketIds :: Lens.Lens' DescribeMatchmaking [Prelude.Text]
describeMatchmaking_ticketIds :: Lens' DescribeMatchmaking [Text]
describeMatchmaking_ticketIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeMatchmaking' {[Text]
ticketIds :: [Text]
$sel:ticketIds:DescribeMatchmaking' :: DescribeMatchmaking -> [Text]
ticketIds} -> [Text]
ticketIds) (\s :: DescribeMatchmaking
s@DescribeMatchmaking' {} [Text]
a -> DescribeMatchmaking
s {$sel:ticketIds:DescribeMatchmaking' :: [Text]
ticketIds = [Text]
a} :: DescribeMatchmaking) 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
instance Core.AWSRequest DescribeMatchmaking where
type
AWSResponse DescribeMatchmaking =
DescribeMatchmakingResponse
request :: (Service -> Service)
-> DescribeMatchmaking -> Request DescribeMatchmaking
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 DescribeMatchmaking
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DescribeMatchmaking)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
( \Int
s ResponseHeaders
h Object
x ->
Maybe [MatchmakingTicket] -> Int -> DescribeMatchmakingResponse
DescribeMatchmakingResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"TicketList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => 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 DescribeMatchmaking where
hashWithSalt :: Int -> DescribeMatchmaking -> Int
hashWithSalt Int
_salt DescribeMatchmaking' {[Text]
ticketIds :: [Text]
$sel:ticketIds:DescribeMatchmaking' :: DescribeMatchmaking -> [Text]
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
ticketIds
instance Prelude.NFData DescribeMatchmaking where
rnf :: DescribeMatchmaking -> ()
rnf DescribeMatchmaking' {[Text]
ticketIds :: [Text]
$sel:ticketIds:DescribeMatchmaking' :: DescribeMatchmaking -> [Text]
..} = forall a. NFData a => a -> ()
Prelude.rnf [Text]
ticketIds
instance Data.ToHeaders DescribeMatchmaking where
toHeaders :: DescribeMatchmaking -> 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.DescribeMatchmaking" ::
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 DescribeMatchmaking where
toJSON :: DescribeMatchmaking -> Value
toJSON DescribeMatchmaking' {[Text]
ticketIds :: [Text]
$sel:ticketIds:DescribeMatchmaking' :: DescribeMatchmaking -> [Text]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"TicketIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
ticketIds)]
)
instance Data.ToPath DescribeMatchmaking where
toPath :: DescribeMatchmaking -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeMatchmaking where
toQuery :: DescribeMatchmaking -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DescribeMatchmakingResponse = DescribeMatchmakingResponse'
{
DescribeMatchmakingResponse -> Maybe [MatchmakingTicket]
ticketList :: Prelude.Maybe [MatchmakingTicket],
DescribeMatchmakingResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DescribeMatchmakingResponse -> DescribeMatchmakingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeMatchmakingResponse -> DescribeMatchmakingResponse -> Bool
$c/= :: DescribeMatchmakingResponse -> DescribeMatchmakingResponse -> Bool
== :: DescribeMatchmakingResponse -> DescribeMatchmakingResponse -> Bool
$c== :: DescribeMatchmakingResponse -> DescribeMatchmakingResponse -> Bool
Prelude.Eq, ReadPrec [DescribeMatchmakingResponse]
ReadPrec DescribeMatchmakingResponse
Int -> ReadS DescribeMatchmakingResponse
ReadS [DescribeMatchmakingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeMatchmakingResponse]
$creadListPrec :: ReadPrec [DescribeMatchmakingResponse]
readPrec :: ReadPrec DescribeMatchmakingResponse
$creadPrec :: ReadPrec DescribeMatchmakingResponse
readList :: ReadS [DescribeMatchmakingResponse]
$creadList :: ReadS [DescribeMatchmakingResponse]
readsPrec :: Int -> ReadS DescribeMatchmakingResponse
$creadsPrec :: Int -> ReadS DescribeMatchmakingResponse
Prelude.Read, Int -> DescribeMatchmakingResponse -> ShowS
[DescribeMatchmakingResponse] -> ShowS
DescribeMatchmakingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeMatchmakingResponse] -> ShowS
$cshowList :: [DescribeMatchmakingResponse] -> ShowS
show :: DescribeMatchmakingResponse -> String
$cshow :: DescribeMatchmakingResponse -> String
showsPrec :: Int -> DescribeMatchmakingResponse -> ShowS
$cshowsPrec :: Int -> DescribeMatchmakingResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeMatchmakingResponse x -> DescribeMatchmakingResponse
forall x.
DescribeMatchmakingResponse -> Rep DescribeMatchmakingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeMatchmakingResponse x -> DescribeMatchmakingResponse
$cfrom :: forall x.
DescribeMatchmakingResponse -> Rep DescribeMatchmakingResponse x
Prelude.Generic)
newDescribeMatchmakingResponse ::
Prelude.Int ->
DescribeMatchmakingResponse
newDescribeMatchmakingResponse :: Int -> DescribeMatchmakingResponse
newDescribeMatchmakingResponse Int
pHttpStatus_ =
DescribeMatchmakingResponse'
{ $sel:ticketList:DescribeMatchmakingResponse' :: Maybe [MatchmakingTicket]
ticketList =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:DescribeMatchmakingResponse' :: Int
httpStatus = Int
pHttpStatus_
}
describeMatchmakingResponse_ticketList :: Lens.Lens' DescribeMatchmakingResponse (Prelude.Maybe [MatchmakingTicket])
describeMatchmakingResponse_ticketList :: Lens' DescribeMatchmakingResponse (Maybe [MatchmakingTicket])
describeMatchmakingResponse_ticketList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeMatchmakingResponse' {Maybe [MatchmakingTicket]
ticketList :: Maybe [MatchmakingTicket]
$sel:ticketList:DescribeMatchmakingResponse' :: DescribeMatchmakingResponse -> Maybe [MatchmakingTicket]
ticketList} -> Maybe [MatchmakingTicket]
ticketList) (\s :: DescribeMatchmakingResponse
s@DescribeMatchmakingResponse' {} Maybe [MatchmakingTicket]
a -> DescribeMatchmakingResponse
s {$sel:ticketList:DescribeMatchmakingResponse' :: Maybe [MatchmakingTicket]
ticketList = Maybe [MatchmakingTicket]
a} :: DescribeMatchmakingResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
describeMatchmakingResponse_httpStatus :: Lens.Lens' DescribeMatchmakingResponse Prelude.Int
describeMatchmakingResponse_httpStatus :: Lens' DescribeMatchmakingResponse Int
describeMatchmakingResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeMatchmakingResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeMatchmakingResponse' :: DescribeMatchmakingResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeMatchmakingResponse
s@DescribeMatchmakingResponse' {} Int
a -> DescribeMatchmakingResponse
s {$sel:httpStatus:DescribeMatchmakingResponse' :: Int
httpStatus = Int
a} :: DescribeMatchmakingResponse)
instance Prelude.NFData DescribeMatchmakingResponse where
rnf :: DescribeMatchmakingResponse -> ()
rnf DescribeMatchmakingResponse' {Int
Maybe [MatchmakingTicket]
httpStatus :: Int
ticketList :: Maybe [MatchmakingTicket]
$sel:httpStatus:DescribeMatchmakingResponse' :: DescribeMatchmakingResponse -> Int
$sel:ticketList:DescribeMatchmakingResponse' :: DescribeMatchmakingResponse -> Maybe [MatchmakingTicket]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [MatchmakingTicket]
ticketList
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus