{-# 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.UpdateFleetAttributes
(
UpdateFleetAttributes (..),
newUpdateFleetAttributes,
updateFleetAttributes_anywhereConfiguration,
updateFleetAttributes_description,
updateFleetAttributes_metricGroups,
updateFleetAttributes_name,
updateFleetAttributes_newGameSessionProtectionPolicy,
updateFleetAttributes_resourceCreationLimitPolicy,
updateFleetAttributes_fleetId,
UpdateFleetAttributesResponse (..),
newUpdateFleetAttributesResponse,
updateFleetAttributesResponse_fleetArn,
updateFleetAttributesResponse_fleetId,
updateFleetAttributesResponse_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 UpdateFleetAttributes = UpdateFleetAttributes'
{
UpdateFleetAttributes -> Maybe AnywhereConfiguration
anywhereConfiguration :: Prelude.Maybe AnywhereConfiguration,
UpdateFleetAttributes -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
UpdateFleetAttributes -> Maybe [Text]
metricGroups :: Prelude.Maybe [Prelude.Text],
UpdateFleetAttributes -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
UpdateFleetAttributes -> Maybe ProtectionPolicy
newGameSessionProtectionPolicy' :: Prelude.Maybe ProtectionPolicy,
UpdateFleetAttributes -> Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy :: Prelude.Maybe ResourceCreationLimitPolicy,
UpdateFleetAttributes -> Text
fleetId :: Prelude.Text
}
deriving (UpdateFleetAttributes -> UpdateFleetAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFleetAttributes -> UpdateFleetAttributes -> Bool
$c/= :: UpdateFleetAttributes -> UpdateFleetAttributes -> Bool
== :: UpdateFleetAttributes -> UpdateFleetAttributes -> Bool
$c== :: UpdateFleetAttributes -> UpdateFleetAttributes -> Bool
Prelude.Eq, ReadPrec [UpdateFleetAttributes]
ReadPrec UpdateFleetAttributes
Int -> ReadS UpdateFleetAttributes
ReadS [UpdateFleetAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFleetAttributes]
$creadListPrec :: ReadPrec [UpdateFleetAttributes]
readPrec :: ReadPrec UpdateFleetAttributes
$creadPrec :: ReadPrec UpdateFleetAttributes
readList :: ReadS [UpdateFleetAttributes]
$creadList :: ReadS [UpdateFleetAttributes]
readsPrec :: Int -> ReadS UpdateFleetAttributes
$creadsPrec :: Int -> ReadS UpdateFleetAttributes
Prelude.Read, Int -> UpdateFleetAttributes -> ShowS
[UpdateFleetAttributes] -> ShowS
UpdateFleetAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFleetAttributes] -> ShowS
$cshowList :: [UpdateFleetAttributes] -> ShowS
show :: UpdateFleetAttributes -> String
$cshow :: UpdateFleetAttributes -> String
showsPrec :: Int -> UpdateFleetAttributes -> ShowS
$cshowsPrec :: Int -> UpdateFleetAttributes -> ShowS
Prelude.Show, forall x. Rep UpdateFleetAttributes x -> UpdateFleetAttributes
forall x. UpdateFleetAttributes -> Rep UpdateFleetAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateFleetAttributes x -> UpdateFleetAttributes
$cfrom :: forall x. UpdateFleetAttributes -> Rep UpdateFleetAttributes x
Prelude.Generic)
newUpdateFleetAttributes ::
Prelude.Text ->
UpdateFleetAttributes
newUpdateFleetAttributes :: Text -> UpdateFleetAttributes
newUpdateFleetAttributes Text
pFleetId_ =
UpdateFleetAttributes'
{ $sel:anywhereConfiguration:UpdateFleetAttributes' :: Maybe AnywhereConfiguration
anywhereConfiguration =
forall a. Maybe a
Prelude.Nothing,
$sel:description:UpdateFleetAttributes' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
$sel:metricGroups:UpdateFleetAttributes' :: Maybe [Text]
metricGroups = forall a. Maybe a
Prelude.Nothing,
$sel:name:UpdateFleetAttributes' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:newGameSessionProtectionPolicy':UpdateFleetAttributes' :: Maybe ProtectionPolicy
newGameSessionProtectionPolicy' = forall a. Maybe a
Prelude.Nothing,
$sel:resourceCreationLimitPolicy:UpdateFleetAttributes' :: Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy = forall a. Maybe a
Prelude.Nothing,
$sel:fleetId:UpdateFleetAttributes' :: Text
fleetId = Text
pFleetId_
}
updateFleetAttributes_anywhereConfiguration :: Lens.Lens' UpdateFleetAttributes (Prelude.Maybe AnywhereConfiguration)
updateFleetAttributes_anywhereConfiguration :: Lens' UpdateFleetAttributes (Maybe AnywhereConfiguration)
updateFleetAttributes_anywhereConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Maybe AnywhereConfiguration
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:anywhereConfiguration:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe AnywhereConfiguration
anywhereConfiguration} -> Maybe AnywhereConfiguration
anywhereConfiguration) (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Maybe AnywhereConfiguration
a -> UpdateFleetAttributes
s {$sel:anywhereConfiguration:UpdateFleetAttributes' :: Maybe AnywhereConfiguration
anywhereConfiguration = Maybe AnywhereConfiguration
a} :: UpdateFleetAttributes)
updateFleetAttributes_description :: Lens.Lens' UpdateFleetAttributes (Prelude.Maybe Prelude.Text)
updateFleetAttributes_description :: Lens' UpdateFleetAttributes (Maybe Text)
updateFleetAttributes_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Maybe Text
description :: Maybe Text
$sel:description:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Maybe Text
a -> UpdateFleetAttributes
s {$sel:description:UpdateFleetAttributes' :: Maybe Text
description = Maybe Text
a} :: UpdateFleetAttributes)
updateFleetAttributes_metricGroups :: Lens.Lens' UpdateFleetAttributes (Prelude.Maybe [Prelude.Text])
updateFleetAttributes_metricGroups :: Lens' UpdateFleetAttributes (Maybe [Text])
updateFleetAttributes_metricGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Maybe [Text]
metricGroups :: Maybe [Text]
$sel:metricGroups:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe [Text]
metricGroups} -> Maybe [Text]
metricGroups) (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Maybe [Text]
a -> UpdateFleetAttributes
s {$sel:metricGroups:UpdateFleetAttributes' :: Maybe [Text]
metricGroups = Maybe [Text]
a} :: UpdateFleetAttributes) 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
updateFleetAttributes_name :: Lens.Lens' UpdateFleetAttributes (Prelude.Maybe Prelude.Text)
updateFleetAttributes_name :: Lens' UpdateFleetAttributes (Maybe Text)
updateFleetAttributes_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Maybe Text
name :: Maybe Text
$sel:name:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Maybe Text
a -> UpdateFleetAttributes
s {$sel:name:UpdateFleetAttributes' :: Maybe Text
name = Maybe Text
a} :: UpdateFleetAttributes)
updateFleetAttributes_newGameSessionProtectionPolicy :: Lens.Lens' UpdateFleetAttributes (Prelude.Maybe ProtectionPolicy)
updateFleetAttributes_newGameSessionProtectionPolicy :: Lens' UpdateFleetAttributes (Maybe ProtectionPolicy)
updateFleetAttributes_newGameSessionProtectionPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Maybe ProtectionPolicy
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
$sel:newGameSessionProtectionPolicy':UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ProtectionPolicy
newGameSessionProtectionPolicy'} -> Maybe ProtectionPolicy
newGameSessionProtectionPolicy') (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Maybe ProtectionPolicy
a -> UpdateFleetAttributes
s {$sel:newGameSessionProtectionPolicy':UpdateFleetAttributes' :: Maybe ProtectionPolicy
newGameSessionProtectionPolicy' = Maybe ProtectionPolicy
a} :: UpdateFleetAttributes)
updateFleetAttributes_resourceCreationLimitPolicy :: Lens.Lens' UpdateFleetAttributes (Prelude.Maybe ResourceCreationLimitPolicy)
updateFleetAttributes_resourceCreationLimitPolicy :: Lens' UpdateFleetAttributes (Maybe ResourceCreationLimitPolicy)
updateFleetAttributes_resourceCreationLimitPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
$sel:resourceCreationLimitPolicy:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy} -> Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy) (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Maybe ResourceCreationLimitPolicy
a -> UpdateFleetAttributes
s {$sel:resourceCreationLimitPolicy:UpdateFleetAttributes' :: Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy = Maybe ResourceCreationLimitPolicy
a} :: UpdateFleetAttributes)
updateFleetAttributes_fleetId :: Lens.Lens' UpdateFleetAttributes Prelude.Text
updateFleetAttributes_fleetId :: Lens' UpdateFleetAttributes Text
updateFleetAttributes_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributes' {Text
fleetId :: Text
$sel:fleetId:UpdateFleetAttributes' :: UpdateFleetAttributes -> Text
fleetId} -> Text
fleetId) (\s :: UpdateFleetAttributes
s@UpdateFleetAttributes' {} Text
a -> UpdateFleetAttributes
s {$sel:fleetId:UpdateFleetAttributes' :: Text
fleetId = Text
a} :: UpdateFleetAttributes)
instance Core.AWSRequest UpdateFleetAttributes where
type
AWSResponse UpdateFleetAttributes =
UpdateFleetAttributesResponse
request :: (Service -> Service)
-> UpdateFleetAttributes -> Request UpdateFleetAttributes
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 UpdateFleetAttributes
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse UpdateFleetAttributes)))
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 -> Int -> UpdateFleetAttributesResponse
UpdateFleetAttributesResponse'
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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable UpdateFleetAttributes where
hashWithSalt :: Int -> UpdateFleetAttributes -> Int
hashWithSalt Int
_salt UpdateFleetAttributes' {Maybe [Text]
Maybe Text
Maybe AnywhereConfiguration
Maybe ProtectionPolicy
Maybe ResourceCreationLimitPolicy
Text
fleetId :: Text
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
name :: Maybe Text
metricGroups :: Maybe [Text]
description :: Maybe Text
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:fleetId:UpdateFleetAttributes' :: UpdateFleetAttributes -> Text
$sel:resourceCreationLimitPolicy:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ResourceCreationLimitPolicy
$sel:newGameSessionProtectionPolicy':UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ProtectionPolicy
$sel:name:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
$sel:metricGroups:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe [Text]
$sel:description:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
$sel:anywhereConfiguration:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe AnywhereConfiguration
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnywhereConfiguration
anywhereConfiguration
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
metricGroups
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProtectionPolicy
newGameSessionProtectionPolicy'
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fleetId
instance Prelude.NFData UpdateFleetAttributes where
rnf :: UpdateFleetAttributes -> ()
rnf UpdateFleetAttributes' {Maybe [Text]
Maybe Text
Maybe AnywhereConfiguration
Maybe ProtectionPolicy
Maybe ResourceCreationLimitPolicy
Text
fleetId :: Text
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
name :: Maybe Text
metricGroups :: Maybe [Text]
description :: Maybe Text
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:fleetId:UpdateFleetAttributes' :: UpdateFleetAttributes -> Text
$sel:resourceCreationLimitPolicy:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ResourceCreationLimitPolicy
$sel:newGameSessionProtectionPolicy':UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ProtectionPolicy
$sel:name:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
$sel:metricGroups:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe [Text]
$sel:description:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
$sel:anywhereConfiguration:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe AnywhereConfiguration
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe AnywhereConfiguration
anywhereConfiguration
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
metricGroups
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProtectionPolicy
newGameSessionProtectionPolicy'
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceCreationLimitPolicy
resourceCreationLimitPolicy
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
fleetId
instance Data.ToHeaders UpdateFleetAttributes where
toHeaders :: UpdateFleetAttributes -> 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.UpdateFleetAttributes" ::
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 UpdateFleetAttributes where
toJSON :: UpdateFleetAttributes -> Value
toJSON UpdateFleetAttributes' {Maybe [Text]
Maybe Text
Maybe AnywhereConfiguration
Maybe ProtectionPolicy
Maybe ResourceCreationLimitPolicy
Text
fleetId :: Text
resourceCreationLimitPolicy :: Maybe ResourceCreationLimitPolicy
newGameSessionProtectionPolicy' :: Maybe ProtectionPolicy
name :: Maybe Text
metricGroups :: Maybe [Text]
description :: Maybe Text
anywhereConfiguration :: Maybe AnywhereConfiguration
$sel:fleetId:UpdateFleetAttributes' :: UpdateFleetAttributes -> Text
$sel:resourceCreationLimitPolicy:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ResourceCreationLimitPolicy
$sel:newGameSessionProtectionPolicy':UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe ProtectionPolicy
$sel:name:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
$sel:metricGroups:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe [Text]
$sel:description:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe Text
$sel:anywhereConfiguration:UpdateFleetAttributes' :: UpdateFleetAttributes -> Maybe AnywhereConfiguration
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"AnywhereConfiguration" 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 AnywhereConfiguration
anywhereConfiguration,
(Key
"Description" 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
description,
(Key
"MetricGroups" 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]
metricGroups,
(Key
"Name" 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
name,
(Key
"NewGameSessionProtectionPolicy" 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 ProtectionPolicy
newGameSessionProtectionPolicy',
(Key
"ResourceCreationLimitPolicy" 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 ResourceCreationLimitPolicy
resourceCreationLimitPolicy,
forall a. a -> Maybe a
Prelude.Just (Key
"FleetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fleetId)
]
)
instance Data.ToPath UpdateFleetAttributes where
toPath :: UpdateFleetAttributes -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery UpdateFleetAttributes where
toQuery :: UpdateFleetAttributes -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateFleetAttributesResponse = UpdateFleetAttributesResponse'
{
UpdateFleetAttributesResponse -> Maybe Text
fleetArn :: Prelude.Maybe Prelude.Text,
UpdateFleetAttributesResponse -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
UpdateFleetAttributesResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateFleetAttributesResponse
-> UpdateFleetAttributesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFleetAttributesResponse
-> UpdateFleetAttributesResponse -> Bool
$c/= :: UpdateFleetAttributesResponse
-> UpdateFleetAttributesResponse -> Bool
== :: UpdateFleetAttributesResponse
-> UpdateFleetAttributesResponse -> Bool
$c== :: UpdateFleetAttributesResponse
-> UpdateFleetAttributesResponse -> Bool
Prelude.Eq, ReadPrec [UpdateFleetAttributesResponse]
ReadPrec UpdateFleetAttributesResponse
Int -> ReadS UpdateFleetAttributesResponse
ReadS [UpdateFleetAttributesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFleetAttributesResponse]
$creadListPrec :: ReadPrec [UpdateFleetAttributesResponse]
readPrec :: ReadPrec UpdateFleetAttributesResponse
$creadPrec :: ReadPrec UpdateFleetAttributesResponse
readList :: ReadS [UpdateFleetAttributesResponse]
$creadList :: ReadS [UpdateFleetAttributesResponse]
readsPrec :: Int -> ReadS UpdateFleetAttributesResponse
$creadsPrec :: Int -> ReadS UpdateFleetAttributesResponse
Prelude.Read, Int -> UpdateFleetAttributesResponse -> ShowS
[UpdateFleetAttributesResponse] -> ShowS
UpdateFleetAttributesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFleetAttributesResponse] -> ShowS
$cshowList :: [UpdateFleetAttributesResponse] -> ShowS
show :: UpdateFleetAttributesResponse -> String
$cshow :: UpdateFleetAttributesResponse -> String
showsPrec :: Int -> UpdateFleetAttributesResponse -> ShowS
$cshowsPrec :: Int -> UpdateFleetAttributesResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateFleetAttributesResponse x
-> UpdateFleetAttributesResponse
forall x.
UpdateFleetAttributesResponse
-> Rep UpdateFleetAttributesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateFleetAttributesResponse x
-> UpdateFleetAttributesResponse
$cfrom :: forall x.
UpdateFleetAttributesResponse
-> Rep UpdateFleetAttributesResponse x
Prelude.Generic)
newUpdateFleetAttributesResponse ::
Prelude.Int ->
UpdateFleetAttributesResponse
newUpdateFleetAttributesResponse :: Int -> UpdateFleetAttributesResponse
newUpdateFleetAttributesResponse Int
pHttpStatus_ =
UpdateFleetAttributesResponse'
{ $sel:fleetArn:UpdateFleetAttributesResponse' :: Maybe Text
fleetArn =
forall a. Maybe a
Prelude.Nothing,
$sel:fleetId:UpdateFleetAttributesResponse' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:UpdateFleetAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
}
updateFleetAttributesResponse_fleetArn :: Lens.Lens' UpdateFleetAttributesResponse (Prelude.Maybe Prelude.Text)
updateFleetAttributesResponse_fleetArn :: Lens' UpdateFleetAttributesResponse (Maybe Text)
updateFleetAttributesResponse_fleetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributesResponse' {Maybe Text
fleetArn :: Maybe Text
$sel:fleetArn:UpdateFleetAttributesResponse' :: UpdateFleetAttributesResponse -> Maybe Text
fleetArn} -> Maybe Text
fleetArn) (\s :: UpdateFleetAttributesResponse
s@UpdateFleetAttributesResponse' {} Maybe Text
a -> UpdateFleetAttributesResponse
s {$sel:fleetArn:UpdateFleetAttributesResponse' :: Maybe Text
fleetArn = Maybe Text
a} :: UpdateFleetAttributesResponse)
updateFleetAttributesResponse_fleetId :: Lens.Lens' UpdateFleetAttributesResponse (Prelude.Maybe Prelude.Text)
updateFleetAttributesResponse_fleetId :: Lens' UpdateFleetAttributesResponse (Maybe Text)
updateFleetAttributesResponse_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributesResponse' {Maybe Text
fleetId :: Maybe Text
$sel:fleetId:UpdateFleetAttributesResponse' :: UpdateFleetAttributesResponse -> Maybe Text
fleetId} -> Maybe Text
fleetId) (\s :: UpdateFleetAttributesResponse
s@UpdateFleetAttributesResponse' {} Maybe Text
a -> UpdateFleetAttributesResponse
s {$sel:fleetId:UpdateFleetAttributesResponse' :: Maybe Text
fleetId = Maybe Text
a} :: UpdateFleetAttributesResponse)
updateFleetAttributesResponse_httpStatus :: Lens.Lens' UpdateFleetAttributesResponse Prelude.Int
updateFleetAttributesResponse_httpStatus :: Lens' UpdateFleetAttributesResponse Int
updateFleetAttributesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFleetAttributesResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateFleetAttributesResponse' :: UpdateFleetAttributesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateFleetAttributesResponse
s@UpdateFleetAttributesResponse' {} Int
a -> UpdateFleetAttributesResponse
s {$sel:httpStatus:UpdateFleetAttributesResponse' :: Int
httpStatus = Int
a} :: UpdateFleetAttributesResponse)
instance Prelude.NFData UpdateFleetAttributesResponse where
rnf :: UpdateFleetAttributesResponse -> ()
rnf UpdateFleetAttributesResponse' {Int
Maybe Text
httpStatus :: Int
fleetId :: Maybe Text
fleetArn :: Maybe Text
$sel:httpStatus:UpdateFleetAttributesResponse' :: UpdateFleetAttributesResponse -> Int
$sel:fleetId:UpdateFleetAttributesResponse' :: UpdateFleetAttributesResponse -> Maybe Text
$sel:fleetArn:UpdateFleetAttributesResponse' :: UpdateFleetAttributesResponse -> 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 Int
httpStatus