{-# 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.ExportTransitGatewayRoutes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Exports routes from the specified transit gateway route table to the
-- specified S3 bucket. By default, all routes are exported. Alternatively,
-- you can filter by CIDR range.
--
-- The routes are saved to the specified bucket in a JSON file. For more
-- information, see
-- <https://docs.aws.amazon.com/vpc/latest/tgw/tgw-route-tables.html#tgw-export-route-tables Export Route Tables to Amazon S3>
-- in /Transit Gateways/.
module Amazonka.EC2.ExportTransitGatewayRoutes
  ( -- * Creating a Request
    ExportTransitGatewayRoutes (..),
    newExportTransitGatewayRoutes,

    -- * Request Lenses
    exportTransitGatewayRoutes_dryRun,
    exportTransitGatewayRoutes_filters,
    exportTransitGatewayRoutes_transitGatewayRouteTableId,
    exportTransitGatewayRoutes_s3Bucket,

    -- * Destructuring the Response
    ExportTransitGatewayRoutesResponse (..),
    newExportTransitGatewayRoutesResponse,

    -- * Response Lenses
    exportTransitGatewayRoutesResponse_s3Location,
    exportTransitGatewayRoutesResponse_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:/ 'newExportTransitGatewayRoutes' smart constructor.
data ExportTransitGatewayRoutes = ExportTransitGatewayRoutes'
  { -- | 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@.
    ExportTransitGatewayRoutes -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | One or more filters. The possible values are:
    --
    -- -   @attachment.transit-gateway-attachment-id@ - The id of the transit
    --     gateway attachment.
    --
    -- -   @attachment.resource-id@ - The resource id of the transit gateway
    --     attachment.
    --
    -- -   @route-search.exact-match@ - The exact match of the specified
    --     filter.
    --
    -- -   @route-search.longest-prefix-match@ - The longest prefix that
    --     matches the route.
    --
    -- -   @route-search.subnet-of-match@ - The routes with a subnet that match
    --     the specified CIDR filter.
    --
    -- -   @route-search.supernet-of-match@ - The routes with a CIDR that
    --     encompass the CIDR filter. For example, if you have 10.0.1.0\/29 and
    --     10.0.1.0\/31 routes in your route table and you specify
    --     supernet-of-match as 10.0.1.0\/30, then the result returns
    --     10.0.1.0\/29.
    --
    -- -   @state@ - The state of the route (@active@ | @blackhole@).
    --
    -- -   @transit-gateway-route-destination-cidr-block@ - The CIDR range.
    --
    -- -   @type@ - The type of route (@propagated@ | @static@).
    ExportTransitGatewayRoutes -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | The ID of the route table.
    ExportTransitGatewayRoutes -> Text
transitGatewayRouteTableId :: Prelude.Text,
    -- | The name of the S3 bucket.
    ExportTransitGatewayRoutes -> Text
s3Bucket :: Prelude.Text
  }
  deriving (ExportTransitGatewayRoutes -> ExportTransitGatewayRoutes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportTransitGatewayRoutes -> ExportTransitGatewayRoutes -> Bool
$c/= :: ExportTransitGatewayRoutes -> ExportTransitGatewayRoutes -> Bool
== :: ExportTransitGatewayRoutes -> ExportTransitGatewayRoutes -> Bool
$c== :: ExportTransitGatewayRoutes -> ExportTransitGatewayRoutes -> Bool
Prelude.Eq, ReadPrec [ExportTransitGatewayRoutes]
ReadPrec ExportTransitGatewayRoutes
Int -> ReadS ExportTransitGatewayRoutes
ReadS [ExportTransitGatewayRoutes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportTransitGatewayRoutes]
$creadListPrec :: ReadPrec [ExportTransitGatewayRoutes]
readPrec :: ReadPrec ExportTransitGatewayRoutes
$creadPrec :: ReadPrec ExportTransitGatewayRoutes
readList :: ReadS [ExportTransitGatewayRoutes]
$creadList :: ReadS [ExportTransitGatewayRoutes]
readsPrec :: Int -> ReadS ExportTransitGatewayRoutes
$creadsPrec :: Int -> ReadS ExportTransitGatewayRoutes
Prelude.Read, Int -> ExportTransitGatewayRoutes -> ShowS
[ExportTransitGatewayRoutes] -> ShowS
ExportTransitGatewayRoutes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportTransitGatewayRoutes] -> ShowS
$cshowList :: [ExportTransitGatewayRoutes] -> ShowS
show :: ExportTransitGatewayRoutes -> String
$cshow :: ExportTransitGatewayRoutes -> String
showsPrec :: Int -> ExportTransitGatewayRoutes -> ShowS
$cshowsPrec :: Int -> ExportTransitGatewayRoutes -> ShowS
Prelude.Show, forall x.
Rep ExportTransitGatewayRoutes x -> ExportTransitGatewayRoutes
forall x.
ExportTransitGatewayRoutes -> Rep ExportTransitGatewayRoutes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExportTransitGatewayRoutes x -> ExportTransitGatewayRoutes
$cfrom :: forall x.
ExportTransitGatewayRoutes -> Rep ExportTransitGatewayRoutes x
Prelude.Generic)

-- |
-- Create a value of 'ExportTransitGatewayRoutes' 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', 'exportTransitGatewayRoutes_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@.
--
-- 'filters', 'exportTransitGatewayRoutes_filters' - One or more filters. The possible values are:
--
-- -   @attachment.transit-gateway-attachment-id@ - The id of the transit
--     gateway attachment.
--
-- -   @attachment.resource-id@ - The resource id of the transit gateway
--     attachment.
--
-- -   @route-search.exact-match@ - The exact match of the specified
--     filter.
--
-- -   @route-search.longest-prefix-match@ - The longest prefix that
--     matches the route.
--
-- -   @route-search.subnet-of-match@ - The routes with a subnet that match
--     the specified CIDR filter.
--
-- -   @route-search.supernet-of-match@ - The routes with a CIDR that
--     encompass the CIDR filter. For example, if you have 10.0.1.0\/29 and
--     10.0.1.0\/31 routes in your route table and you specify
--     supernet-of-match as 10.0.1.0\/30, then the result returns
--     10.0.1.0\/29.
--
-- -   @state@ - The state of the route (@active@ | @blackhole@).
--
-- -   @transit-gateway-route-destination-cidr-block@ - The CIDR range.
--
-- -   @type@ - The type of route (@propagated@ | @static@).
--
-- 'transitGatewayRouteTableId', 'exportTransitGatewayRoutes_transitGatewayRouteTableId' - The ID of the route table.
--
-- 's3Bucket', 'exportTransitGatewayRoutes_s3Bucket' - The name of the S3 bucket.
newExportTransitGatewayRoutes ::
  -- | 'transitGatewayRouteTableId'
  Prelude.Text ->
  -- | 's3Bucket'
  Prelude.Text ->
  ExportTransitGatewayRoutes
newExportTransitGatewayRoutes :: Text -> Text -> ExportTransitGatewayRoutes
newExportTransitGatewayRoutes
  Text
pTransitGatewayRouteTableId_
  Text
pS3Bucket_ =
    ExportTransitGatewayRoutes'
      { $sel:dryRun:ExportTransitGatewayRoutes' :: Maybe Bool
dryRun =
          forall a. Maybe a
Prelude.Nothing,
        $sel:filters:ExportTransitGatewayRoutes' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
        $sel:transitGatewayRouteTableId:ExportTransitGatewayRoutes' :: Text
transitGatewayRouteTableId =
          Text
pTransitGatewayRouteTableId_,
        $sel:s3Bucket:ExportTransitGatewayRoutes' :: Text
s3Bucket = Text
pS3Bucket_
      }

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

-- | One or more filters. The possible values are:
--
-- -   @attachment.transit-gateway-attachment-id@ - The id of the transit
--     gateway attachment.
--
-- -   @attachment.resource-id@ - The resource id of the transit gateway
--     attachment.
--
-- -   @route-search.exact-match@ - The exact match of the specified
--     filter.
--
-- -   @route-search.longest-prefix-match@ - The longest prefix that
--     matches the route.
--
-- -   @route-search.subnet-of-match@ - The routes with a subnet that match
--     the specified CIDR filter.
--
-- -   @route-search.supernet-of-match@ - The routes with a CIDR that
--     encompass the CIDR filter. For example, if you have 10.0.1.0\/29 and
--     10.0.1.0\/31 routes in your route table and you specify
--     supernet-of-match as 10.0.1.0\/30, then the result returns
--     10.0.1.0\/29.
--
-- -   @state@ - The state of the route (@active@ | @blackhole@).
--
-- -   @transit-gateway-route-destination-cidr-block@ - The CIDR range.
--
-- -   @type@ - The type of route (@propagated@ | @static@).
exportTransitGatewayRoutes_filters :: Lens.Lens' ExportTransitGatewayRoutes (Prelude.Maybe [Filter])
exportTransitGatewayRoutes_filters :: Lens' ExportTransitGatewayRoutes (Maybe [Filter])
exportTransitGatewayRoutes_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportTransitGatewayRoutes' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ExportTransitGatewayRoutes
s@ExportTransitGatewayRoutes' {} Maybe [Filter]
a -> ExportTransitGatewayRoutes
s {$sel:filters:ExportTransitGatewayRoutes' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ExportTransitGatewayRoutes) 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 route table.
exportTransitGatewayRoutes_transitGatewayRouteTableId :: Lens.Lens' ExportTransitGatewayRoutes Prelude.Text
exportTransitGatewayRoutes_transitGatewayRouteTableId :: Lens' ExportTransitGatewayRoutes Text
exportTransitGatewayRoutes_transitGatewayRouteTableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportTransitGatewayRoutes' {Text
transitGatewayRouteTableId :: Text
$sel:transitGatewayRouteTableId:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
transitGatewayRouteTableId} -> Text
transitGatewayRouteTableId) (\s :: ExportTransitGatewayRoutes
s@ExportTransitGatewayRoutes' {} Text
a -> ExportTransitGatewayRoutes
s {$sel:transitGatewayRouteTableId:ExportTransitGatewayRoutes' :: Text
transitGatewayRouteTableId = Text
a} :: ExportTransitGatewayRoutes)

-- | The name of the S3 bucket.
exportTransitGatewayRoutes_s3Bucket :: Lens.Lens' ExportTransitGatewayRoutes Prelude.Text
exportTransitGatewayRoutes_s3Bucket :: Lens' ExportTransitGatewayRoutes Text
exportTransitGatewayRoutes_s3Bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportTransitGatewayRoutes' {Text
s3Bucket :: Text
$sel:s3Bucket:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
s3Bucket} -> Text
s3Bucket) (\s :: ExportTransitGatewayRoutes
s@ExportTransitGatewayRoutes' {} Text
a -> ExportTransitGatewayRoutes
s {$sel:s3Bucket:ExportTransitGatewayRoutes' :: Text
s3Bucket = Text
a} :: ExportTransitGatewayRoutes)

instance Core.AWSRequest ExportTransitGatewayRoutes where
  type
    AWSResponse ExportTransitGatewayRoutes =
      ExportTransitGatewayRoutesResponse
  request :: (Service -> Service)
-> ExportTransitGatewayRoutes -> Request ExportTransitGatewayRoutes
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 ExportTransitGatewayRoutes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ExportTransitGatewayRoutes)))
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 Text -> Int -> ExportTransitGatewayRoutesResponse
ExportTransitGatewayRoutesResponse'
            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
"s3Location")
            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 ExportTransitGatewayRoutes where
  hashWithSalt :: Int -> ExportTransitGatewayRoutes -> Int
hashWithSalt Int
_salt ExportTransitGatewayRoutes' {Maybe Bool
Maybe [Filter]
Text
s3Bucket :: Text
transitGatewayRouteTableId :: Text
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:s3Bucket:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
$sel:transitGatewayRouteTableId:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
$sel:filters:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Maybe [Filter]
$sel:dryRun:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> 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 [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
transitGatewayRouteTableId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3Bucket

instance Prelude.NFData ExportTransitGatewayRoutes where
  rnf :: ExportTransitGatewayRoutes -> ()
rnf ExportTransitGatewayRoutes' {Maybe Bool
Maybe [Filter]
Text
s3Bucket :: Text
transitGatewayRouteTableId :: Text
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:s3Bucket:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
$sel:transitGatewayRouteTableId:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
$sel:filters:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Maybe [Filter]
$sel:dryRun:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> 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 [Filter]
filters
      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
s3Bucket

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

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

instance Data.ToQuery ExportTransitGatewayRoutes where
  toQuery :: ExportTransitGatewayRoutes -> QueryString
toQuery ExportTransitGatewayRoutes' {Maybe Bool
Maybe [Filter]
Text
s3Bucket :: Text
transitGatewayRouteTableId :: Text
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:s3Bucket:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
$sel:transitGatewayRouteTableId:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Text
$sel:filters:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Maybe [Filter]
$sel:dryRun:ExportTransitGatewayRoutes' :: ExportTransitGatewayRoutes -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ExportTransitGatewayRoutes" :: 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,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Filter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters),
        ByteString
"TransitGatewayRouteTableId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
transitGatewayRouteTableId,
        ByteString
"S3Bucket" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
s3Bucket
      ]

-- | /See:/ 'newExportTransitGatewayRoutesResponse' smart constructor.
data ExportTransitGatewayRoutesResponse = ExportTransitGatewayRoutesResponse'
  { -- | The URL of the exported file in Amazon S3. For example,
    -- s3:\/\//bucket_name/\/VPCTransitGateway\/TransitGatewayRouteTables\//file_name/.
    ExportTransitGatewayRoutesResponse -> Maybe Text
s3Location :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ExportTransitGatewayRoutesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ExportTransitGatewayRoutesResponse
-> ExportTransitGatewayRoutesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportTransitGatewayRoutesResponse
-> ExportTransitGatewayRoutesResponse -> Bool
$c/= :: ExportTransitGatewayRoutesResponse
-> ExportTransitGatewayRoutesResponse -> Bool
== :: ExportTransitGatewayRoutesResponse
-> ExportTransitGatewayRoutesResponse -> Bool
$c== :: ExportTransitGatewayRoutesResponse
-> ExportTransitGatewayRoutesResponse -> Bool
Prelude.Eq, ReadPrec [ExportTransitGatewayRoutesResponse]
ReadPrec ExportTransitGatewayRoutesResponse
Int -> ReadS ExportTransitGatewayRoutesResponse
ReadS [ExportTransitGatewayRoutesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExportTransitGatewayRoutesResponse]
$creadListPrec :: ReadPrec [ExportTransitGatewayRoutesResponse]
readPrec :: ReadPrec ExportTransitGatewayRoutesResponse
$creadPrec :: ReadPrec ExportTransitGatewayRoutesResponse
readList :: ReadS [ExportTransitGatewayRoutesResponse]
$creadList :: ReadS [ExportTransitGatewayRoutesResponse]
readsPrec :: Int -> ReadS ExportTransitGatewayRoutesResponse
$creadsPrec :: Int -> ReadS ExportTransitGatewayRoutesResponse
Prelude.Read, Int -> ExportTransitGatewayRoutesResponse -> ShowS
[ExportTransitGatewayRoutesResponse] -> ShowS
ExportTransitGatewayRoutesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportTransitGatewayRoutesResponse] -> ShowS
$cshowList :: [ExportTransitGatewayRoutesResponse] -> ShowS
show :: ExportTransitGatewayRoutesResponse -> String
$cshow :: ExportTransitGatewayRoutesResponse -> String
showsPrec :: Int -> ExportTransitGatewayRoutesResponse -> ShowS
$cshowsPrec :: Int -> ExportTransitGatewayRoutesResponse -> ShowS
Prelude.Show, forall x.
Rep ExportTransitGatewayRoutesResponse x
-> ExportTransitGatewayRoutesResponse
forall x.
ExportTransitGatewayRoutesResponse
-> Rep ExportTransitGatewayRoutesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExportTransitGatewayRoutesResponse x
-> ExportTransitGatewayRoutesResponse
$cfrom :: forall x.
ExportTransitGatewayRoutesResponse
-> Rep ExportTransitGatewayRoutesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ExportTransitGatewayRoutesResponse' 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:
--
-- 's3Location', 'exportTransitGatewayRoutesResponse_s3Location' - The URL of the exported file in Amazon S3. For example,
-- s3:\/\//bucket_name/\/VPCTransitGateway\/TransitGatewayRouteTables\//file_name/.
--
-- 'httpStatus', 'exportTransitGatewayRoutesResponse_httpStatus' - The response's http status code.
newExportTransitGatewayRoutesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ExportTransitGatewayRoutesResponse
newExportTransitGatewayRoutesResponse :: Int -> ExportTransitGatewayRoutesResponse
newExportTransitGatewayRoutesResponse Int
pHttpStatus_ =
  ExportTransitGatewayRoutesResponse'
    { $sel:s3Location:ExportTransitGatewayRoutesResponse' :: Maybe Text
s3Location =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ExportTransitGatewayRoutesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The URL of the exported file in Amazon S3. For example,
-- s3:\/\//bucket_name/\/VPCTransitGateway\/TransitGatewayRouteTables\//file_name/.
exportTransitGatewayRoutesResponse_s3Location :: Lens.Lens' ExportTransitGatewayRoutesResponse (Prelude.Maybe Prelude.Text)
exportTransitGatewayRoutesResponse_s3Location :: Lens' ExportTransitGatewayRoutesResponse (Maybe Text)
exportTransitGatewayRoutesResponse_s3Location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportTransitGatewayRoutesResponse' {Maybe Text
s3Location :: Maybe Text
$sel:s3Location:ExportTransitGatewayRoutesResponse' :: ExportTransitGatewayRoutesResponse -> Maybe Text
s3Location} -> Maybe Text
s3Location) (\s :: ExportTransitGatewayRoutesResponse
s@ExportTransitGatewayRoutesResponse' {} Maybe Text
a -> ExportTransitGatewayRoutesResponse
s {$sel:s3Location:ExportTransitGatewayRoutesResponse' :: Maybe Text
s3Location = Maybe Text
a} :: ExportTransitGatewayRoutesResponse)

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

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