{-# 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.CreateFleetLocations
(
CreateFleetLocations (..),
newCreateFleetLocations,
createFleetLocations_fleetId,
createFleetLocations_locations,
CreateFleetLocationsResponse (..),
newCreateFleetLocationsResponse,
createFleetLocationsResponse_fleetArn,
createFleetLocationsResponse_fleetId,
createFleetLocationsResponse_locationStates,
createFleetLocationsResponse_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 CreateFleetLocations = CreateFleetLocations'
{
CreateFleetLocations -> Text
fleetId :: Prelude.Text,
CreateFleetLocations -> NonEmpty LocationConfiguration
locations :: Prelude.NonEmpty LocationConfiguration
}
deriving (CreateFleetLocations -> CreateFleetLocations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFleetLocations -> CreateFleetLocations -> Bool
$c/= :: CreateFleetLocations -> CreateFleetLocations -> Bool
== :: CreateFleetLocations -> CreateFleetLocations -> Bool
$c== :: CreateFleetLocations -> CreateFleetLocations -> Bool
Prelude.Eq, ReadPrec [CreateFleetLocations]
ReadPrec CreateFleetLocations
Int -> ReadS CreateFleetLocations
ReadS [CreateFleetLocations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFleetLocations]
$creadListPrec :: ReadPrec [CreateFleetLocations]
readPrec :: ReadPrec CreateFleetLocations
$creadPrec :: ReadPrec CreateFleetLocations
readList :: ReadS [CreateFleetLocations]
$creadList :: ReadS [CreateFleetLocations]
readsPrec :: Int -> ReadS CreateFleetLocations
$creadsPrec :: Int -> ReadS CreateFleetLocations
Prelude.Read, Int -> CreateFleetLocations -> ShowS
[CreateFleetLocations] -> ShowS
CreateFleetLocations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFleetLocations] -> ShowS
$cshowList :: [CreateFleetLocations] -> ShowS
show :: CreateFleetLocations -> String
$cshow :: CreateFleetLocations -> String
showsPrec :: Int -> CreateFleetLocations -> ShowS
$cshowsPrec :: Int -> CreateFleetLocations -> ShowS
Prelude.Show, forall x. Rep CreateFleetLocations x -> CreateFleetLocations
forall x. CreateFleetLocations -> Rep CreateFleetLocations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFleetLocations x -> CreateFleetLocations
$cfrom :: forall x. CreateFleetLocations -> Rep CreateFleetLocations x
Prelude.Generic)
newCreateFleetLocations ::
Prelude.Text ->
Prelude.NonEmpty LocationConfiguration ->
CreateFleetLocations
newCreateFleetLocations :: Text -> NonEmpty LocationConfiguration -> CreateFleetLocations
newCreateFleetLocations Text
pFleetId_ NonEmpty LocationConfiguration
pLocations_ =
CreateFleetLocations'
{ $sel:fleetId:CreateFleetLocations' :: Text
fleetId = Text
pFleetId_,
$sel:locations:CreateFleetLocations' :: NonEmpty LocationConfiguration
locations = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty LocationConfiguration
pLocations_
}
createFleetLocations_fleetId :: Lens.Lens' CreateFleetLocations Prelude.Text
createFleetLocations_fleetId :: Lens' CreateFleetLocations Text
createFleetLocations_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFleetLocations' {Text
fleetId :: Text
$sel:fleetId:CreateFleetLocations' :: CreateFleetLocations -> Text
fleetId} -> Text
fleetId) (\s :: CreateFleetLocations
s@CreateFleetLocations' {} Text
a -> CreateFleetLocations
s {$sel:fleetId:CreateFleetLocations' :: Text
fleetId = Text
a} :: CreateFleetLocations)
createFleetLocations_locations :: Lens.Lens' CreateFleetLocations (Prelude.NonEmpty LocationConfiguration)
createFleetLocations_locations :: Lens' CreateFleetLocations (NonEmpty LocationConfiguration)
createFleetLocations_locations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFleetLocations' {NonEmpty LocationConfiguration
locations :: NonEmpty LocationConfiguration
$sel:locations:CreateFleetLocations' :: CreateFleetLocations -> NonEmpty LocationConfiguration
locations} -> NonEmpty LocationConfiguration
locations) (\s :: CreateFleetLocations
s@CreateFleetLocations' {} NonEmpty LocationConfiguration
a -> CreateFleetLocations
s {$sel:locations:CreateFleetLocations' :: NonEmpty LocationConfiguration
locations = NonEmpty LocationConfiguration
a} :: CreateFleetLocations) 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 CreateFleetLocations where
type
AWSResponse CreateFleetLocations =
CreateFleetLocationsResponse
request :: (Service -> Service)
-> CreateFleetLocations -> Request CreateFleetLocations
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 CreateFleetLocations
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse CreateFleetLocations)))
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 Text
-> Maybe Text
-> Maybe [LocationState]
-> Int
-> CreateFleetLocationsResponse
CreateFleetLocationsResponse'
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
"FleetArn")
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
"FleetId")
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
"LocationStates" 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 CreateFleetLocations where
hashWithSalt :: Int -> CreateFleetLocations -> Int
hashWithSalt Int
_salt CreateFleetLocations' {NonEmpty LocationConfiguration
Text
locations :: NonEmpty LocationConfiguration
fleetId :: Text
$sel:locations:CreateFleetLocations' :: CreateFleetLocations -> NonEmpty LocationConfiguration
$sel:fleetId:CreateFleetLocations' :: CreateFleetLocations -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fleetId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty LocationConfiguration
locations
instance Prelude.NFData CreateFleetLocations where
rnf :: CreateFleetLocations -> ()
rnf CreateFleetLocations' {NonEmpty LocationConfiguration
Text
locations :: NonEmpty LocationConfiguration
fleetId :: Text
$sel:locations:CreateFleetLocations' :: CreateFleetLocations -> NonEmpty LocationConfiguration
$sel:fleetId:CreateFleetLocations' :: CreateFleetLocations -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
fleetId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty LocationConfiguration
locations
instance Data.ToHeaders CreateFleetLocations where
toHeaders :: CreateFleetLocations -> 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.CreateFleetLocations" ::
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 CreateFleetLocations where
toJSON :: CreateFleetLocations -> Value
toJSON CreateFleetLocations' {NonEmpty LocationConfiguration
Text
locations :: NonEmpty LocationConfiguration
fleetId :: Text
$sel:locations:CreateFleetLocations' :: CreateFleetLocations -> NonEmpty LocationConfiguration
$sel:fleetId:CreateFleetLocations' :: CreateFleetLocations -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ forall a. a -> Maybe a
Prelude.Just (Key
"FleetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fleetId),
forall a. a -> Maybe a
Prelude.Just (Key
"Locations" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty LocationConfiguration
locations)
]
)
instance Data.ToPath CreateFleetLocations where
toPath :: CreateFleetLocations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateFleetLocations where
toQuery :: CreateFleetLocations -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CreateFleetLocationsResponse = CreateFleetLocationsResponse'
{
CreateFleetLocationsResponse -> Maybe Text
fleetArn :: Prelude.Maybe Prelude.Text,
CreateFleetLocationsResponse -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
CreateFleetLocationsResponse -> Maybe [LocationState]
locationStates :: Prelude.Maybe [LocationState],
CreateFleetLocationsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CreateFleetLocationsResponse
-> CreateFleetLocationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFleetLocationsResponse
-> CreateFleetLocationsResponse -> Bool
$c/= :: CreateFleetLocationsResponse
-> CreateFleetLocationsResponse -> Bool
== :: CreateFleetLocationsResponse
-> CreateFleetLocationsResponse -> Bool
$c== :: CreateFleetLocationsResponse
-> CreateFleetLocationsResponse -> Bool
Prelude.Eq, ReadPrec [CreateFleetLocationsResponse]
ReadPrec CreateFleetLocationsResponse
Int -> ReadS CreateFleetLocationsResponse
ReadS [CreateFleetLocationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFleetLocationsResponse]
$creadListPrec :: ReadPrec [CreateFleetLocationsResponse]
readPrec :: ReadPrec CreateFleetLocationsResponse
$creadPrec :: ReadPrec CreateFleetLocationsResponse
readList :: ReadS [CreateFleetLocationsResponse]
$creadList :: ReadS [CreateFleetLocationsResponse]
readsPrec :: Int -> ReadS CreateFleetLocationsResponse
$creadsPrec :: Int -> ReadS CreateFleetLocationsResponse
Prelude.Read, Int -> CreateFleetLocationsResponse -> ShowS
[CreateFleetLocationsResponse] -> ShowS
CreateFleetLocationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFleetLocationsResponse] -> ShowS
$cshowList :: [CreateFleetLocationsResponse] -> ShowS
show :: CreateFleetLocationsResponse -> String
$cshow :: CreateFleetLocationsResponse -> String
showsPrec :: Int -> CreateFleetLocationsResponse -> ShowS
$cshowsPrec :: Int -> CreateFleetLocationsResponse -> ShowS
Prelude.Show, forall x.
Rep CreateFleetLocationsResponse x -> CreateFleetLocationsResponse
forall x.
CreateFleetLocationsResponse -> Rep CreateFleetLocationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateFleetLocationsResponse x -> CreateFleetLocationsResponse
$cfrom :: forall x.
CreateFleetLocationsResponse -> Rep CreateFleetLocationsResponse x
Prelude.Generic)
newCreateFleetLocationsResponse ::
Prelude.Int ->
CreateFleetLocationsResponse
newCreateFleetLocationsResponse :: Int -> CreateFleetLocationsResponse
newCreateFleetLocationsResponse Int
pHttpStatus_ =
CreateFleetLocationsResponse'
{ $sel:fleetArn:CreateFleetLocationsResponse' :: Maybe Text
fleetArn =
forall a. Maybe a
Prelude.Nothing,
$sel:fleetId:CreateFleetLocationsResponse' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
$sel:locationStates:CreateFleetLocationsResponse' :: Maybe [LocationState]
locationStates = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateFleetLocationsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createFleetLocationsResponse_fleetArn :: Lens.Lens' CreateFleetLocationsResponse (Prelude.Maybe Prelude.Text)
createFleetLocationsResponse_fleetArn :: Lens' CreateFleetLocationsResponse (Maybe Text)
createFleetLocationsResponse_fleetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFleetLocationsResponse' {Maybe Text
fleetArn :: Maybe Text
$sel:fleetArn:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Maybe Text
fleetArn} -> Maybe Text
fleetArn) (\s :: CreateFleetLocationsResponse
s@CreateFleetLocationsResponse' {} Maybe Text
a -> CreateFleetLocationsResponse
s {$sel:fleetArn:CreateFleetLocationsResponse' :: Maybe Text
fleetArn = Maybe Text
a} :: CreateFleetLocationsResponse)
createFleetLocationsResponse_fleetId :: Lens.Lens' CreateFleetLocationsResponse (Prelude.Maybe Prelude.Text)
createFleetLocationsResponse_fleetId :: Lens' CreateFleetLocationsResponse (Maybe Text)
createFleetLocationsResponse_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFleetLocationsResponse' {Maybe Text
fleetId :: Maybe Text
$sel:fleetId:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Maybe Text
fleetId} -> Maybe Text
fleetId) (\s :: CreateFleetLocationsResponse
s@CreateFleetLocationsResponse' {} Maybe Text
a -> CreateFleetLocationsResponse
s {$sel:fleetId:CreateFleetLocationsResponse' :: Maybe Text
fleetId = Maybe Text
a} :: CreateFleetLocationsResponse)
createFleetLocationsResponse_locationStates :: Lens.Lens' CreateFleetLocationsResponse (Prelude.Maybe [LocationState])
createFleetLocationsResponse_locationStates :: Lens' CreateFleetLocationsResponse (Maybe [LocationState])
createFleetLocationsResponse_locationStates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFleetLocationsResponse' {Maybe [LocationState]
locationStates :: Maybe [LocationState]
$sel:locationStates:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Maybe [LocationState]
locationStates} -> Maybe [LocationState]
locationStates) (\s :: CreateFleetLocationsResponse
s@CreateFleetLocationsResponse' {} Maybe [LocationState]
a -> CreateFleetLocationsResponse
s {$sel:locationStates:CreateFleetLocationsResponse' :: Maybe [LocationState]
locationStates = Maybe [LocationState]
a} :: CreateFleetLocationsResponse) 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
createFleetLocationsResponse_httpStatus :: Lens.Lens' CreateFleetLocationsResponse Prelude.Int
createFleetLocationsResponse_httpStatus :: Lens' CreateFleetLocationsResponse Int
createFleetLocationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFleetLocationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateFleetLocationsResponse
s@CreateFleetLocationsResponse' {} Int
a -> CreateFleetLocationsResponse
s {$sel:httpStatus:CreateFleetLocationsResponse' :: Int
httpStatus = Int
a} :: CreateFleetLocationsResponse)
instance Prelude.NFData CreateFleetLocationsResponse where
rnf :: CreateFleetLocationsResponse -> ()
rnf CreateFleetLocationsResponse' {Int
Maybe [LocationState]
Maybe Text
httpStatus :: Int
locationStates :: Maybe [LocationState]
fleetId :: Maybe Text
fleetArn :: Maybe Text
$sel:httpStatus:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Int
$sel:locationStates:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Maybe [LocationState]
$sel:fleetId:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Maybe Text
$sel:fleetArn:CreateFleetLocationsResponse' :: CreateFleetLocationsResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fleetArn
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 [LocationState]
locationStates
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus