{-# 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.CreateRoute
-- 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 route in a route table within a VPC.
--
-- You must specify either a destination CIDR block or a prefix list ID.
-- You must also specify exactly one of the resources from the parameter
-- list.
--
-- When determining how to route traffic, we use the route with the most
-- specific match. For example, traffic is destined for the IPv4 address
-- @192.0.2.3@, and the route table includes the following two IPv4 routes:
--
-- -   @192.0.2.0\/24@ (goes to some target A)
--
-- -   @192.0.2.0\/28@ (goes to some target B)
--
-- Both routes apply to the traffic destined for @192.0.2.3@. However, the
-- second route in the list covers a smaller number of IP addresses and is
-- therefore more specific, so we use that route to determine where to
-- target the traffic.
--
-- 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/.
module Amazonka.EC2.CreateRoute
  ( -- * Creating a Request
    CreateRoute (..),
    newCreateRoute,

    -- * Request Lenses
    createRoute_carrierGatewayId,
    createRoute_coreNetworkArn,
    createRoute_destinationCidrBlock,
    createRoute_destinationIpv6CidrBlock,
    createRoute_destinationPrefixListId,
    createRoute_dryRun,
    createRoute_egressOnlyInternetGatewayId,
    createRoute_gatewayId,
    createRoute_instanceId,
    createRoute_localGatewayId,
    createRoute_natGatewayId,
    createRoute_networkInterfaceId,
    createRoute_transitGatewayId,
    createRoute_vpcEndpointId,
    createRoute_vpcPeeringConnectionId,
    createRoute_routeTableId,

    -- * Destructuring the Response
    CreateRouteResponse (..),
    newCreateRouteResponse,

    -- * Response Lenses
    createRouteResponse_return,
    createRouteResponse_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:/ 'newCreateRoute' smart constructor.
data CreateRoute = CreateRoute'
  { -- | The ID of the carrier gateway.
    --
    -- You can only use this option when the VPC contains a subnet which is
    -- associated with a Wavelength Zone.
    CreateRoute -> Maybe Text
carrierGatewayId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the core network.
    CreateRoute -> Maybe Text
coreNetworkArn :: Prelude.Maybe Prelude.Text,
    -- | The IPv4 CIDR address block used for the destination match. Routing
    -- decisions are based on the most specific match. We modify the specified
    -- CIDR block to its canonical form; for example, if you specify
    -- @100.68.0.18\/18@, we modify it to @100.68.0.0\/18@.
    CreateRoute -> Maybe Text
destinationCidrBlock :: Prelude.Maybe Prelude.Text,
    -- | The IPv6 CIDR block used for the destination match. Routing decisions
    -- are based on the most specific match.
    CreateRoute -> Maybe Text
destinationIpv6CidrBlock :: Prelude.Maybe Prelude.Text,
    -- | The ID of a prefix list used for the destination match.
    CreateRoute -> Maybe Text
destinationPrefixListId :: Prelude.Maybe Prelude.Text,
    -- | 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@.
    CreateRoute -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | [IPv6 traffic only] The ID of an egress-only internet gateway.
    CreateRoute -> Maybe Text
egressOnlyInternetGatewayId :: Prelude.Maybe Prelude.Text,
    -- | The ID of an internet gateway or virtual private gateway attached to
    -- your VPC.
    CreateRoute -> Maybe Text
gatewayId :: Prelude.Maybe Prelude.Text,
    -- | The ID of a NAT instance in your VPC. The operation fails if you specify
    -- an instance ID unless exactly one network interface is attached.
    CreateRoute -> Maybe Text
instanceId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the local gateway.
    CreateRoute -> Maybe Text
localGatewayId :: Prelude.Maybe Prelude.Text,
    -- | [IPv4 traffic only] The ID of a NAT gateway.
    CreateRoute -> Maybe Text
natGatewayId :: Prelude.Maybe Prelude.Text,
    -- | The ID of a network interface.
    CreateRoute -> Maybe Text
networkInterfaceId :: Prelude.Maybe Prelude.Text,
    -- | The ID of a transit gateway.
    CreateRoute -> Maybe Text
transitGatewayId :: Prelude.Maybe Prelude.Text,
    -- | The ID of a VPC endpoint. Supported for Gateway Load Balancer endpoints
    -- only.
    CreateRoute -> Maybe Text
vpcEndpointId :: Prelude.Maybe Prelude.Text,
    -- | The ID of a VPC peering connection.
    CreateRoute -> Maybe Text
vpcPeeringConnectionId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the route table for the route.
    CreateRoute -> Text
routeTableId :: Prelude.Text
  }
  deriving (CreateRoute -> CreateRoute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRoute -> CreateRoute -> Bool
$c/= :: CreateRoute -> CreateRoute -> Bool
== :: CreateRoute -> CreateRoute -> Bool
$c== :: CreateRoute -> CreateRoute -> Bool
Prelude.Eq, ReadPrec [CreateRoute]
ReadPrec CreateRoute
Int -> ReadS CreateRoute
ReadS [CreateRoute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRoute]
$creadListPrec :: ReadPrec [CreateRoute]
readPrec :: ReadPrec CreateRoute
$creadPrec :: ReadPrec CreateRoute
readList :: ReadS [CreateRoute]
$creadList :: ReadS [CreateRoute]
readsPrec :: Int -> ReadS CreateRoute
$creadsPrec :: Int -> ReadS CreateRoute
Prelude.Read, Int -> CreateRoute -> ShowS
[CreateRoute] -> ShowS
CreateRoute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRoute] -> ShowS
$cshowList :: [CreateRoute] -> ShowS
show :: CreateRoute -> String
$cshow :: CreateRoute -> String
showsPrec :: Int -> CreateRoute -> ShowS
$cshowsPrec :: Int -> CreateRoute -> ShowS
Prelude.Show, forall x. Rep CreateRoute x -> CreateRoute
forall x. CreateRoute -> Rep CreateRoute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRoute x -> CreateRoute
$cfrom :: forall x. CreateRoute -> Rep CreateRoute x
Prelude.Generic)

-- |
-- Create a value of 'CreateRoute' 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:
--
-- 'carrierGatewayId', 'createRoute_carrierGatewayId' - The ID of the carrier gateway.
--
-- You can only use this option when the VPC contains a subnet which is
-- associated with a Wavelength Zone.
--
-- 'coreNetworkArn', 'createRoute_coreNetworkArn' - The Amazon Resource Name (ARN) of the core network.
--
-- 'destinationCidrBlock', 'createRoute_destinationCidrBlock' - The IPv4 CIDR address block used for the destination match. Routing
-- decisions are based on the most specific match. We modify the specified
-- CIDR block to its canonical form; for example, if you specify
-- @100.68.0.18\/18@, we modify it to @100.68.0.0\/18@.
--
-- 'destinationIpv6CidrBlock', 'createRoute_destinationIpv6CidrBlock' - The IPv6 CIDR block used for the destination match. Routing decisions
-- are based on the most specific match.
--
-- 'destinationPrefixListId', 'createRoute_destinationPrefixListId' - The ID of a prefix list used for the destination match.
--
-- 'dryRun', 'createRoute_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@.
--
-- 'egressOnlyInternetGatewayId', 'createRoute_egressOnlyInternetGatewayId' - [IPv6 traffic only] The ID of an egress-only internet gateway.
--
-- 'gatewayId', 'createRoute_gatewayId' - The ID of an internet gateway or virtual private gateway attached to
-- your VPC.
--
-- 'instanceId', 'createRoute_instanceId' - The ID of a NAT instance in your VPC. The operation fails if you specify
-- an instance ID unless exactly one network interface is attached.
--
-- 'localGatewayId', 'createRoute_localGatewayId' - The ID of the local gateway.
--
-- 'natGatewayId', 'createRoute_natGatewayId' - [IPv4 traffic only] The ID of a NAT gateway.
--
-- 'networkInterfaceId', 'createRoute_networkInterfaceId' - The ID of a network interface.
--
-- 'transitGatewayId', 'createRoute_transitGatewayId' - The ID of a transit gateway.
--
-- 'vpcEndpointId', 'createRoute_vpcEndpointId' - The ID of a VPC endpoint. Supported for Gateway Load Balancer endpoints
-- only.
--
-- 'vpcPeeringConnectionId', 'createRoute_vpcPeeringConnectionId' - The ID of a VPC peering connection.
--
-- 'routeTableId', 'createRoute_routeTableId' - The ID of the route table for the route.
newCreateRoute ::
  -- | 'routeTableId'
  Prelude.Text ->
  CreateRoute
newCreateRoute :: Text -> CreateRoute
newCreateRoute Text
pRouteTableId_ =
  CreateRoute'
    { $sel:carrierGatewayId:CreateRoute' :: Maybe Text
carrierGatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:coreNetworkArn:CreateRoute' :: Maybe Text
coreNetworkArn = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationCidrBlock:CreateRoute' :: Maybe Text
destinationCidrBlock = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationIpv6CidrBlock:CreateRoute' :: Maybe Text
destinationIpv6CidrBlock = forall a. Maybe a
Prelude.Nothing,
      $sel:destinationPrefixListId:CreateRoute' :: Maybe Text
destinationPrefixListId = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:CreateRoute' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:egressOnlyInternetGatewayId:CreateRoute' :: Maybe Text
egressOnlyInternetGatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:gatewayId:CreateRoute' :: Maybe Text
gatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:CreateRoute' :: Maybe Text
instanceId = forall a. Maybe a
Prelude.Nothing,
      $sel:localGatewayId:CreateRoute' :: Maybe Text
localGatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:natGatewayId:CreateRoute' :: Maybe Text
natGatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaceId:CreateRoute' :: Maybe Text
networkInterfaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:transitGatewayId:CreateRoute' :: Maybe Text
transitGatewayId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcEndpointId:CreateRoute' :: Maybe Text
vpcEndpointId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcPeeringConnectionId:CreateRoute' :: Maybe Text
vpcPeeringConnectionId = forall a. Maybe a
Prelude.Nothing,
      $sel:routeTableId:CreateRoute' :: Text
routeTableId = Text
pRouteTableId_
    }

-- | The ID of the carrier gateway.
--
-- You can only use this option when the VPC contains a subnet which is
-- associated with a Wavelength Zone.
createRoute_carrierGatewayId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_carrierGatewayId :: Lens' CreateRoute (Maybe Text)
createRoute_carrierGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
carrierGatewayId :: Maybe Text
$sel:carrierGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
carrierGatewayId} -> Maybe Text
carrierGatewayId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:carrierGatewayId:CreateRoute' :: Maybe Text
carrierGatewayId = Maybe Text
a} :: CreateRoute)

-- | The Amazon Resource Name (ARN) of the core network.
createRoute_coreNetworkArn :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_coreNetworkArn :: Lens' CreateRoute (Maybe Text)
createRoute_coreNetworkArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
coreNetworkArn :: Maybe Text
$sel:coreNetworkArn:CreateRoute' :: CreateRoute -> Maybe Text
coreNetworkArn} -> Maybe Text
coreNetworkArn) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:coreNetworkArn:CreateRoute' :: Maybe Text
coreNetworkArn = Maybe Text
a} :: CreateRoute)

-- | The IPv4 CIDR address block used for the destination match. Routing
-- decisions are based on the most specific match. We modify the specified
-- CIDR block to its canonical form; for example, if you specify
-- @100.68.0.18\/18@, we modify it to @100.68.0.0\/18@.
createRoute_destinationCidrBlock :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_destinationCidrBlock :: Lens' CreateRoute (Maybe Text)
createRoute_destinationCidrBlock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
destinationCidrBlock :: Maybe Text
$sel:destinationCidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
destinationCidrBlock} -> Maybe Text
destinationCidrBlock) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:destinationCidrBlock:CreateRoute' :: Maybe Text
destinationCidrBlock = Maybe Text
a} :: CreateRoute)

-- | The IPv6 CIDR block used for the destination match. Routing decisions
-- are based on the most specific match.
createRoute_destinationIpv6CidrBlock :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_destinationIpv6CidrBlock :: Lens' CreateRoute (Maybe Text)
createRoute_destinationIpv6CidrBlock = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
destinationIpv6CidrBlock :: Maybe Text
$sel:destinationIpv6CidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
destinationIpv6CidrBlock} -> Maybe Text
destinationIpv6CidrBlock) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:destinationIpv6CidrBlock:CreateRoute' :: Maybe Text
destinationIpv6CidrBlock = Maybe Text
a} :: CreateRoute)

-- | The ID of a prefix list used for the destination match.
createRoute_destinationPrefixListId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_destinationPrefixListId :: Lens' CreateRoute (Maybe Text)
createRoute_destinationPrefixListId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
destinationPrefixListId :: Maybe Text
$sel:destinationPrefixListId:CreateRoute' :: CreateRoute -> Maybe Text
destinationPrefixListId} -> Maybe Text
destinationPrefixListId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:destinationPrefixListId:CreateRoute' :: Maybe Text
destinationPrefixListId = Maybe Text
a} :: CreateRoute)

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

-- | [IPv6 traffic only] The ID of an egress-only internet gateway.
createRoute_egressOnlyInternetGatewayId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_egressOnlyInternetGatewayId :: Lens' CreateRoute (Maybe Text)
createRoute_egressOnlyInternetGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
egressOnlyInternetGatewayId :: Maybe Text
$sel:egressOnlyInternetGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
egressOnlyInternetGatewayId} -> Maybe Text
egressOnlyInternetGatewayId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:egressOnlyInternetGatewayId:CreateRoute' :: Maybe Text
egressOnlyInternetGatewayId = Maybe Text
a} :: CreateRoute)

-- | The ID of an internet gateway or virtual private gateway attached to
-- your VPC.
createRoute_gatewayId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_gatewayId :: Lens' CreateRoute (Maybe Text)
createRoute_gatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
gatewayId :: Maybe Text
$sel:gatewayId:CreateRoute' :: CreateRoute -> Maybe Text
gatewayId} -> Maybe Text
gatewayId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:gatewayId:CreateRoute' :: Maybe Text
gatewayId = Maybe Text
a} :: CreateRoute)

-- | The ID of a NAT instance in your VPC. The operation fails if you specify
-- an instance ID unless exactly one network interface is attached.
createRoute_instanceId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_instanceId :: Lens' CreateRoute (Maybe Text)
createRoute_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
instanceId :: Maybe Text
$sel:instanceId:CreateRoute' :: CreateRoute -> Maybe Text
instanceId} -> Maybe Text
instanceId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:instanceId:CreateRoute' :: Maybe Text
instanceId = Maybe Text
a} :: CreateRoute)

-- | The ID of the local gateway.
createRoute_localGatewayId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_localGatewayId :: Lens' CreateRoute (Maybe Text)
createRoute_localGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
localGatewayId :: Maybe Text
$sel:localGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
localGatewayId} -> Maybe Text
localGatewayId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:localGatewayId:CreateRoute' :: Maybe Text
localGatewayId = Maybe Text
a} :: CreateRoute)

-- | [IPv4 traffic only] The ID of a NAT gateway.
createRoute_natGatewayId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_natGatewayId :: Lens' CreateRoute (Maybe Text)
createRoute_natGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
natGatewayId :: Maybe Text
$sel:natGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
natGatewayId} -> Maybe Text
natGatewayId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:natGatewayId:CreateRoute' :: Maybe Text
natGatewayId = Maybe Text
a} :: CreateRoute)

-- | The ID of a network interface.
createRoute_networkInterfaceId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_networkInterfaceId :: Lens' CreateRoute (Maybe Text)
createRoute_networkInterfaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
networkInterfaceId :: Maybe Text
$sel:networkInterfaceId:CreateRoute' :: CreateRoute -> Maybe Text
networkInterfaceId} -> Maybe Text
networkInterfaceId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:networkInterfaceId:CreateRoute' :: Maybe Text
networkInterfaceId = Maybe Text
a} :: CreateRoute)

-- | The ID of a transit gateway.
createRoute_transitGatewayId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_transitGatewayId :: Lens' CreateRoute (Maybe Text)
createRoute_transitGatewayId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
transitGatewayId :: Maybe Text
$sel:transitGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
transitGatewayId} -> Maybe Text
transitGatewayId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:transitGatewayId:CreateRoute' :: Maybe Text
transitGatewayId = Maybe Text
a} :: CreateRoute)

-- | The ID of a VPC endpoint. Supported for Gateway Load Balancer endpoints
-- only.
createRoute_vpcEndpointId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_vpcEndpointId :: Lens' CreateRoute (Maybe Text)
createRoute_vpcEndpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
vpcEndpointId :: Maybe Text
$sel:vpcEndpointId:CreateRoute' :: CreateRoute -> Maybe Text
vpcEndpointId} -> Maybe Text
vpcEndpointId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:vpcEndpointId:CreateRoute' :: Maybe Text
vpcEndpointId = Maybe Text
a} :: CreateRoute)

-- | The ID of a VPC peering connection.
createRoute_vpcPeeringConnectionId :: Lens.Lens' CreateRoute (Prelude.Maybe Prelude.Text)
createRoute_vpcPeeringConnectionId :: Lens' CreateRoute (Maybe Text)
createRoute_vpcPeeringConnectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoute' {Maybe Text
vpcPeeringConnectionId :: Maybe Text
$sel:vpcPeeringConnectionId:CreateRoute' :: CreateRoute -> Maybe Text
vpcPeeringConnectionId} -> Maybe Text
vpcPeeringConnectionId) (\s :: CreateRoute
s@CreateRoute' {} Maybe Text
a -> CreateRoute
s {$sel:vpcPeeringConnectionId:CreateRoute' :: Maybe Text
vpcPeeringConnectionId = Maybe Text
a} :: CreateRoute)

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

instance Core.AWSRequest CreateRoute where
  type AWSResponse CreateRoute = CreateRouteResponse
  request :: (Service -> Service) -> CreateRoute -> Request CreateRoute
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 CreateRoute
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateRoute)))
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 Bool -> Int -> CreateRouteResponse
CreateRouteResponse'
            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
"return")
            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 CreateRoute where
  hashWithSalt :: Int -> CreateRoute -> Int
hashWithSalt Int
_salt CreateRoute' {Maybe Bool
Maybe Text
Text
routeTableId :: Text
vpcPeeringConnectionId :: Maybe Text
vpcEndpointId :: Maybe Text
transitGatewayId :: Maybe Text
networkInterfaceId :: Maybe Text
natGatewayId :: Maybe Text
localGatewayId :: Maybe Text
instanceId :: Maybe Text
gatewayId :: Maybe Text
egressOnlyInternetGatewayId :: Maybe Text
dryRun :: Maybe Bool
destinationPrefixListId :: Maybe Text
destinationIpv6CidrBlock :: Maybe Text
destinationCidrBlock :: Maybe Text
coreNetworkArn :: Maybe Text
carrierGatewayId :: Maybe Text
$sel:routeTableId:CreateRoute' :: CreateRoute -> Text
$sel:vpcPeeringConnectionId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:vpcEndpointId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:transitGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:networkInterfaceId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:natGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:localGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:instanceId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:gatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:egressOnlyInternetGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:dryRun:CreateRoute' :: CreateRoute -> Maybe Bool
$sel:destinationPrefixListId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:destinationIpv6CidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
$sel:destinationCidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
$sel:coreNetworkArn:CreateRoute' :: CreateRoute -> Maybe Text
$sel:carrierGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
carrierGatewayId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
coreNetworkArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationCidrBlock
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationIpv6CidrBlock
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destinationPrefixListId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
egressOnlyInternetGatewayId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
gatewayId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
localGatewayId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
natGatewayId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkInterfaceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transitGatewayId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcEndpointId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcPeeringConnectionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routeTableId

instance Prelude.NFData CreateRoute where
  rnf :: CreateRoute -> ()
rnf CreateRoute' {Maybe Bool
Maybe Text
Text
routeTableId :: Text
vpcPeeringConnectionId :: Maybe Text
vpcEndpointId :: Maybe Text
transitGatewayId :: Maybe Text
networkInterfaceId :: Maybe Text
natGatewayId :: Maybe Text
localGatewayId :: Maybe Text
instanceId :: Maybe Text
gatewayId :: Maybe Text
egressOnlyInternetGatewayId :: Maybe Text
dryRun :: Maybe Bool
destinationPrefixListId :: Maybe Text
destinationIpv6CidrBlock :: Maybe Text
destinationCidrBlock :: Maybe Text
coreNetworkArn :: Maybe Text
carrierGatewayId :: Maybe Text
$sel:routeTableId:CreateRoute' :: CreateRoute -> Text
$sel:vpcPeeringConnectionId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:vpcEndpointId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:transitGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:networkInterfaceId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:natGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:localGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:instanceId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:gatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:egressOnlyInternetGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:dryRun:CreateRoute' :: CreateRoute -> Maybe Bool
$sel:destinationPrefixListId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:destinationIpv6CidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
$sel:destinationCidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
$sel:coreNetworkArn:CreateRoute' :: CreateRoute -> Maybe Text
$sel:carrierGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
carrierGatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
coreNetworkArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationCidrBlock
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationIpv6CidrBlock
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destinationPrefixListId
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
egressOnlyInternetGatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
localGatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
natGatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
networkInterfaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transitGatewayId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcEndpointId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcPeeringConnectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
routeTableId

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

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

instance Data.ToQuery CreateRoute where
  toQuery :: CreateRoute -> QueryString
toQuery CreateRoute' {Maybe Bool
Maybe Text
Text
routeTableId :: Text
vpcPeeringConnectionId :: Maybe Text
vpcEndpointId :: Maybe Text
transitGatewayId :: Maybe Text
networkInterfaceId :: Maybe Text
natGatewayId :: Maybe Text
localGatewayId :: Maybe Text
instanceId :: Maybe Text
gatewayId :: Maybe Text
egressOnlyInternetGatewayId :: Maybe Text
dryRun :: Maybe Bool
destinationPrefixListId :: Maybe Text
destinationIpv6CidrBlock :: Maybe Text
destinationCidrBlock :: Maybe Text
coreNetworkArn :: Maybe Text
carrierGatewayId :: Maybe Text
$sel:routeTableId:CreateRoute' :: CreateRoute -> Text
$sel:vpcPeeringConnectionId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:vpcEndpointId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:transitGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:networkInterfaceId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:natGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:localGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:instanceId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:gatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:egressOnlyInternetGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:dryRun:CreateRoute' :: CreateRoute -> Maybe Bool
$sel:destinationPrefixListId:CreateRoute' :: CreateRoute -> Maybe Text
$sel:destinationIpv6CidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
$sel:destinationCidrBlock:CreateRoute' :: CreateRoute -> Maybe Text
$sel:coreNetworkArn:CreateRoute' :: CreateRoute -> Maybe Text
$sel:carrierGatewayId:CreateRoute' :: CreateRoute -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateRoute" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"CarrierGatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
carrierGatewayId,
        ByteString
"CoreNetworkArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
coreNetworkArn,
        ByteString
"DestinationCidrBlock" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationCidrBlock,
        ByteString
"DestinationIpv6CidrBlock"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationIpv6CidrBlock,
        ByteString
"DestinationPrefixListId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
destinationPrefixListId,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"EgressOnlyInternetGatewayId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
egressOnlyInternetGatewayId,
        ByteString
"GatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
gatewayId,
        ByteString
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
instanceId,
        ByteString
"LocalGatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
localGatewayId,
        ByteString
"NatGatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
natGatewayId,
        ByteString
"NetworkInterfaceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
networkInterfaceId,
        ByteString
"TransitGatewayId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
transitGatewayId,
        ByteString
"VpcEndpointId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
vpcEndpointId,
        ByteString
"VpcPeeringConnectionId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
vpcPeeringConnectionId,
        ByteString
"RouteTableId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
routeTableId
      ]

-- | /See:/ 'newCreateRouteResponse' smart constructor.
data CreateRouteResponse = CreateRouteResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    CreateRouteResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    CreateRouteResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateRouteResponse -> CreateRouteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRouteResponse -> CreateRouteResponse -> Bool
$c/= :: CreateRouteResponse -> CreateRouteResponse -> Bool
== :: CreateRouteResponse -> CreateRouteResponse -> Bool
$c== :: CreateRouteResponse -> CreateRouteResponse -> Bool
Prelude.Eq, ReadPrec [CreateRouteResponse]
ReadPrec CreateRouteResponse
Int -> ReadS CreateRouteResponse
ReadS [CreateRouteResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRouteResponse]
$creadListPrec :: ReadPrec [CreateRouteResponse]
readPrec :: ReadPrec CreateRouteResponse
$creadPrec :: ReadPrec CreateRouteResponse
readList :: ReadS [CreateRouteResponse]
$creadList :: ReadS [CreateRouteResponse]
readsPrec :: Int -> ReadS CreateRouteResponse
$creadsPrec :: Int -> ReadS CreateRouteResponse
Prelude.Read, Int -> CreateRouteResponse -> ShowS
[CreateRouteResponse] -> ShowS
CreateRouteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRouteResponse] -> ShowS
$cshowList :: [CreateRouteResponse] -> ShowS
show :: CreateRouteResponse -> String
$cshow :: CreateRouteResponse -> String
showsPrec :: Int -> CreateRouteResponse -> ShowS
$cshowsPrec :: Int -> CreateRouteResponse -> ShowS
Prelude.Show, forall x. Rep CreateRouteResponse x -> CreateRouteResponse
forall x. CreateRouteResponse -> Rep CreateRouteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRouteResponse x -> CreateRouteResponse
$cfrom :: forall x. CreateRouteResponse -> Rep CreateRouteResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateRouteResponse' 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:
--
-- 'return'', 'createRouteResponse_return' - Returns @true@ if the request succeeds; otherwise, it returns an error.
--
-- 'httpStatus', 'createRouteResponse_httpStatus' - The response's http status code.
newCreateRouteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRouteResponse
newCreateRouteResponse :: Int -> CreateRouteResponse
newCreateRouteResponse Int
pHttpStatus_ =
  CreateRouteResponse'
    { $sel:return':CreateRouteResponse' :: Maybe Bool
return' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRouteResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns @true@ if the request succeeds; otherwise, it returns an error.
createRouteResponse_return :: Lens.Lens' CreateRouteResponse (Prelude.Maybe Prelude.Bool)
createRouteResponse_return :: Lens' CreateRouteResponse (Maybe Bool)
createRouteResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRouteResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':CreateRouteResponse' :: CreateRouteResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: CreateRouteResponse
s@CreateRouteResponse' {} Maybe Bool
a -> CreateRouteResponse
s {$sel:return':CreateRouteResponse' :: Maybe Bool
return' = Maybe Bool
a} :: CreateRouteResponse)

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

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