{-# 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.DeleteTransitGatewayPrefixListReference
-- 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 a reference (route) to a prefix list in a specified transit
-- gateway route table.
module Amazonka.EC2.DeleteTransitGatewayPrefixListReference
  ( -- * Creating a Request
    DeleteTransitGatewayPrefixListReference (..),
    newDeleteTransitGatewayPrefixListReference,

    -- * Request Lenses
    deleteTransitGatewayPrefixListReference_dryRun,
    deleteTransitGatewayPrefixListReference_transitGatewayRouteTableId,
    deleteTransitGatewayPrefixListReference_prefixListId,

    -- * Destructuring the Response
    DeleteTransitGatewayPrefixListReferenceResponse (..),
    newDeleteTransitGatewayPrefixListReferenceResponse,

    -- * Response Lenses
    deleteTransitGatewayPrefixListReferenceResponse_transitGatewayPrefixListReference,
    deleteTransitGatewayPrefixListReferenceResponse_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:/ 'newDeleteTransitGatewayPrefixListReference' smart constructor.
data DeleteTransitGatewayPrefixListReference = DeleteTransitGatewayPrefixListReference'
  { -- | 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@.
    DeleteTransitGatewayPrefixListReference -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the route table.
    DeleteTransitGatewayPrefixListReference -> Text
transitGatewayRouteTableId :: Prelude.Text,
    -- | The ID of the prefix list.
    DeleteTransitGatewayPrefixListReference -> Text
prefixListId :: Prelude.Text
  }
  deriving (DeleteTransitGatewayPrefixListReference
-> DeleteTransitGatewayPrefixListReference -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteTransitGatewayPrefixListReference
-> DeleteTransitGatewayPrefixListReference -> Bool
$c/= :: DeleteTransitGatewayPrefixListReference
-> DeleteTransitGatewayPrefixListReference -> Bool
== :: DeleteTransitGatewayPrefixListReference
-> DeleteTransitGatewayPrefixListReference -> Bool
$c== :: DeleteTransitGatewayPrefixListReference
-> DeleteTransitGatewayPrefixListReference -> Bool
Prelude.Eq, ReadPrec [DeleteTransitGatewayPrefixListReference]
ReadPrec DeleteTransitGatewayPrefixListReference
Int -> ReadS DeleteTransitGatewayPrefixListReference
ReadS [DeleteTransitGatewayPrefixListReference]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteTransitGatewayPrefixListReference]
$creadListPrec :: ReadPrec [DeleteTransitGatewayPrefixListReference]
readPrec :: ReadPrec DeleteTransitGatewayPrefixListReference
$creadPrec :: ReadPrec DeleteTransitGatewayPrefixListReference
readList :: ReadS [DeleteTransitGatewayPrefixListReference]
$creadList :: ReadS [DeleteTransitGatewayPrefixListReference]
readsPrec :: Int -> ReadS DeleteTransitGatewayPrefixListReference
$creadsPrec :: Int -> ReadS DeleteTransitGatewayPrefixListReference
Prelude.Read, Int -> DeleteTransitGatewayPrefixListReference -> ShowS
[DeleteTransitGatewayPrefixListReference] -> ShowS
DeleteTransitGatewayPrefixListReference -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteTransitGatewayPrefixListReference] -> ShowS
$cshowList :: [DeleteTransitGatewayPrefixListReference] -> ShowS
show :: DeleteTransitGatewayPrefixListReference -> String
$cshow :: DeleteTransitGatewayPrefixListReference -> String
showsPrec :: Int -> DeleteTransitGatewayPrefixListReference -> ShowS
$cshowsPrec :: Int -> DeleteTransitGatewayPrefixListReference -> ShowS
Prelude.Show, forall x.
Rep DeleteTransitGatewayPrefixListReference x
-> DeleteTransitGatewayPrefixListReference
forall x.
DeleteTransitGatewayPrefixListReference
-> Rep DeleteTransitGatewayPrefixListReference x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteTransitGatewayPrefixListReference x
-> DeleteTransitGatewayPrefixListReference
$cfrom :: forall x.
DeleteTransitGatewayPrefixListReference
-> Rep DeleteTransitGatewayPrefixListReference x
Prelude.Generic)

-- |
-- Create a value of 'DeleteTransitGatewayPrefixListReference' 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', 'deleteTransitGatewayPrefixListReference_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@.
--
-- 'transitGatewayRouteTableId', 'deleteTransitGatewayPrefixListReference_transitGatewayRouteTableId' - The ID of the route table.
--
-- 'prefixListId', 'deleteTransitGatewayPrefixListReference_prefixListId' - The ID of the prefix list.
newDeleteTransitGatewayPrefixListReference ::
  -- | 'transitGatewayRouteTableId'
  Prelude.Text ->
  -- | 'prefixListId'
  Prelude.Text ->
  DeleteTransitGatewayPrefixListReference
newDeleteTransitGatewayPrefixListReference :: Text -> Text -> DeleteTransitGatewayPrefixListReference
newDeleteTransitGatewayPrefixListReference
  Text
pTransitGatewayRouteTableId_
  Text
pPrefixListId_ =
    DeleteTransitGatewayPrefixListReference'
      { $sel:dryRun:DeleteTransitGatewayPrefixListReference' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:transitGatewayRouteTableId:DeleteTransitGatewayPrefixListReference' :: Text
transitGatewayRouteTableId =
          Text
pTransitGatewayRouteTableId_,
        $sel:prefixListId:DeleteTransitGatewayPrefixListReference' :: Text
prefixListId = Text
pPrefixListId_
      }

-- | 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@.
deleteTransitGatewayPrefixListReference_dryRun :: Lens.Lens' DeleteTransitGatewayPrefixListReference (Prelude.Maybe Prelude.Bool)
deleteTransitGatewayPrefixListReference_dryRun :: Lens' DeleteTransitGatewayPrefixListReference (Maybe Bool)
deleteTransitGatewayPrefixListReference_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTransitGatewayPrefixListReference' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DeleteTransitGatewayPrefixListReference
s@DeleteTransitGatewayPrefixListReference' {} Maybe Bool
a -> DeleteTransitGatewayPrefixListReference
s {$sel:dryRun:DeleteTransitGatewayPrefixListReference' :: Maybe Bool
dryRun = Maybe Bool
a} :: DeleteTransitGatewayPrefixListReference)

-- | The ID of the route table.
deleteTransitGatewayPrefixListReference_transitGatewayRouteTableId :: Lens.Lens' DeleteTransitGatewayPrefixListReference Prelude.Text
deleteTransitGatewayPrefixListReference_transitGatewayRouteTableId :: Lens' DeleteTransitGatewayPrefixListReference Text
deleteTransitGatewayPrefixListReference_transitGatewayRouteTableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTransitGatewayPrefixListReference' {Text
transitGatewayRouteTableId :: Text
$sel:transitGatewayRouteTableId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
transitGatewayRouteTableId} -> Text
transitGatewayRouteTableId) (\s :: DeleteTransitGatewayPrefixListReference
s@DeleteTransitGatewayPrefixListReference' {} Text
a -> DeleteTransitGatewayPrefixListReference
s {$sel:transitGatewayRouteTableId:DeleteTransitGatewayPrefixListReference' :: Text
transitGatewayRouteTableId = Text
a} :: DeleteTransitGatewayPrefixListReference)

-- | The ID of the prefix list.
deleteTransitGatewayPrefixListReference_prefixListId :: Lens.Lens' DeleteTransitGatewayPrefixListReference Prelude.Text
deleteTransitGatewayPrefixListReference_prefixListId :: Lens' DeleteTransitGatewayPrefixListReference Text
deleteTransitGatewayPrefixListReference_prefixListId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTransitGatewayPrefixListReference' {Text
prefixListId :: Text
$sel:prefixListId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
prefixListId} -> Text
prefixListId) (\s :: DeleteTransitGatewayPrefixListReference
s@DeleteTransitGatewayPrefixListReference' {} Text
a -> DeleteTransitGatewayPrefixListReference
s {$sel:prefixListId:DeleteTransitGatewayPrefixListReference' :: Text
prefixListId = Text
a} :: DeleteTransitGatewayPrefixListReference)

instance
  Core.AWSRequest
    DeleteTransitGatewayPrefixListReference
  where
  type
    AWSResponse
      DeleteTransitGatewayPrefixListReference =
      DeleteTransitGatewayPrefixListReferenceResponse
  request :: (Service -> Service)
-> DeleteTransitGatewayPrefixListReference
-> Request DeleteTransitGatewayPrefixListReference
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 DeleteTransitGatewayPrefixListReference
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DeleteTransitGatewayPrefixListReference)))
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 TransitGatewayPrefixListReference
-> Int -> DeleteTransitGatewayPrefixListReferenceResponse
DeleteTransitGatewayPrefixListReferenceResponse'
            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
"transitGatewayPrefixListReference")
            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
    DeleteTransitGatewayPrefixListReference
  where
  hashWithSalt :: Int -> DeleteTransitGatewayPrefixListReference -> Int
