{-# 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.SearchGameSessions
(
SearchGameSessions (..),
newSearchGameSessions,
searchGameSessions_aliasId,
searchGameSessions_filterExpression,
searchGameSessions_fleetId,
searchGameSessions_limit,
searchGameSessions_location,
searchGameSessions_nextToken,
searchGameSessions_sortExpression,
SearchGameSessionsResponse (..),
newSearchGameSessionsResponse,
searchGameSessionsResponse_gameSessions,
searchGameSessionsResponse_nextToken,
searchGameSessionsResponse_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 SearchGameSessions = SearchGameSessions'
{
SearchGameSessions -> Maybe Text
aliasId :: Prelude.Maybe Prelude.Text,
SearchGameSessions -> Maybe Text
filterExpression :: Prelude.Maybe Prelude.Text,
SearchGameSessions -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
SearchGameSessions -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
SearchGameSessions -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
SearchGameSessions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
SearchGameSessions -> Maybe Text
sortExpression :: Prelude.Maybe Prelude.Text
}
deriving (SearchGameSessions -> SearchGameSessions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchGameSessions -> SearchGameSessions -> Bool
$c/= :: SearchGameSessions -> SearchGameSessions -> Bool
== :: SearchGameSessions -> SearchGameSessions -> Bool
$c== :: SearchGameSessions -> SearchGameSessions -> Bool
Prelude.Eq, ReadPrec [SearchGameSessions]
ReadPrec SearchGameSessions
Int -> ReadS SearchGameSessions
ReadS [SearchGameSessions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchGameSessions]
$creadListPrec :: ReadPrec [SearchGameSessions]
readPrec :: ReadPrec SearchGameSessions
$creadPrec :: ReadPrec SearchGameSessions
readList :: ReadS [SearchGameSessions]
$creadList :: ReadS [SearchGameSessions]
readsPrec :: Int -> ReadS SearchGameSessions
$creadsPrec :: Int -> ReadS SearchGameSessions
Prelude.Read, Int -> SearchGameSessions -> ShowS
[SearchGameSessions] -> ShowS
SearchGameSessions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchGameSessions] -> ShowS
$cshowList :: [SearchGameSessions] -> ShowS
show :: SearchGameSessions -> String
$cshow :: SearchGameSessions -> String
showsPrec :: Int -> SearchGameSessions -> ShowS
$cshowsPrec :: Int -> SearchGameSessions -> ShowS
Prelude.Show, forall x. Rep SearchGameSessions x -> SearchGameSessions
forall x. SearchGameSessions -> Rep SearchGameSessions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchGameSessions x -> SearchGameSessions
$cfrom :: forall x. SearchGameSessions -> Rep SearchGameSessions x
Prelude.Generic)
newSearchGameSessions ::
SearchGameSessions
newSearchGameSessions :: SearchGameSessions
newSearchGameSessions =
SearchGameSessions'
{ $sel:aliasId:SearchGameSessions' :: Maybe Text
aliasId = forall a. Maybe a
Prelude.Nothing,
$sel:filterExpression:SearchGameSessions' :: Maybe Text
filterExpression = forall a. Maybe a
Prelude.Nothing,
$sel:fleetId:SearchGameSessions' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
$sel:limit:SearchGameSessions' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
$sel:location:SearchGameSessions' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:SearchGameSessions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:sortExpression:SearchGameSessions' :: Maybe Text
sortExpression = forall a. Maybe a
Prelude.Nothing
}
searchGameSessions_aliasId :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Text)
searchGameSessions_aliasId :: Lens' SearchGameSessions (Maybe Text)
searchGameSessions_aliasId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Text
aliasId :: Maybe Text
$sel:aliasId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
aliasId} -> Maybe Text
aliasId) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Text
a -> SearchGameSessions
s {$sel:aliasId:SearchGameSessions' :: Maybe Text
aliasId = Maybe Text
a} :: SearchGameSessions)
searchGameSessions_filterExpression :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Text)
searchGameSessions_filterExpression :: Lens' SearchGameSessions (Maybe Text)
searchGameSessions_filterExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Text
filterExpression :: Maybe Text
$sel:filterExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
filterExpression} -> Maybe Text
filterExpression) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Text
a -> SearchGameSessions
s {$sel:filterExpression:SearchGameSessions' :: Maybe Text
filterExpression = Maybe Text
a} :: SearchGameSessions)
searchGameSessions_fleetId :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Text)
searchGameSessions_fleetId :: Lens' SearchGameSessions (Maybe Text)
searchGameSessions_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Text
fleetId :: Maybe Text
$sel:fleetId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
fleetId} -> Maybe Text
fleetId) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Text
a -> SearchGameSessions
s {$sel:fleetId:SearchGameSessions' :: Maybe Text
fleetId = Maybe Text
a} :: SearchGameSessions)
searchGameSessions_limit :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Natural)
searchGameSessions_limit :: Lens' SearchGameSessions (Maybe Natural)
searchGameSessions_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Natural
limit :: Maybe Natural
$sel:limit:SearchGameSessions' :: SearchGameSessions -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Natural
a -> SearchGameSessions
s {$sel:limit:SearchGameSessions' :: Maybe Natural
limit = Maybe Natural
a} :: SearchGameSessions)
searchGameSessions_location :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Text)
searchGameSessions_location :: Lens' SearchGameSessions (Maybe Text)
searchGameSessions_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Text
location :: Maybe Text
$sel:location:SearchGameSessions' :: SearchGameSessions -> Maybe Text
location} -> Maybe Text
location) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Text
a -> SearchGameSessions
s {$sel:location:SearchGameSessions' :: Maybe Text
location = Maybe Text
a} :: SearchGameSessions)
searchGameSessions_nextToken :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Text)
searchGameSessions_nextToken :: Lens' SearchGameSessions (Maybe Text)
searchGameSessions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchGameSessions' :: SearchGameSessions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Text
a -> SearchGameSessions
s {$sel:nextToken:SearchGameSessions' :: Maybe Text
nextToken = Maybe Text
a} :: SearchGameSessions)
searchGameSessions_sortExpression :: Lens.Lens' SearchGameSessions (Prelude.Maybe Prelude.Text)
searchGameSessions_sortExpression :: Lens' SearchGameSessions (Maybe Text)
searchGameSessions_sortExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessions' {Maybe Text
sortExpression :: Maybe Text
$sel:sortExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
sortExpression} -> Maybe Text
sortExpression) (\s :: SearchGameSessions
s@SearchGameSessions' {} Maybe Text
a -> SearchGameSessions
s {$sel:sortExpression:SearchGameSessions' :: Maybe Text
sortExpression = Maybe Text
a} :: SearchGameSessions)
instance Core.AWSPager SearchGameSessions where
page :: SearchGameSessions
-> AWSResponse SearchGameSessions -> Maybe SearchGameSessions
page SearchGameSessions
rq AWSResponse SearchGameSessions
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse SearchGameSessions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchGameSessionsResponse (Maybe Text)
searchGameSessionsResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse SearchGameSessions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchGameSessionsResponse (Maybe [GameSession])
searchGameSessionsResponse_gameSessions
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ SearchGameSessions
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchGameSessions (Maybe Text)
searchGameSessions_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchGameSessions
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchGameSessionsResponse (Maybe Text)
searchGameSessionsResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest SearchGameSessions where
type
AWSResponse SearchGameSessions =
SearchGameSessionsResponse
request :: (Service -> Service)
-> SearchGameSessions -> Request SearchGameSessions
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 SearchGameSessions
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse SearchGameSessions)))
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 [GameSession]
-> Maybe Text -> Int -> SearchGameSessionsResponse
SearchGameSessionsResponse'
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
"GameSessions" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
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 SearchGameSessions where
hashWithSalt :: Int -> SearchGameSessions -> Int
hashWithSalt Int
_salt SearchGameSessions' {Maybe Natural
Maybe Text
sortExpression :: Maybe Text
nextToken :: Maybe Text
location :: Maybe Text
limit :: Maybe Natural
fleetId :: Maybe Text
filterExpression :: Maybe Text
aliasId :: Maybe Text
$sel:sortExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:nextToken:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:location:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:limit:SearchGameSessions' :: SearchGameSessions -> Maybe Natural
$sel:fleetId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:filterExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:aliasId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
aliasId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
filterExpression
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fleetId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
location
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sortExpression
instance Prelude.NFData SearchGameSessions where
rnf :: SearchGameSessions -> ()
rnf SearchGameSessions' {Maybe Natural
Maybe Text
sortExpression :: Maybe Text
nextToken :: Maybe Text
location :: Maybe Text
limit :: Maybe Natural
fleetId :: Maybe Text
filterExpression :: Maybe Text
aliasId :: Maybe Text
$sel:sortExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:nextToken:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:location:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:limit:SearchGameSessions' :: SearchGameSessions -> Maybe Natural
$sel:fleetId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:filterExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:aliasId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
aliasId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
filterExpression
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fleetId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sortExpression
instance Data.ToHeaders SearchGameSessions where
toHeaders :: SearchGameSessions -> 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.SearchGameSessions" ::
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 SearchGameSessions where
toJSON :: SearchGameSessions -> Value
toJSON SearchGameSessions' {Maybe Natural
Maybe Text
sortExpression :: Maybe Text
nextToken :: Maybe Text
location :: Maybe Text
limit :: Maybe Natural
fleetId :: Maybe Text
filterExpression :: Maybe Text
aliasId :: Maybe Text
$sel:sortExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:nextToken:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:location:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:limit:SearchGameSessions' :: SearchGameSessions -> Maybe Natural
$sel:fleetId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:filterExpression:SearchGameSessions' :: SearchGameSessions -> Maybe Text
$sel:aliasId:SearchGameSessions' :: SearchGameSessions -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"AliasId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
aliasId,
(Key
"FilterExpression" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
filterExpression,
(Key
"FleetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
fleetId,
(Key
"Limit" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
limit,
(Key
"Location" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
location,
(Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
(Key
"SortExpression" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
sortExpression
]
)
instance Data.ToPath SearchGameSessions where
toPath :: SearchGameSessions -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery SearchGameSessions where
toQuery :: SearchGameSessions -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data SearchGameSessionsResponse = SearchGameSessionsResponse'
{
SearchGameSessionsResponse -> Maybe [GameSession]
gameSessions :: Prelude.Maybe [GameSession],
SearchGameSessionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
SearchGameSessionsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (SearchGameSessionsResponse -> SearchGameSessionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchGameSessionsResponse -> SearchGameSessionsResponse -> Bool
$c/= :: SearchGameSessionsResponse -> SearchGameSessionsResponse -> Bool
== :: SearchGameSessionsResponse -> SearchGameSessionsResponse -> Bool
$c== :: SearchGameSessionsResponse -> SearchGameSessionsResponse -> Bool
Prelude.Eq, ReadPrec [SearchGameSessionsResponse]
ReadPrec SearchGameSessionsResponse
Int -> ReadS SearchGameSessionsResponse
ReadS [SearchGameSessionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchGameSessionsResponse]
$creadListPrec :: ReadPrec [SearchGameSessionsResponse]
readPrec :: ReadPrec SearchGameSessionsResponse
$creadPrec :: ReadPrec SearchGameSessionsResponse
readList :: ReadS [SearchGameSessionsResponse]
$creadList :: ReadS [SearchGameSessionsResponse]
readsPrec :: Int -> ReadS SearchGameSessionsResponse
$creadsPrec :: Int -> ReadS SearchGameSessionsResponse
Prelude.Read, Int -> SearchGameSessionsResponse -> ShowS
[SearchGameSessionsResponse] -> ShowS
SearchGameSessionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchGameSessionsResponse] -> ShowS
$cshowList :: [SearchGameSessionsResponse] -> ShowS
show :: SearchGameSessionsResponse -> String
$cshow :: SearchGameSessionsResponse -> String
showsPrec :: Int -> SearchGameSessionsResponse -> ShowS
$cshowsPrec :: Int -> SearchGameSessionsResponse -> ShowS
Prelude.Show, forall x.
Rep SearchGameSessionsResponse x -> SearchGameSessionsResponse
forall x.
SearchGameSessionsResponse -> Rep SearchGameSessionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchGameSessionsResponse x -> SearchGameSessionsResponse
$cfrom :: forall x.
SearchGameSessionsResponse -> Rep SearchGameSessionsResponse x
Prelude.Generic)
newSearchGameSessionsResponse ::
Prelude.Int ->
SearchGameSessionsResponse
newSearchGameSessionsResponse :: Int -> SearchGameSessionsResponse
newSearchGameSessionsResponse Int
pHttpStatus_ =
SearchGameSessionsResponse'
{ $sel:gameSessions:SearchGameSessionsResponse' :: Maybe [GameSession]
gameSessions =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:SearchGameSessionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:SearchGameSessionsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
searchGameSessionsResponse_gameSessions :: Lens.Lens' SearchGameSessionsResponse (Prelude.Maybe [GameSession])
searchGameSessionsResponse_gameSessions :: Lens' SearchGameSessionsResponse (Maybe [GameSession])
searchGameSessionsResponse_gameSessions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessionsResponse' {Maybe [GameSession]
gameSessions :: Maybe [GameSession]
$sel:gameSessions:SearchGameSessionsResponse' :: SearchGameSessionsResponse -> Maybe [GameSession]
gameSessions} -> Maybe [GameSession]
gameSessions) (\s :: SearchGameSessionsResponse
s@SearchGameSessionsResponse' {} Maybe [GameSession]
a -> SearchGameSessionsResponse
s {$sel:gameSessions:SearchGameSessionsResponse' :: Maybe [GameSession]
gameSessions = Maybe [GameSession]
a} :: SearchGameSessionsResponse) 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
searchGameSessionsResponse_nextToken :: Lens.Lens' SearchGameSessionsResponse (Prelude.Maybe Prelude.Text)
searchGameSessionsResponse_nextToken :: Lens' SearchGameSessionsResponse (Maybe Text)
searchGameSessionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchGameSessionsResponse' :: SearchGameSessionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchGameSessionsResponse
s@SearchGameSessionsResponse' {} Maybe Text
a -> SearchGameSessionsResponse
s {$sel:nextToken:SearchGameSessionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: SearchGameSessionsResponse)
searchGameSessionsResponse_httpStatus :: Lens.Lens' SearchGameSessionsResponse Prelude.Int
searchGameSessionsResponse_httpStatus :: Lens' SearchGameSessionsResponse Int
searchGameSessionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchGameSessionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:SearchGameSessionsResponse' :: SearchGameSessionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SearchGameSessionsResponse
s@SearchGameSessionsResponse' {} Int
a -> SearchGameSessionsResponse
s {$sel:httpStatus:SearchGameSessionsResponse' :: Int
httpStatus = Int
a} :: SearchGameSessionsResponse)
instance Prelude.NFData SearchGameSessionsResponse where
rnf :: SearchGameSessionsResponse -> ()
rnf SearchGameSessionsResponse' {Int
Maybe [GameSession]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
gameSessions :: Maybe [GameSession]
$sel:httpStatus:SearchGameSessionsResponse' :: SearchGameSessionsResponse -> Int
$sel:nextToken:SearchGameSessionsResponse' :: SearchGameSessionsResponse -> Maybe Text
$sel:gameSessions:SearchGameSessionsResponse' :: SearchGameSessionsResponse -> Maybe [GameSession]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [GameSession]
gameSessions
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus