{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.GameLift.DeleteFleetLocations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes locations from a multi-location fleet. When deleting a location,
-- all game server process and all instances that are still active in the
-- location are shut down.
--
-- To delete fleet locations, identify the fleet ID and provide a list of
-- the locations to be deleted.
--
-- If successful, GameLift sets the location status to @DELETING@, and
-- begins to shut down existing server processes and terminate instances in
-- each location being deleted. When completed, the location status changes
-- to @TERMINATED@.
--
-- __Learn more__
--
-- <https://docs.aws.amazon.com/gamelift/latest/developerguide/fleets-intro.html Setting up GameLift fleets>
module Amazonka.GameLift.DeleteFleetLocations
  ( -- * Creating a Request
    DeleteFleetLocations (..),
    newDeleteFleetLocations,

    -- * Request Lenses
    deleteFleetLocations_fleetId,
    deleteFleetLocations_locations,

    -- * Destructuring the Response
    DeleteFleetLocationsResponse (..),
    newDeleteFleetLocationsResponse,

    -- * Response Lenses
    deleteFleetLocationsResponse_fleetArn,
    deleteFleetLocationsResponse_fleetId,
    deleteFleetLocationsResponse_locationStates,
    deleteFleetLocationsResponse_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

-- | /See:/ 'newDeleteFleetLocations' smart constructor.
data DeleteFleetLocations = DeleteFleetLocations'
  { -- | A unique identifier for the fleet to delete locations for. You can use
    -- either the fleet ID or ARN value.
    DeleteFleetLocations -> Text
fleetId :: Prelude.Text,
    -- | The list of fleet locations to delete. Specify locations in the form of
    -- an Amazon Web Services Region code, such as @us-west-2@.
    DeleteFleetLocations -> NonEmpty Text
locations :: Prelude.NonEmpty Prelude.Text
  }
  deriving (DeleteFleetLocations -> DeleteFleetLocations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFleetLocations -> DeleteFleetLocations -> Bool
$c/= :: DeleteFleetLocations -> DeleteFleetLocations -> Bool
== :: DeleteFleetLocations -> DeleteFleetLocations -> Bool
$c== :: DeleteFleetLocations -> DeleteFleetLocations -> Bool
Prelude.Eq, ReadPrec [DeleteFleetLocations]
ReadPrec DeleteFleetLocations
Int -> ReadS DeleteFleetLocations
ReadS [DeleteFleetLocations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFleetLocations]
$creadListPrec :: ReadPrec [DeleteFleetLocations]
readPrec :: ReadPrec DeleteFleetLocations
$creadPrec :: ReadPrec DeleteFleetLocations
readList :: ReadS [DeleteFleetLocations]
$creadList :: ReadS [DeleteFleetLocations]
readsPrec :: Int -> ReadS DeleteFleetLocations
$creadsPrec :: Int -> ReadS DeleteFleetLocations
Prelude.Read, Int -> DeleteFleetLocations -> ShowS
[DeleteFleetLocations] -> ShowS
DeleteFleetLocations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFleetLocations] -> ShowS
$cshowList :: [DeleteFleetLocations] -> ShowS
show :: DeleteFleetLocations -> String
$cshow :: DeleteFleetLocations -> String
showsPrec :: Int -> DeleteFleetLocations -> ShowS
$cshowsPrec :: Int -> DeleteFleetLocations -> ShowS
Prelude.Show, forall x. Rep DeleteFleetLocations x -> DeleteFleetLocations
forall x. DeleteFleetLocations -> Rep DeleteFleetLocations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFleetLocations x -> DeleteFleetLocations
$cfrom :: forall x. DeleteFleetLocations -> Rep DeleteFleetLocations x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFleetLocations' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'fleetId', 'deleteFleetLocations_fleetId' - A unique identifier for the fleet to delete locations for. You can use
-- either the fleet ID or ARN value.
--
-- 'locations', 'deleteFleetLocations_locations' - The list of fleet locations to delete. Specify locations in the form of
-- an Amazon Web Services Region code, such as @us-west-2@.
newDeleteFleetLocations ::
  -- | 'fleetId'
  Prelude.Text ->
  -- | 'locations'
  Prelude.NonEmpty Prelude.Text ->
  DeleteFleetLocations
newDeleteFleetLocations :: Text -> NonEmpty Text -> DeleteFleetLocations
newDeleteFleetLocations Text
pFleetId_ NonEmpty Text
pLocations_ =
  DeleteFleetLocations'
    { $sel:fleetId:DeleteFleetLocations' :: Text
fleetId = Text
pFleetId_,
      $sel:locations:DeleteFleetLocations' :: NonEmpty Text
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 Text
pLocations_
    }

-- | A unique identifier for the fleet to delete locations for. You can use
-- either the fleet ID or ARN value.
deleteFleetLocations_fleetId :: Lens.Lens' DeleteFleetLocations Prelude.Text
deleteFleetLocations_fleetId :: Lens' DeleteFleetLocations Text
deleteFleetLocations_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFleetLocations' {Text
fleetId :: Text
$sel:fleetId:DeleteFleetLocations' :: DeleteFleetLocations -> Text
fleetId} -> Text
fleetId) (\s :: DeleteFleetLocations
s@DeleteFleetLocations' {} Text
a -> DeleteFleetLocations
s {$sel:fleetId:DeleteFleetLocations' :: Text
fleetId = Text
a} :: DeleteFleetLocations)

-- | The list of fleet locations to delete. Specify locations in the form of
-- an Amazon Web Services Region code, such as @us-west-2@.
deleteFleetLocations_locations :: Lens.Lens' DeleteFleetLocations (Prelude.NonEmpty Prelude.Text)
deleteFleetLocations_locations :: Lens' DeleteFleetLocations (NonEmpty Text)
deleteFleetLocations_locations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFleetLocations' {NonEmpty Text
locations :: NonEmpty Text
$sel:locations:DeleteFleetLocations' :: DeleteFleetLocations -> NonEmpty Text
locations} -> NonEmpty Text
locations) (\s :: DeleteFleetLocations
s@DeleteFleetLocations' {} NonEmpty Text
a -> DeleteFleetLocations
s {$sel:locations:DeleteFleetLocations' :: NonEmpty Text
locations = NonEmpty Text
a} :: DeleteFleetLocations) 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 DeleteFleetLocations where
  type
    AWSResponse DeleteFleetLocations =
      DeleteFleetLocationsResponse
  request :: (Service -> Service)
-> DeleteFleetLocations -> Request DeleteFleetLocations
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 DeleteFleetLocations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteFleetLocations)))
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
-> DeleteFleetLocationsResponse
DeleteFleetLocationsResponse'
            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 DeleteFleetLocations where
  hashWithSalt :: Int -> DeleteFleetLocations -> Int
hashWithSalt Int
_salt DeleteFleetLocations' {NonEmpty Text
Text
locations :: NonEmpty Text
fleetId :: Text
$sel:locations:DeleteFleetLocations' :: DeleteFleetLocations -> NonEmpty Text
$sel:fleetId:DeleteFleetLocations' :: DeleteFleetLocations -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
fleetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
locations

instance Prelude.NFData DeleteFleetLocations where
  rnf :: DeleteFleetLocations -> ()
rnf DeleteFleetLocations' {NonEmpty Text
Text
locations :: NonEmpty Text
fleetId :: Text
$sel:locations:DeleteFleetLocations' :: DeleteFleetLocations -> NonEmpty Text
$sel:fleetId:DeleteFleetLocations' :: DeleteFleetLocations -> 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 Text
locations

instance Data.ToHeaders DeleteFleetLocations where
  toHeaders :: DeleteFleetLocations -> 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.DeleteFleetLocations" ::
                          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 DeleteFleetLocations where
  toJSON :: DeleteFleetLocations -> Value
toJSON DeleteFleetLocations' {NonEmpty Text
Text
locations :: NonEmpty Text
fleetId :: Text
$sel:locations:DeleteFleetLocations' :: DeleteFleetLocations -> NonEmpty Text
$sel:fleetId:DeleteFleetLocations' :: DeleteFleetLocations -> 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 Text
locations)
          ]
      )

instance Data.ToPath DeleteFleetLocations where
  toPath :: DeleteFleetLocations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DeleteFleetLocations where
  toQuery :: DeleteFleetLocations -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDeleteFleetLocationsResponse' smart constructor.
data DeleteFleetLocationsResponse = DeleteFleetLocationsResponse'
  { -- | The Amazon Resource Name
    -- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
    -- that is assigned to a GameLift fleet resource and uniquely identifies
    -- it. ARNs are unique across all Regions. Format is
    -- @arn:aws:gamelift:\<region>::fleet\/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912@.
    DeleteFleetLocationsResponse -> Maybe Text
fleetArn :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the fleet that location attributes are being
    -- deleted for.
    DeleteFleetLocationsResponse -> Maybe Text
fleetId :: Prelude.Maybe Prelude.Text,
    -- | The remote locations that are being deleted, with each location status
    -- set to @DELETING@.
    DeleteFleetLocationsResponse -> Maybe [LocationState]
locationStates :: Prelude.Maybe [LocationState],
    -- | The response's http status code.
    DeleteFleetLocationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteFleetLocationsResponse
-> DeleteFleetLocationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFleetLocationsResponse
-> DeleteFleetLocationsResponse -> Bool
$c/= :: DeleteFleetLocationsResponse
-> DeleteFleetLocationsResponse -> Bool
== :: DeleteFleetLocationsResponse
-> DeleteFleetLocationsResponse -> Bool
$c== :: DeleteFleetLocationsResponse
-> DeleteFleetLocationsResponse -> Bool
Prelude.Eq, ReadPrec [DeleteFleetLocationsResponse]
ReadPrec DeleteFleetLocationsResponse
Int -> ReadS DeleteFleetLocationsResponse
ReadS [DeleteFleetLocationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFleetLocationsResponse]
$creadListPrec :: ReadPrec [DeleteFleetLocationsResponse]
readPrec :: ReadPrec DeleteFleetLocationsResponse
$creadPrec :: ReadPrec DeleteFleetLocationsResponse
readList :: ReadS [DeleteFleetLocationsResponse]
$creadList :: ReadS [DeleteFleetLocationsResponse]
readsPrec :: Int -> ReadS DeleteFleetLocationsResponse
$creadsPrec :: Int -> ReadS DeleteFleetLocationsResponse
Prelude.Read, Int -> DeleteFleetLocationsResponse -> ShowS
[DeleteFleetLocationsResponse] -> ShowS
DeleteFleetLocationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFleetLocationsResponse] -> ShowS
$cshowList :: [DeleteFleetLocationsResponse] -> ShowS
show :: DeleteFleetLocationsResponse -> String
$cshow :: DeleteFleetLocationsResponse -> String
showsPrec :: Int -> DeleteFleetLocationsResponse -> ShowS
$cshowsPrec :: Int -> DeleteFleetLocationsResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteFleetLocationsResponse x -> DeleteFleetLocationsResponse
forall x.
DeleteFleetLocationsResponse -> Rep DeleteFleetLocationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteFleetLocationsResponse x -> DeleteFleetLocationsResponse
$cfrom :: forall x.
DeleteFleetLocationsResponse -> Rep DeleteFleetLocationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFleetLocationsResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'fleetArn', 'deleteFleetLocationsResponse_fleetArn' - The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- that is assigned to a GameLift fleet resource and uniquely identifies
-- it. ARNs are unique across all Regions. Format is
-- @arn:aws:gamelift:\<region>::fleet\/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912@.
--
-- 'fleetId', 'deleteFleetLocationsResponse_fleetId' - A unique identifier for the fleet that location attributes are being
-- deleted for.
--
-- 'locationStates', 'deleteFleetLocationsResponse_locationStates' - The remote locations that are being deleted, with each location status
-- set to @DELETING@.
--
-- 'httpStatus', 'deleteFleetLocationsResponse_httpStatus' - The response's http status code.
newDeleteFleetLocationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteFleetLocationsResponse
newDeleteFleetLocationsResponse :: Int -> DeleteFleetLocationsResponse
newDeleteFleetLocationsResponse Int
pHttpStatus_ =
  DeleteFleetLocationsResponse'
    { $sel:fleetArn:DeleteFleetLocationsResponse' :: Maybe Text
fleetArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:fleetId:DeleteFleetLocationsResponse' :: Maybe Text
fleetId = forall a. Maybe a
Prelude.Nothing,
      $sel:locationStates:DeleteFleetLocationsResponse' :: Maybe [LocationState]
locationStates = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteFleetLocationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name
-- (<https://docs.aws.amazon.com/AmazonS3/latest/dev/s3-arn-format.html ARN>)
-- that is assigned to a GameLift fleet resource and uniquely identifies
-- it. ARNs are unique across all Regions. Format is
-- @arn:aws:gamelift:\<region>::fleet\/fleet-a1234567-b8c9-0d1e-2fa3-b45c6d7e8912@.
deleteFleetLocationsResponse_fleetArn :: Lens.Lens' DeleteFleetLocationsResponse (Prelude.Maybe Prelude.Text)
deleteFleetLocationsResponse_fleetArn :: Lens' DeleteFleetLocationsResponse (Maybe Text)
deleteFleetLocationsResponse_fleetArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFleetLocationsResponse' {Maybe Text
fleetArn :: Maybe Text
$sel:fleetArn:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Maybe Text
fleetArn} -> Maybe Text
fleetArn) (\s :: DeleteFleetLocationsResponse
s@DeleteFleetLocationsResponse' {} Maybe Text
a -> DeleteFleetLocationsResponse
s {$sel:fleetArn:DeleteFleetLocationsResponse' :: Maybe Text
fleetArn = Maybe Text
a} :: DeleteFleetLocationsResponse)

-- | A unique identifier for the fleet that location attributes are being
-- deleted for.
deleteFleetLocationsResponse_fleetId :: Lens.Lens' DeleteFleetLocationsResponse (Prelude.Maybe Prelude.Text)
deleteFleetLocationsResponse_fleetId :: Lens' DeleteFleetLocationsResponse (Maybe Text)
deleteFleetLocationsResponse_fleetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFleetLocationsResponse' {Maybe Text
fleetId :: Maybe Text
$sel:fleetId:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Maybe Text
fleetId} -> Maybe Text
fleetId) (\s :: DeleteFleetLocationsResponse
s@DeleteFleetLocationsResponse' {} Maybe Text
a -> DeleteFleetLocationsResponse
s {$sel:fleetId:DeleteFleetLocationsResponse' :: Maybe Text
fleetId = Maybe Text
a} :: DeleteFleetLocationsResponse)

-- | The remote locations that are being deleted, with each location status
-- set to @DELETING@.
deleteFleetLocationsResponse_locationStates :: Lens.Lens' DeleteFleetLocationsResponse (Prelude.Maybe [LocationState])
deleteFleetLocationsResponse_locationStates :: Lens' DeleteFleetLocationsResponse (Maybe [LocationState])
deleteFleetLocationsResponse_locationStates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFleetLocationsResponse' {Maybe [LocationState]
locationStates :: Maybe [LocationState]
$sel:locationStates:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Maybe [LocationState]
locationStates} -> Maybe [LocationState]
locationStates) (\s :: DeleteFleetLocationsResponse
s@DeleteFleetLocationsResponse' {} Maybe [LocationState]
a -> DeleteFleetLocationsResponse
s {$sel:locationStates:DeleteFleetLocationsResponse' :: Maybe [LocationState]
locationStates = Maybe [LocationState]
a} :: DeleteFleetLocationsResponse) 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

-- | The response's http status code.
deleteFleetLocationsResponse_httpStatus :: Lens.Lens' DeleteFleetLocationsResponse Prelude.Int
deleteFleetLocationsResponse_httpStatus :: Lens' DeleteFleetLocationsResponse Int
deleteFleetLocationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFleetLocationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteFleetLocationsResponse
s@DeleteFleetLocationsResponse' {} Int
a -> DeleteFleetLocationsResponse
s {$sel:httpStatus:DeleteFleetLocationsResponse' :: Int
httpStatus = Int
a} :: DeleteFleetLocationsResponse)

instance Prelude.NFData DeleteFleetLocationsResponse where
  rnf :: DeleteFleetLocationsResponse -> ()
rnf DeleteFleetLocationsResponse' {Int
Maybe [LocationState]
Maybe Text
httpStatus :: Int
locationStates :: Maybe [LocationState]
fleetId :: Maybe Text
fleetArn :: Maybe Text
$sel:httpStatus:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Int
$sel:locationStates:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Maybe [LocationState]
$sel:fleetId:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> Maybe Text
$sel:fleetArn:DeleteFleetLocationsResponse' :: DeleteFleetLocationsResponse -> 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