hashWithSalt
    Int
_salt
    DeleteTransitGatewayPrefixListReference' {Maybe Bool
Text
prefixListId :: Text
transitGatewayRouteTableId :: Text
dryRun :: Maybe Bool
$sel:prefixListId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
$sel:transitGatewayRouteTableId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
$sel:dryRun:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> 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
transitGatewayRouteTableId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
prefixListId

instance
  Prelude.NFData
    DeleteTransitGatewayPrefixListReference
  where
  rnf :: DeleteTransitGatewayPrefixListReference -> ()
rnf DeleteTransitGatewayPrefixListReference' {Maybe Bool
Text
prefixListId :: Text
transitGatewayRouteTableId :: Text
dryRun :: Maybe Bool
$sel:prefixListId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
$sel:transitGatewayRouteTableId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
$sel:dryRun:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> 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
transitGatewayRouteTableId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
prefixListId

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

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

instance
  Data.ToQuery
    DeleteTransitGatewayPrefixListReference
  where
  toQuery :: DeleteTransitGatewayPrefixListReference -> QueryString
toQuery DeleteTransitGatewayPrefixListReference' {Maybe Bool
Text
prefixListId :: Text
transitGatewayRouteTableId :: Text
dryRun :: Maybe Bool
$sel:prefixListId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
$sel:transitGatewayRouteTableId:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Text
$sel:dryRun:DeleteTransitGatewayPrefixListReference' :: DeleteTransitGatewayPrefixListReference -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteTransitGatewayPrefixListReference" ::
                      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
"TransitGatewayRouteTableId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
transitGatewayRouteTableId,
        ByteString
"PrefixListId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
prefixListId
      ]

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

-- |
-- Create a value of 'DeleteTransitGatewayPrefixListReferenceResponse' 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:
--
-- 'transitGatewayPrefixListReference', 'deleteTransitGatewayPrefixListReferenceResponse_transitGatewayPrefixListReference' - Information about the deleted prefix list reference.
--
-- 'httpStatus', 'deleteTransitGatewayPrefixListReferenceResponse_httpStatus' - The response's http status code.
newDeleteTransitGatewayPrefixListReferenceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteTransitGatewayPrefixListReferenceResponse
newDeleteTransitGatewayPrefixListReferenceResponse :: Int -> DeleteTransitGatewayPrefixListReferenceResponse
newDeleteTransitGatewayPrefixListReferenceResponse
  Int
pHttpStatus_ =
    DeleteTransitGatewayPrefixListReferenceResponse'
      { $sel:transitGatewayPrefixListReference:DeleteTransitGatewayPrefixListReferenceResponse' :: Maybe TransitGatewayPrefixListReference
transitGatewayPrefixListReference =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DeleteTransitGatewayPrefixListReferenceResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Information about the deleted prefix list reference.
deleteTransitGatewayPrefixListReferenceResponse_transitGatewayPrefixListReference :: Lens.Lens' DeleteTransitGatewayPrefixListReferenceResponse (Prelude.Maybe TransitGatewayPrefixListReference)
deleteTransitGatewayPrefixListReferenceResponse_transitGatewayPrefixListReference :: Lens'
  DeleteTransitGatewayPrefixListReferenceResponse
  (Maybe TransitGatewayPrefixListReference)
deleteTransitGatewayPrefixListReferenceResponse_transitGatewayPrefixListReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTransitGatewayPrefixListReferenceResponse' {Maybe TransitGatewayPrefixListReference
transitGatewayPrefixListReference :: Maybe TransitGatewayPrefixListReference
$sel:transitGatewayPrefixListReference:DeleteTransitGatewayPrefixListReferenceResponse' :: DeleteTransitGatewayPrefixListReferenceResponse
-> Maybe TransitGatewayPrefixListReference
transitGatewayPrefixListReference} -> Maybe TransitGatewayPrefixListReference
transitGatewayPrefixListReference) (\s :: DeleteTransitGatewayPrefixListReferenceResponse
s@DeleteTransitGatewayPrefixListReferenceResponse' {} Maybe TransitGatewayPrefixListReference
a -> DeleteTransitGatewayPrefixListReferenceResponse
s {$sel:transitGatewayPrefixListReference:DeleteTransitGatewayPrefixListReferenceResponse' :: Maybe TransitGatewayPrefixListReference
transitGatewayPrefixListReference = Maybe TransitGatewayPrefixListReference
a} :: DeleteTransitGatewayPrefixListReferenceResponse)

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

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