{-# 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.ReplaceRouteTableAssociation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes the route table associated with a given subnet, internet
-- gateway, or virtual private gateway in a VPC. After the operation
-- completes, the subnet or gateway uses the routes in the new route table.
-- For more information about route tables, see
-- <https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Route_Tables.html Route tables>
-- in the /Amazon Virtual Private Cloud User Guide/.
--
-- You can also use this operation to change which table is the main route
-- table in the VPC. Specify the main route table\'s association ID and the
-- route table ID of the new main route table.
module Amazonka.EC2.ReplaceRouteTableAssociation
  ( -- * Creating a Request
    ReplaceRouteTableAssociation (..),
    newReplaceRouteTableAssociation,

    -- * Request Lenses
    replaceRouteTableAssociation_dryRun,
    replaceRouteTableAssociation_associationId,
    replaceRouteTableAssociation_routeTableId,

    -- * Destructuring the Response
    ReplaceRouteTableAssociationResponse (..),
    newReplaceRouteTableAssociationResponse,

    -- * Response Lenses
    replaceRouteTableAssociationResponse_associationState,
    replaceRouteTableAssociationResponse_newAssociationId,
    replaceRouteTableAssociationResponse_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:/ 'newReplaceRouteTableAssociation' smart constructor.
data ReplaceRouteTableAssociation = ReplaceRouteTableAssociation'
  { -- | 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@.
    ReplaceRouteTableAssociation -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The association ID.
    ReplaceRouteTableAssociation -> Text
associationId :: Prelude.Text,
    -- | The ID of the new route table to associate with the subnet.
    ReplaceRouteTableAssociation -> Text
routeTableId :: Prelude.Text
  }
  deriving (ReplaceRouteTableAssociation
-> ReplaceRouteTableAssociation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplaceRouteTableAssociation
-> ReplaceRouteTableAssociation -> Bool
$c/= :: ReplaceRouteTableAssociation
-> ReplaceRouteTableAssociation -> Bool
== :: ReplaceRouteTableAssociation
-> ReplaceRouteTableAssociation -> Bool
$c== :: ReplaceRouteTableAssociation
-> ReplaceRouteTableAssociation -> Bool
Prelude.Eq, ReadPrec [ReplaceRouteTableAssociation]
ReadPrec ReplaceRouteTableAssociation
Int -> ReadS ReplaceRouteTableAssociation
ReadS [ReplaceRouteTableAssociation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplaceRouteTableAssociation]
$creadListPrec :: ReadPrec [ReplaceRouteTableAssociation]
readPrec :: ReadPrec ReplaceRouteTableAssociation
$creadPrec :: ReadPrec ReplaceRouteTableAssociation
readList :: ReadS [ReplaceRouteTableAssociation]
$creadList :: ReadS [ReplaceRouteTableAssociation]
readsPrec :: Int -> ReadS ReplaceRouteTableAssociation
$creadsPrec :: Int -> ReadS ReplaceRouteTableAssociation
Prelude.Read, Int -> ReplaceRouteTableAssociation -> ShowS
[ReplaceRouteTableAssociation] -> ShowS
ReplaceRouteTableAssociation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplaceRouteTableAssociation] -> ShowS
$cshowList :: [ReplaceRouteTableAssociation] -> ShowS
show :: ReplaceRouteTableAssociation -> String
$cshow :: ReplaceRouteTableAssociation -> String
showsPrec :: Int -> ReplaceRouteTableAssociation -> ShowS
$cshowsPrec :: Int -> ReplaceRouteTableAssociation -> ShowS
Prelude.Show, forall x.
Rep ReplaceRouteTableAssociation x -> ReplaceRouteTableAssociation
forall x.
ReplaceRouteTableAssociation -> Rep ReplaceRouteTableAssociation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ReplaceRouteTableAssociation x -> ReplaceRouteTableAssociation
$cfrom :: forall x.
ReplaceRouteTableAssociation -> Rep ReplaceRouteTableAssociation x
Prelude.Generic)

-- |
-- Create a value of 'ReplaceRouteTableAssociation' 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', 'replaceRouteTableAssociation_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@.
--
-- 'associationId', 'replaceRouteTableAssociation_associationId' - The association ID.
--
-- 'routeTableId', 'replaceRouteTableAssociation_routeTableId' - The ID of the new route table to associate with the subnet.
newReplaceRouteTableAssociation ::
  -- | 'associationId'
  Prelude.Text ->
  -- | 'routeTableId'
  Prelude.Text ->
  ReplaceRouteTableAssociation
newReplaceRouteTableAssociation :: Text -> Text -> ReplaceRouteTableAssociation
newReplaceRouteTableAssociation
  Text
pAssociationId_
  Text
pRouteTableId_ =
    ReplaceRouteTableAssociation'
      { $sel:dryRun:ReplaceRouteTableAssociation' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:associationId:ReplaceRouteTableAssociation' :: Text
associationId = Text
pAssociationId_,
        $sel:routeTableId:ReplaceRouteTableAssociation' :: Text
routeTableId = Text
pRouteTableId_
      }

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

-- | The association ID.
replaceRouteTableAssociation_associationId :: Lens.Lens' ReplaceRouteTableAssociation Prelude.Text
replaceRouteTableAssociation_associationId :: Lens' ReplaceRouteTableAssociation Text
replaceRouteTableAssociation_associationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceRouteTableAssociation' {Text
associationId :: Text
$sel:associationId:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Text
associationId} -> Text
associationId) (\s :: ReplaceRouteTableAssociation
s@ReplaceRouteTableAssociation' {} Text
a -> ReplaceRouteTableAssociation
s {$sel:associationId:ReplaceRouteTableAssociation' :: Text
associationId = Text
a} :: ReplaceRouteTableAssociation)

-- | The ID of the new route table to associate with the subnet.
replaceRouteTableAssociation_routeTableId :: Lens.Lens' ReplaceRouteTableAssociation Prelude.Text
replaceRouteTableAssociation_routeTableId :: Lens' ReplaceRouteTableAssociation Text
replaceRouteTableAssociation_routeTableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceRouteTableAssociation' {Text
routeTableId :: Text
$sel:routeTableId:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Text
routeTableId} -> Text
routeTableId) (\s :: ReplaceRouteTableAssociation
s@ReplaceRouteTableAssociation' {} Text
a -> ReplaceRouteTableAssociation
s {$sel:routeTableId:ReplaceRouteTableAssociation' :: Text
routeTableId = Text
a} :: ReplaceRouteTableAssociation)

instance Core.AWSRequest ReplaceRouteTableAssociation where
  type
    AWSResponse ReplaceRouteTableAssociation =
      ReplaceRouteTableAssociationResponse
  request :: (Service -> Service)
-> ReplaceRouteTableAssociation
-> Request ReplaceRouteTableAssociation
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 ReplaceRouteTableAssociation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ReplaceRouteTableAssociation)))
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 RouteTableAssociationState
-> Maybe Text -> Int -> ReplaceRouteTableAssociationResponse
ReplaceRouteTableAssociationResponse'
            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
"associationState")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"newAssociationId")
            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
    ReplaceRouteTableAssociation
  where
  hashWithSalt :: Int -> ReplaceRouteTableAssociation -> Int
hashWithSalt Int
_salt ReplaceRouteTableAssociation' {Maybe Bool
Text
routeTableId :: Text
associationId :: Text
dryRun :: Maybe Bool
$sel:routeTableId:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Text
$sel:associationId:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Text
$sel:dryRun:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> 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
associationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routeTableId

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

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

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

instance Data.ToQuery ReplaceRouteTableAssociation where
  toQuery :: ReplaceRouteTableAssociation -> QueryString
toQuery ReplaceRouteTableAssociation' {Maybe Bool
Text
routeTableId :: Text
associationId :: Text
dryRun :: Maybe Bool
$sel:routeTableId:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Text
$sel:associationId:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Text
$sel:dryRun:ReplaceRouteTableAssociation' :: ReplaceRouteTableAssociation -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"ReplaceRouteTableAssociation" ::
                      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
"AssociationId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
associationId,
        ByteString
"RouteTableId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
routeTableId
      ]

-- | /See:/ 'newReplaceRouteTableAssociationResponse' smart constructor.
data ReplaceRouteTableAssociationResponse = ReplaceRouteTableAssociationResponse'
  { -- | The state of the association.
    ReplaceRouteTableAssociationResponse
-> Maybe RouteTableAssociationState
associationState :: Prelude.Maybe RouteTableAssociationState,
    -- | The ID of the new association.
    ReplaceRouteTableAssociationResponse -> Maybe Text
newAssociationId' :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ReplaceRouteTableAssociationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ReplaceRouteTableAssociationResponse
-> ReplaceRouteTableAssociationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplaceRouteTableAssociationResponse
-> ReplaceRouteTableAssociationResponse -> Bool
$c/= :: ReplaceRouteTableAssociationResponse
-> ReplaceRouteTableAssociationResponse -> Bool
== :: ReplaceRouteTableAssociationResponse
-> ReplaceRouteTableAssociationResponse -> Bool
$c== :: ReplaceRouteTableAssociationResponse
-> ReplaceRouteTableAssociationResponse -> Bool
Prelude.Eq, ReadPrec [ReplaceRouteTableAssociationResponse]
ReadPrec ReplaceRouteTableAssociationResponse
Int -> ReadS ReplaceRouteTableAssociationResponse
ReadS [ReplaceRouteTableAssociationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReplaceRouteTableAssociationResponse]
$creadListPrec :: ReadPrec [ReplaceRouteTableAssociationResponse]
readPrec :: ReadPrec ReplaceRouteTableAssociationResponse
$creadPrec :: ReadPrec ReplaceRouteTableAssociationResponse
readList :: ReadS [ReplaceRouteTableAssociationResponse]
$creadList :: ReadS [ReplaceRouteTableAssociationResponse]
readsPrec :: Int -> ReadS ReplaceRouteTableAssociationResponse
$creadsPrec :: Int -> ReadS ReplaceRouteTableAssociationResponse
Prelude.Read, Int -> ReplaceRouteTableAssociationResponse -> ShowS
[ReplaceRouteTableAssociationResponse] -> ShowS
ReplaceRouteTableAssociationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplaceRouteTableAssociationResponse] -> ShowS
$cshowList :: [ReplaceRouteTableAssociationResponse] -> ShowS
show :: ReplaceRouteTableAssociationResponse -> String
$cshow :: ReplaceRouteTableAssociationResponse -> String
showsPrec :: Int -> ReplaceRouteTableAssociationResponse -> ShowS
$cshowsPrec :: Int -> ReplaceRouteTableAssociationResponse -> ShowS
Prelude.Show, forall x.
Rep ReplaceRouteTableAssociationResponse x
-> ReplaceRouteTableAssociationResponse
forall x.
ReplaceRouteTableAssociationResponse
-> Rep ReplaceRouteTableAssociationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ReplaceRouteTableAssociationResponse x
-> ReplaceRouteTableAssociationResponse
$cfrom :: forall x.
ReplaceRouteTableAssociationResponse
-> Rep ReplaceRouteTableAssociationResponse x
Prelude.Generic)

-- |
-- Create a value of 'ReplaceRouteTableAssociationResponse' 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:
--
-- 'associationState', 'replaceRouteTableAssociationResponse_associationState' - The state of the association.
--
-- 'newAssociationId'', 'replaceRouteTableAssociationResponse_newAssociationId' - The ID of the new association.
--
-- 'httpStatus', 'replaceRouteTableAssociationResponse_httpStatus' - The response's http status code.
newReplaceRouteTableAssociationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ReplaceRouteTableAssociationResponse
newReplaceRouteTableAssociationResponse :: Int -> ReplaceRouteTableAssociationResponse
newReplaceRouteTableAssociationResponse Int
pHttpStatus_ =
  ReplaceRouteTableAssociationResponse'
    { $sel:associationState:ReplaceRouteTableAssociationResponse' :: Maybe RouteTableAssociationState
associationState =
        forall a. Maybe a
Prelude.Nothing,
      $sel:newAssociationId':ReplaceRouteTableAssociationResponse' :: Maybe Text
newAssociationId' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ReplaceRouteTableAssociationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The state of the association.
replaceRouteTableAssociationResponse_associationState :: Lens.Lens' ReplaceRouteTableAssociationResponse (Prelude.Maybe RouteTableAssociationState)
replaceRouteTableAssociationResponse_associationState :: Lens'
  ReplaceRouteTableAssociationResponse
  (Maybe RouteTableAssociationState)
replaceRouteTableAssociationResponse_associationState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceRouteTableAssociationResponse' {Maybe RouteTableAssociationState
associationState :: Maybe RouteTableAssociationState
$sel:associationState:ReplaceRouteTableAssociationResponse' :: ReplaceRouteTableAssociationResponse
-> Maybe RouteTableAssociationState
associationState} -> Maybe RouteTableAssociationState
associationState) (\s :: ReplaceRouteTableAssociationResponse
s@ReplaceRouteTableAssociationResponse' {} Maybe RouteTableAssociationState
a -> ReplaceRouteTableAssociationResponse
s {$sel:associationState:ReplaceRouteTableAssociationResponse' :: Maybe RouteTableAssociationState
associationState = Maybe RouteTableAssociationState
a} :: ReplaceRouteTableAssociationResponse)

-- | The ID of the new association.
replaceRouteTableAssociationResponse_newAssociationId :: Lens.Lens' ReplaceRouteTableAssociationResponse (Prelude.Maybe Prelude.Text)
replaceRouteTableAssociationResponse_newAssociationId :: Lens' ReplaceRouteTableAssociationResponse (Maybe Text)
replaceRouteTableAssociationResponse_newAssociationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReplaceRouteTableAssociationResponse' {Maybe Text
newAssociationId' :: Maybe Text
$sel:newAssociationId':ReplaceRouteTableAssociationResponse' :: ReplaceRouteTableAssociationResponse -> Maybe Text
newAssociationId'} -> Maybe Text
newAssociationId') (\s :: ReplaceRouteTableAssociationResponse
s@ReplaceRouteTableAssociationResponse' {} Maybe Text
a -> ReplaceRouteTableAssociationResponse
s {$sel:newAssociationId':ReplaceRouteTableAssociationResponse' :: Maybe Text
newAssociationId' = Maybe Text
a} :: ReplaceRouteTableAssociationResponse)

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

instance
  Prelude.NFData
    ReplaceRouteTableAssociationResponse
  where
  rnf :: ReplaceRouteTableAssociationResponse -> ()
rnf ReplaceRouteTableAssociationResponse' {Int
Maybe Text
Maybe RouteTableAssociationState
httpStatus :: Int
newAssociationId' :: Maybe Text
associationState :: Maybe RouteTableAssociationState
$sel:httpStatus:ReplaceRouteTableAssociationResponse' :: ReplaceRouteTableAssociationResponse -> Int
$sel:newAssociationId':ReplaceRouteTableAssociationResponse' :: ReplaceRouteTableAssociationResponse -> Maybe Text
$sel:associationState:ReplaceRouteTableAssociationResponse' :: ReplaceRouteTableAssociationResponse
-> Maybe RouteTableAssociationState
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe RouteTableAssociationState
associationState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
newAssociationId'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus