{-# 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.CreateLocalGatewayRouteTable
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a local gateway route table.
module Amazonka.EC2.CreateLocalGatewayRouteTable
  ( -- * Creating a Request
    CreateLocalGatewayRouteTable (..),
    newCreateLocalGatewayRouteTable,

    -- * Request Lenses
    createLocalGatewayRouteTable_dryRun,
    createLocalGatewayRouteTable_mode,
    createLocalGatewayRouteTable_tagSpecifications,
    createLocalGatewayRouteTable_localGatewayId,

    -- * Destructuring the Response
    CreateLocalGatewayRouteTableResponse (..),
    newCreateLocalGatewayRouteTableResponse,

    -- * Response Lenses
    createLocalGatewayRouteTableResponse_localGatewayRouteTable,
    createLocalGatewayRouteTableResponse_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:/ 'newCreateLocalGatewayRouteTable' smart constructor.
data CreateLocalGatewayRouteTable = CreateLocalGatewayRouteTable'
  { -- | 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@.
    CreateLocalGatewayRouteTable -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The mode of the local gateway route table.
    CreateLocalGatewayRouteTable -> Maybe LocalGatewayRouteTableMode
mode :: Prelude.Maybe LocalGatewayRouteTableMode,
    -- | The tags assigned to the local gateway route table.
    CreateLocalGatewayRouteTable -> Maybe [TagSpecification]
tagSpecifications :: Prelude.Maybe [TagSpecification],
    -- | The ID of the local gateway.
    CreateLocalGatewayRouteTable -> Text
localGatewayId :: Prelude.Text
  }
  deriving (CreateLocalGatewayRouteTable
-> CreateLocalGatewayRouteTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLocalGatewayRouteTable
-> CreateLocalGatewayRouteTable -> Bool
$c/= :: CreateLocalGatewayRouteTable
-> CreateLocalGatewayRouteTable -> Bool
== :: CreateLocalGatewayRouteTable
-> CreateLocalGatewayRouteTable -> Bool
$c== :: CreateLocalGatewayRouteTable
-> CreateLocalGatewayRouteTable -> Bool
Prelude.Eq, ReadPrec [CreateLocalGatewayRouteTable]
ReadPrec CreateLocalGatewayRouteTable
Int -> ReadS CreateLocalGatewayRouteTable
ReadS [CreateLocalGatewayRouteTable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateLocalGatewayRouteTable]
$creadListPrec :: ReadPrec [CreateLocalGatewayRouteTable]
readPrec :: ReadPrec CreateLocalGatewayRouteTable
$creadPrec :: ReadPrec CreateLocalGatewayRouteTable
readList :: ReadS [CreateLocalGatewayRouteTable]
$creadList :: ReadS [CreateLocalGatewayRouteTable]
readsPrec :: Int -> ReadS CreateLocalGatewayRouteTable
$creadsPrec :: Int -> ReadS CreateLocalGatewayRouteTable
Prelude.Read, Int -> CreateLocalGatewayRouteTable -> ShowS
[CreateLocalGatewayRouteTable] -> ShowS
CreateLocalGatewayRouteTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLocalGatewayRouteTable] -> ShowS
$cshowList :: [CreateLocalGatewayRouteTable] -> ShowS
show :: CreateLocalGatewayRouteTable -> String
$cshow :: CreateLocalGatewayRouteTable -> String
showsPrec :: Int -> CreateLocalGatewayRouteTable -> ShowS
$cshowsPrec :: Int -> CreateLocalGatewayRouteTable -> ShowS
Prelude.Show, forall x.
Rep CreateLocalGatewayRouteTable x -> CreateLocalGatewayRouteTable
forall x.
CreateLocalGatewayRouteTable -> Rep CreateLocalGatewayRouteTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateLocalGatewayRouteTable x -> CreateLocalGatewayRouteTable
$cfrom :: forall x.
CreateLocalGatewayRouteTable -> Rep CreateLocalGatewayRouteTable x
Prelude.Generic)

-- |
-- Create a value of 'CreateLocalGatewayRouteTable' 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', 'createLocalGatewayRouteTable_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@.
--
-- 'mode', 'createLocalGatewayRouteTable_mode' - The mode of the local gateway route table.
--
-- 'tagSpecifications', 'createLocalGatewayRouteTable_tagSpecifications' - The tags assigned to the local gateway route table.
--
-- 'localGatewayId', 'createLocalGatewayRouteTable_localGatewayId' - The ID of the local gateway.
newCreateLocalGatewayRouteTable ::
  -- | 'localGatewayId'
  Prelude.Text ->
  CreateLocalGatewayRouteTable
newCreateLocalGatewayRouteTable :: Text -> CreateLocalGatewayRouteTable
newCreateLocalGatewayRouteTable Text
pLocalGatewayId_ =
  CreateLocalGatewayRouteTable'
    { $sel:dryRun:CreateLocalGatewayRouteTable' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:mode:CreateLocalGatewayRouteTable' :: Maybe LocalGatewayRouteTableMode
mode = forall a. Maybe a
Prelude.Nothing,
      $sel:tagSpecifications:CreateLocalGatewayRouteTable' :: Maybe [TagSpecification]
tagSpecifications = forall a. Maybe a
Prelude.Nothing,
      $sel:localGatewayId:CreateLocalGatewayRouteTable' :: Text
localGatewayId = Text
pLocalGatewayId_
    }

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

-- | The mode of the local gateway route table.
createLocalGatewayRouteTable_mode :: Lens.Lens' CreateLocalGatewayRouteTable (Prelude.Maybe LocalGatewayRouteTableMode)
createLocalGatewayRouteTable_mode :: Lens'
  CreateLocalGatewayRouteTable (Maybe LocalGatewayRouteTableMode)
createLocalGatewayRouteTable_mode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocalGatewayRouteTable' {Maybe LocalGatewayRouteTableMode
mode :: Maybe LocalGatewayRouteTableMode
$sel:mode:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe LocalGatewayRouteTableMode
mode} -> Maybe LocalGatewayRouteTableMode
mode) (\s :: CreateLocalGatewayRouteTable
s@CreateLocalGatewayRouteTable' {} Maybe LocalGatewayRouteTableMode
a -> CreateLocalGatewayRouteTable
s {$sel:mode:CreateLocalGatewayRouteTable' :: Maybe LocalGatewayRouteTableMode
mode = Maybe LocalGatewayRouteTableMode
a} :: CreateLocalGatewayRouteTable)

-- | The tags assigned to the local gateway route table.
createLocalGatewayRouteTable_tagSpecifications :: Lens.Lens' CreateLocalGatewayRouteTable (Prelude.Maybe [TagSpecification])
createLocalGatewayRouteTable_tagSpecifications :: Lens' CreateLocalGatewayRouteTable (Maybe [TagSpecification])
createLocalGatewayRouteTable_tagSpecifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocalGatewayRouteTable' {Maybe [TagSpecification]
tagSpecifications :: Maybe [TagSpecification]
$sel:tagSpecifications:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe [TagSpecification]
tagSpecifications} -> Maybe [TagSpecification]
tagSpecifications) (\s :: CreateLocalGatewayRouteTable
s@CreateLocalGatewayRouteTable' {} Maybe [TagSpecification]
a -> CreateLocalGatewayRouteTable
s {$sel:tagSpecifications:CreateLocalGatewayRouteTable' :: Maybe [TagSpecification]
tagSpecifications = Maybe [TagSpecification]
a} :: CreateLocalGatewayRouteTable) 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 ID of the local gateway.
createLocalGatewayRouteTable_localGatewayId :: Lens.Lens' CreateLocalGatewayRouteTable Prelude.Text
createLocalGatewayRouteTable_localGatewayId :: Lens' CreateLocalGatewayRouteTable Text
createLocalGatewayRouteTable_localGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocalGatewayRouteTable' {Text
localGatewayId :: Text
$sel:localGatewayId:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Text
localGatewayId} -> Text
localGatewayId) (\s :: CreateLocalGatewayRouteTable
s@CreateLocalGatewayRouteTable' {} Text
a -> CreateLocalGatewayRouteTable
s {$sel:localGatewayId:CreateLocalGatewayRouteTable' :: Text
localGatewayId = Text
a} :: CreateLocalGatewayRouteTable)

instance Core.AWSRequest CreateLocalGatewayRouteTable where
  type
    AWSResponse CreateLocalGatewayRouteTable =
      CreateLocalGatewayRouteTableResponse
  request :: (Service -> Service)
-> CreateLocalGatewayRouteTable
-> Request CreateLocalGatewayRouteTable
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 CreateLocalGatewayRouteTable
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateLocalGatewayRouteTable)))
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 LocalGatewayRouteTable
-> Int -> CreateLocalGatewayRouteTableResponse
CreateLocalGatewayRouteTableResponse'
            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
"localGatewayRouteTable")
            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
    CreateLocalGatewayRouteTable
  where
  hashWithSalt :: Int -> CreateLocalGatewayRouteTable -> Int
hashWithSalt Int
_salt CreateLocalGatewayRouteTable' {Maybe Bool
Maybe [TagSpecification]
Maybe LocalGatewayRouteTableMode
Text
localGatewayId :: Text
tagSpecifications :: Maybe [TagSpecification]
mode :: Maybe LocalGatewayRouteTableMode
dryRun :: Maybe Bool
$sel:localGatewayId:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Text
$sel:tagSpecifications:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe [TagSpecification]
$sel:mode:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe LocalGatewayRouteTableMode
$sel:dryRun:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> 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` Maybe LocalGatewayRouteTableMode
mode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TagSpecification]
tagSpecifications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
localGatewayId

instance Prelude.NFData CreateLocalGatewayRouteTable where
  rnf :: CreateLocalGatewayRouteTable -> ()
rnf CreateLocalGatewayRouteTable' {Maybe Bool
Maybe [TagSpecification]
Maybe LocalGatewayRouteTableMode
Text
localGatewayId :: Text
tagSpecifications :: Maybe [TagSpecification]
mode :: Maybe LocalGatewayRouteTableMode
dryRun :: Maybe Bool
$sel:localGatewayId:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Text
$sel:tagSpecifications:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe [TagSpecification]
$sel:mode:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe LocalGatewayRouteTableMode
$sel:dryRun:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> 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 Maybe LocalGatewayRouteTableMode
mode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TagSpecification]
tagSpecifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
localGatewayId

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

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

instance Data.ToQuery CreateLocalGatewayRouteTable where
  toQuery :: CreateLocalGatewayRouteTable -> QueryString
toQuery CreateLocalGatewayRouteTable' {Maybe Bool
Maybe [TagSpecification]
Maybe LocalGatewayRouteTableMode
Text
localGatewayId :: Text
tagSpecifications :: Maybe [TagSpecification]
mode :: Maybe LocalGatewayRouteTableMode
dryRun :: Maybe Bool
$sel:localGatewayId:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Text
$sel:tagSpecifications:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe [TagSpecification]
$sel:mode:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe LocalGatewayRouteTableMode
$sel:dryRun:CreateLocalGatewayRouteTable' :: CreateLocalGatewayRouteTable -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"CreateLocalGatewayRouteTable" ::
                      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
"Mode" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe LocalGatewayRouteTableMode
mode,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TagSpecification"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TagSpecification]
tagSpecifications
          ),
        ByteString
"LocalGatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
localGatewayId
      ]

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

-- |
-- Create a value of 'CreateLocalGatewayRouteTableResponse' 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:
--
-- 'localGatewayRouteTable', 'createLocalGatewayRouteTableResponse_localGatewayRouteTable' - Information about the local gateway route table.
--
-- 'httpStatus', 'createLocalGatewayRouteTableResponse_httpStatus' - The response's http status code.
newCreateLocalGatewayRouteTableResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateLocalGatewayRouteTableResponse
newCreateLocalGatewayRouteTableResponse :: Int -> CreateLocalGatewayRouteTableResponse
newCreateLocalGatewayRouteTableResponse Int
pHttpStatus_ =
  CreateLocalGatewayRouteTableResponse'
    { $sel:localGatewayRouteTable:CreateLocalGatewayRouteTableResponse' :: Maybe LocalGatewayRouteTable
localGatewayRouteTable =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateLocalGatewayRouteTableResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the local gateway route table.
createLocalGatewayRouteTableResponse_localGatewayRouteTable :: Lens.Lens' CreateLocalGatewayRouteTableResponse (Prelude.Maybe LocalGatewayRouteTable)
createLocalGatewayRouteTableResponse_localGatewayRouteTable :: Lens'
  CreateLocalGatewayRouteTableResponse (Maybe LocalGatewayRouteTable)
createLocalGatewayRouteTableResponse_localGatewayRouteTable = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLocalGatewayRouteTableResponse' {Maybe LocalGatewayRouteTable
localGatewayRouteTable :: Maybe LocalGatewayRouteTable
$sel:localGatewayRouteTable:CreateLocalGatewayRouteTableResponse' :: CreateLocalGatewayRouteTableResponse
-> Maybe LocalGatewayRouteTable
localGatewayRouteTable} -> Maybe LocalGatewayRouteTable
localGatewayRouteTable) (\s :: CreateLocalGatewayRouteTableResponse
s@CreateLocalGatewayRouteTableResponse' {} Maybe LocalGatewayRouteTable
a -> CreateLocalGatewayRouteTableResponse
s {$sel:localGatewayRouteTable:CreateLocalGatewayRouteTableResponse' :: Maybe LocalGatewayRouteTable
localGatewayRouteTable = Maybe LocalGatewayRouteTable
a} :: CreateLocalGatewayRouteTableResponse)

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

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