{-# 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.EC2.DeleteLocalGatewayRouteTableVpcAssociation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified association between a VPC and local gateway route
-- table.
module Amazonka.EC2.DeleteLocalGatewayRouteTableVpcAssociation
  ( -- * Creating a Request
    DeleteLocalGatewayRouteTableVpcAssociation (..),
    newDeleteLocalGatewayRouteTableVpcAssociation,

    -- * Request Lenses
    deleteLocalGatewayRouteTableVpcAssociation_dryRun,
    deleteLocalGatewayRouteTableVpcAssociation_localGatewayRouteTableVpcAssociationId,

    -- * Destructuring the Response
    DeleteLocalGatewayRouteTableVpcAssociationResponse (..),
    newDeleteLocalGatewayRouteTableVpcAssociationResponse,

    -- * Response Lenses
    deleteLocalGatewayRouteTableVpcAssociationResponse_localGatewayRouteTableVpcAssociation,
    deleteLocalGatewayRouteTableVpcAssociationResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteLocalGatewayRouteTableVpcAssociation' smart constructor.
data DeleteLocalGatewayRouteTableVpcAssociation = DeleteLocalGatewayRouteTableVpcAssociation'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DeleteLocalGatewayRouteTableVpcAssociation -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the association.
    DeleteLocalGatewayRouteTableVpcAssociation -> Text
localGatewayRouteTableVpcAssociationId :: Prelude.Text
  }
  deriving (DeleteLocalGatewayRouteTableVpcAssociation
-> DeleteLocalGatewayRouteTableVpcAssociation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLocalGatewayRouteTableVpcAssociation
-> DeleteLocalGatewayRouteTableVpcAssociation -> Bool
$c/= :: DeleteLocalGatewayRouteTableVpcAssociation
-> DeleteLocalGatewayRouteTableVpcAssociation -> Bool
== :: DeleteLocalGatewayRouteTableVpcAssociation
-> DeleteLocalGatewayRouteTableVpcAssociation -> Bool
$c== :: DeleteLocalGatewayRouteTableVpcAssociation
-> DeleteLocalGatewayRouteTableVpcAssociation -> Bool
Prelude.Eq, ReadPrec [DeleteLocalGatewayRouteTableVpcAssociation]
ReadPrec DeleteLocalGatewayRouteTableVpcAssociation
Int -> ReadS DeleteLocalGatewayRouteTableVpcAssociation
ReadS [DeleteLocalGatewayRouteTableVpcAssociation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLocalGatewayRouteTableVpcAssociation]
$creadListPrec :: ReadPrec [DeleteLocalGatewayRouteTableVpcAssociation]
readPrec :: ReadPrec DeleteLocalGatewayRouteTableVpcAssociation
$creadPrec :: ReadPrec DeleteLocalGatewayRouteTableVpcAssociation
readList :: ReadS [DeleteLocalGatewayRouteTableVpcAssociation]
$creadList :: ReadS [DeleteLocalGatewayRouteTableVpcAssociation]
readsPrec :: Int -> ReadS DeleteLocalGatewayRouteTableVpcAssociation
$creadsPrec :: Int -> ReadS DeleteLocalGatewayRouteTableVpcAssociation
Prelude.Read, Int -> DeleteLocalGatewayRouteTableVpcAssociation -> ShowS
[DeleteLocalGatewayRouteTableVpcAssociation] -> ShowS
DeleteLocalGatewayRouteTableVpcAssociation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLocalGatewayRouteTableVpcAssociation] -> ShowS
$cshowList :: [DeleteLocalGatewayRouteTableVpcAssociation] -> ShowS
show :: DeleteLocalGatewayRouteTableVpcAssociation -> String
$cshow :: DeleteLocalGatewayRouteTableVpcAssociation -> String
showsPrec :: Int -> DeleteLocalGatewayRouteTableVpcAssociation -> ShowS
$cshowsPrec :: Int -> DeleteLocalGatewayRouteTableVpcAssociation -> ShowS
Prelude.Show, forall x.
Rep DeleteLocalGatewayRouteTableVpcAssociation x
-> DeleteLocalGatewayRouteTableVpcAssociation
forall x.
DeleteLocalGatewayRouteTableVpcAssociation
-> Rep DeleteLocalGatewayRouteTableVpcAssociation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteLocalGatewayRouteTableVpcAssociation x
-> DeleteLocalGatewayRouteTableVpcAssociation
$cfrom :: forall x.
DeleteLocalGatewayRouteTableVpcAssociation
-> Rep DeleteLocalGatewayRouteTableVpcAssociation x
Prelude.Generic)

-- |
-- Create a value of 'DeleteLocalGatewayRouteTableVpcAssociation' 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:
--
-- 'dryRun', 'deleteLocalGatewayRouteTableVpcAssociation_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'localGatewayRouteTableVpcAssociationId', 'deleteLocalGatewayRouteTableVpcAssociation_localGatewayRouteTableVpcAssociationId' - The ID of the association.
newDeleteLocalGatewayRouteTableVpcAssociation ::
  -- | 'localGatewayRouteTableVpcAssociationId'
  Prelude.Text ->
  DeleteLocalGatewayRouteTableVpcAssociation
newDeleteLocalGatewayRouteTableVpcAssociation :: Text -> DeleteLocalGatewayRouteTableVpcAssociation
newDeleteLocalGatewayRouteTableVpcAssociation
  Text
pLocalGatewayRouteTableVpcAssociationId_ =
    DeleteLocalGatewayRouteTableVpcAssociation'
      { $sel:dryRun:DeleteLocalGatewayRouteTableVpcAssociation' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:localGatewayRouteTableVpcAssociationId:DeleteLocalGatewayRouteTableVpcAssociation' :: Text
localGatewayRouteTableVpcAssociationId =
          Text
pLocalGatewayRouteTableVpcAssociationId_
      }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
deleteLocalGatewayRouteTableVpcAssociation_dryRun :: Lens.Lens' DeleteLocalGatewayRouteTableVpcAssociation (Prelude.Maybe Prelude.Bool)
deleteLocalGatewayRouteTableVpcAssociation_dryRun :: Lens' DeleteLocalGatewayRouteTableVpcAssociation (Maybe Bool)
deleteLocalGatewayRouteTableVpcAssociation_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLocalGatewayRouteTableVpcAssociation' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteLocalGatewayRouteTableVpcAssociation
s@DeleteLocalGatewayRouteTableVpcAssociation' {} Maybe Bool
a -> DeleteLocalGatewayRouteTableVpcAssociation
s {$sel:dryRun:DeleteLocalGatewayRouteTableVpcAssociation' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteLocalGatewayRouteTableVpcAssociation)

-- | The ID of the association.
deleteLocalGatewayRouteTableVpcAssociation_localGatewayRouteTableVpcAssociationId :: Lens.Lens' DeleteLocalGatewayRouteTableVpcAssociation Prelude.Text
deleteLocalGatewayRouteTableVpcAssociation_localGatewayRouteTableVpcAssociationId :: Lens' DeleteLocalGatewayRouteTableVpcAssociation Text
deleteLocalGatewayRouteTableVpcAssociation_localGatewayRouteTableVpcAssociationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLocalGatewayRouteTableVpcAssociation' {Text
localGatewayRouteTableVpcAssociationId :: Text
$sel:localGatewayRouteTableVpcAssociationId:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Text
localGatewayRouteTableVpcAssociationId} -> Text
localGatewayRouteTableVpcAssociationId) (\s :: DeleteLocalGatewayRouteTableVpcAssociation
s@DeleteLocalGatewayRouteTableVpcAssociation' {} Text
a -> DeleteLocalGatewayRouteTableVpcAssociation
s {$sel:localGatewayRouteTableVpcAssociationId:DeleteLocalGatewayRouteTableVpcAssociation' :: Text
localGatewayRouteTableVpcAssociationId = Text
a} :: DeleteLocalGatewayRouteTableVpcAssociation)

instance
  Core.AWSRequest
    DeleteLocalGatewayRouteTableVpcAssociation
  where
  type
    AWSResponse
      DeleteLocalGatewayRouteTableVpcAssociation =
      DeleteLocalGatewayRouteTableVpcAssociationResponse
  request :: (Service -> Service)
-> DeleteLocalGatewayRouteTableVpcAssociation
-> Request DeleteLocalGatewayRouteTableVpcAssociation
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteLocalGatewayRouteTableVpcAssociation
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DeleteLocalGatewayRouteTableVpcAssociation)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe LocalGatewayRouteTableVpcAssociation
-> Int -> DeleteLocalGatewayRouteTableVpcAssociationResponse
DeleteLocalGatewayRouteTableVpcAssociationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"localGatewayRouteTableVpcAssociation")
            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
    DeleteLocalGatewayRouteTableVpcAssociation
  where
  hashWithSalt :: Int -> DeleteLocalGatewayRouteTableVpcAssociation -> Int
hashWithSalt
    Int
_salt
    DeleteLocalGatewayRouteTableVpcAssociation' {Maybe Bool
Text
localGatewayRouteTableVpcAssociationId :: Text
dryRun :: Maybe Bool
$sel:localGatewayRouteTableVpcAssociationId:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Text
$sel:dryRun:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Maybe Bool
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
localGatewayRouteTableVpcAssociationId

instance
  Prelude.NFData
    DeleteLocalGatewayRouteTableVpcAssociation
  where
  rnf :: DeleteLocalGatewayRouteTableVpcAssociation -> ()
rnf DeleteLocalGatewayRouteTableVpcAssociation' {Maybe Bool
Text
localGatewayRouteTableVpcAssociationId :: Text
dryRun :: Maybe Bool
$sel:localGatewayRouteTableVpcAssociationId:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Text
$sel:dryRun:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
localGatewayRouteTableVpcAssociationId

instance
  Data.ToHeaders
    DeleteLocalGatewayRouteTableVpcAssociation
  where
  toHeaders :: DeleteLocalGatewayRouteTableVpcAssociation -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    DeleteLocalGatewayRouteTableVpcAssociation
  where
  toQuery :: DeleteLocalGatewayRouteTableVpcAssociation -> QueryString
toQuery
    DeleteLocalGatewayRouteTableVpcAssociation' {Maybe Bool
Text
localGatewayRouteTableVpcAssociationId :: Text
dryRun :: Maybe Bool
$sel:localGatewayRouteTableVpcAssociationId:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Text
$sel:dryRun:DeleteLocalGatewayRouteTableVpcAssociation' :: DeleteLocalGatewayRouteTableVpcAssociation -> Maybe Bool
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ ByteString
"Action"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteLocalGatewayRouteTableVpcAssociation" ::
                        Prelude.ByteString
                    ),
          ByteString
"Version"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
          ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
          ByteString
"LocalGatewayRouteTableVpcAssociationId"
            forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
localGatewayRouteTableVpcAssociationId
        ]

-- | /See:/ 'newDeleteLocalGatewayRouteTableVpcAssociationResponse' smart constructor.
data DeleteLocalGatewayRouteTableVpcAssociationResponse = DeleteLocalGatewayRouteTableVpcAssociationResponse'
  { -- | Information about the association.
    DeleteLocalGatewayRouteTableVpcAssociationResponse
-> Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation :: Prelude.Maybe LocalGatewayRouteTableVpcAssociation,
    -- | The response's http status code.
    DeleteLocalGatewayRouteTableVpcAssociationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteLocalGatewayRouteTableVpcAssociationResponse
-> DeleteLocalGatewayRouteTableVpcAssociationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLocalGatewayRouteTableVpcAssociationResponse
-> DeleteLocalGatewayRouteTableVpcAssociationResponse -> Bool
$c/= :: DeleteLocalGatewayRouteTableVpcAssociationResponse
-> DeleteLocalGatewayRouteTableVpcAssociationResponse -> Bool
== :: DeleteLocalGatewayRouteTableVpcAssociationResponse
-> DeleteLocalGatewayRouteTableVpcAssociationResponse -> Bool
$c== :: DeleteLocalGatewayRouteTableVpcAssociationResponse
-> DeleteLocalGatewayRouteTableVpcAssociationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteLocalGatewayRouteTableVpcAssociationResponse]
ReadPrec DeleteLocalGatewayRouteTableVpcAssociationResponse
Int -> ReadS DeleteLocalGatewayRouteTableVpcAssociationResponse
ReadS [DeleteLocalGatewayRouteTableVpcAssociationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLocalGatewayRouteTableVpcAssociationResponse]
$creadListPrec :: ReadPrec [DeleteLocalGatewayRouteTableVpcAssociationResponse]
readPrec :: ReadPrec DeleteLocalGatewayRouteTableVpcAssociationResponse
$creadPrec :: ReadPrec DeleteLocalGatewayRouteTableVpcAssociationResponse
readList :: ReadS [DeleteLocalGatewayRouteTableVpcAssociationResponse]
$creadList :: ReadS [DeleteLocalGatewayRouteTableVpcAssociationResponse]
readsPrec :: Int -> ReadS DeleteLocalGatewayRouteTableVpcAssociationResponse
$creadsPrec :: Int -> ReadS DeleteLocalGatewayRouteTableVpcAssociationResponse
Prelude.Read, Int -> DeleteLocalGatewayRouteTableVpcAssociationResponse -> ShowS
[DeleteLocalGatewayRouteTableVpcAssociationResponse] -> ShowS
DeleteLocalGatewayRouteTableVpcAssociationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLocalGatewayRouteTableVpcAssociationResponse] -> ShowS
$cshowList :: [DeleteLocalGatewayRouteTableVpcAssociationResponse] -> ShowS
show :: DeleteLocalGatewayRouteTableVpcAssociationResponse -> String
$cshow :: DeleteLocalGatewayRouteTableVpcAssociationResponse -> String
showsPrec :: Int -> DeleteLocalGatewayRouteTableVpcAssociationResponse -> ShowS
$cshowsPrec :: Int -> DeleteLocalGatewayRouteTableVpcAssociationResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteLocalGatewayRouteTableVpcAssociationResponse x
-> DeleteLocalGatewayRouteTableVpcAssociationResponse
forall x.
DeleteLocalGatewayRouteTableVpcAssociationResponse
-> Rep DeleteLocalGatewayRouteTableVpcAssociationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteLocalGatewayRouteTableVpcAssociationResponse x
-> DeleteLocalGatewayRouteTableVpcAssociationResponse
$cfrom :: forall x.
DeleteLocalGatewayRouteTableVpcAssociationResponse
-> Rep DeleteLocalGatewayRouteTableVpcAssociationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteLocalGatewayRouteTableVpcAssociationResponse' 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:
--
-- 'localGatewayRouteTableVpcAssociation', 'deleteLocalGatewayRouteTableVpcAssociationResponse_localGatewayRouteTableVpcAssociation' - Information about the association.
--
-- 'httpStatus', 'deleteLocalGatewayRouteTableVpcAssociationResponse_httpStatus' - The response's http status code.
newDeleteLocalGatewayRouteTableVpcAssociationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteLocalGatewayRouteTableVpcAssociationResponse
newDeleteLocalGatewayRouteTableVpcAssociationResponse :: Int -> DeleteLocalGatewayRouteTableVpcAssociationResponse
newDeleteLocalGatewayRouteTableVpcAssociationResponse
  Int
pHttpStatus_ =
    DeleteLocalGatewayRouteTableVpcAssociationResponse'
      { $sel:localGatewayRouteTableVpcAssociation:DeleteLocalGatewayRouteTableVpcAssociationResponse' :: Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DeleteLocalGatewayRouteTableVpcAssociationResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | Information about the association.
deleteLocalGatewayRouteTableVpcAssociationResponse_localGatewayRouteTableVpcAssociation :: Lens.Lens' DeleteLocalGatewayRouteTableVpcAssociationResponse (Prelude.Maybe LocalGatewayRouteTableVpcAssociation)
deleteLocalGatewayRouteTableVpcAssociationResponse_localGatewayRouteTableVpcAssociation :: Lens'
  DeleteLocalGatewayRouteTableVpcAssociationResponse
  (Maybe LocalGatewayRouteTableVpcAssociation)
deleteLocalGatewayRouteTableVpcAssociationResponse_localGatewayRouteTableVpcAssociation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLocalGatewayRouteTableVpcAssociationResponse' {Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation :: Maybe LocalGatewayRouteTableVpcAssociation
$sel:localGatewayRouteTableVpcAssociation:DeleteLocalGatewayRouteTableVpcAssociationResponse' :: DeleteLocalGatewayRouteTableVpcAssociationResponse
-> Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation} -> Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation) (\s :: DeleteLocalGatewayRouteTableVpcAssociationResponse
s@DeleteLocalGatewayRouteTableVpcAssociationResponse' {} Maybe LocalGatewayRouteTableVpcAssociation
a -> DeleteLocalGatewayRouteTableVpcAssociationResponse
s {$sel:localGatewayRouteTableVpcAssociation:DeleteLocalGatewayRouteTableVpcAssociationResponse' :: Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation = Maybe LocalGatewayRouteTableVpcAssociation
a} :: DeleteLocalGatewayRouteTableVpcAssociationResponse)

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

instance
  Prelude.NFData
    DeleteLocalGatewayRouteTableVpcAssociationResponse
  where
  rnf :: DeleteLocalGatewayRouteTableVpcAssociationResponse -> ()
rnf
    DeleteLocalGatewayRouteTableVpcAssociationResponse' {Int
Maybe LocalGatewayRouteTableVpcAssociation
httpStatus :: Int
localGatewayRouteTableVpcAssociation :: Maybe LocalGatewayRouteTableVpcAssociation
$sel:httpStatus:DeleteLocalGatewayRouteTableVpcAssociationResponse' :: DeleteLocalGatewayRouteTableVpcAssociationResponse -> Int
$sel:localGatewayRouteTableVpcAssociation:DeleteLocalGatewayRouteTableVpcAssociationResponse' :: DeleteLocalGatewayRouteTableVpcAssociationResponse
-> Maybe LocalGatewayRouteTableVpcAssociation
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe LocalGatewayRouteTableVpcAssociation
localGatewayRouteTableVpcAssociation
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus