{-# 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.MigrationHubReFactorSpaces.GetRoute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets an Amazon Web Services Migration Hub Refactor Spaces route.
module Amazonka.MigrationHubReFactorSpaces.GetRoute
  ( -- * Creating a Request
    GetRoute (..),
    newGetRoute,

    -- * Request Lenses
    getRoute_applicationIdentifier,
    getRoute_environmentIdentifier,
    getRoute_routeIdentifier,

    -- * Destructuring the Response
    GetRouteResponse (..),
    newGetRouteResponse,

    -- * Response Lenses
    getRouteResponse_applicationId,
    getRouteResponse_arn,
    getRouteResponse_createdByAccountId,
    getRouteResponse_createdTime,
    getRouteResponse_environmentId,
    getRouteResponse_error,
    getRouteResponse_includeChildPaths,
    getRouteResponse_lastUpdatedTime,
    getRouteResponse_methods,
    getRouteResponse_ownerAccountId,
    getRouteResponse_pathResourceToId,
    getRouteResponse_routeId,
    getRouteResponse_routeType,
    getRouteResponse_serviceId,
    getRouteResponse_sourcePath,
    getRouteResponse_state,
    getRouteResponse_tags,
    getRouteResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MigrationHubReFactorSpaces.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetRoute' smart constructor.
data GetRoute = GetRoute'
  { -- | The ID of the application.
    GetRoute -> Text
applicationIdentifier :: Prelude.Text,
    -- | The ID of the environment.
    GetRoute -> Text
environmentIdentifier :: Prelude.Text,
    -- | The ID of the route.
    GetRoute -> Text
routeIdentifier :: Prelude.Text
  }
  deriving (GetRoute -> GetRoute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRoute -> GetRoute -> Bool
$c/= :: GetRoute -> GetRoute -> Bool
== :: GetRoute -> GetRoute -> Bool
$c== :: GetRoute -> GetRoute -> Bool
Prelude.Eq, ReadPrec [GetRoute]
ReadPrec GetRoute
Int -> ReadS GetRoute
ReadS [GetRoute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetRoute]
$creadListPrec :: ReadPrec [GetRoute]
readPrec :: ReadPrec GetRoute
$creadPrec :: ReadPrec GetRoute
readList :: ReadS [GetRoute]
$creadList :: ReadS [GetRoute]
readsPrec :: Int -> ReadS GetRoute
$creadsPrec :: Int -> ReadS GetRoute
Prelude.Read, Int -> GetRoute -> ShowS
[GetRoute] -> ShowS
GetRoute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRoute] -> ShowS
$cshowList :: [GetRoute] -> ShowS
show :: GetRoute -> String
$cshow :: GetRoute -> String
showsPrec :: Int -> GetRoute -> ShowS
$cshowsPrec :: Int -> GetRoute -> ShowS
Prelude.Show, forall x. Rep GetRoute x -> GetRoute
forall x. GetRoute -> Rep GetRoute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRoute x -> GetRoute
$cfrom :: forall x. GetRoute -> Rep GetRoute x
Prelude.Generic)

-- |
-- Create a value of 'GetRoute' 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:
--
-- 'applicationIdentifier', 'getRoute_applicationIdentifier' - The ID of the application.
--
-- 'environmentIdentifier', 'getRoute_environmentIdentifier' - The ID of the environment.
--
-- 'routeIdentifier', 'getRoute_routeIdentifier' - The ID of the route.
newGetRoute ::
  -- | 'applicationIdentifier'
  Prelude.Text ->
  -- | 'environmentIdentifier'
  Prelude.Text ->
  -- | 'routeIdentifier'
  Prelude.Text ->
  GetRoute
newGetRoute :: Text -> Text -> Text -> GetRoute
newGetRoute
  Text
pApplicationIdentifier_
  Text
pEnvironmentIdentifier_
  Text
pRouteIdentifier_ =
    GetRoute'
      { $sel:applicationIdentifier:GetRoute' :: Text
applicationIdentifier =
          Text
pApplicationIdentifier_,
        $sel:environmentIdentifier:GetRoute' :: Text
environmentIdentifier = Text
pEnvironmentIdentifier_,
        $sel:routeIdentifier:GetRoute' :: Text
routeIdentifier = Text
pRouteIdentifier_
      }

-- | The ID of the application.
getRoute_applicationIdentifier :: Lens.Lens' GetRoute Prelude.Text
getRoute_applicationIdentifier :: Lens' GetRoute Text
getRoute_applicationIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRoute' {Text
applicationIdentifier :: Text
$sel:applicationIdentifier:GetRoute' :: GetRoute -> Text
applicationIdentifier} -> Text
applicationIdentifier) (\s :: GetRoute
s@GetRoute' {} Text
a -> GetRoute
s {$sel:applicationIdentifier:GetRoute' :: Text
applicationIdentifier = Text
a} :: GetRoute)

-- | The ID of the environment.
getRoute_environmentIdentifier :: Lens.Lens' GetRoute Prelude.Text
getRoute_environmentIdentifier :: Lens' GetRoute Text
getRoute_environmentIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRoute' {Text
environmentIdentifier :: Text
$sel:environmentIdentifier:GetRoute' :: GetRoute -> Text
environmentIdentifier} -> Text
environmentIdentifier) (\s :: GetRoute
s@GetRoute' {} Text
a -> GetRoute
s {$sel:environmentIdentifier:GetRoute' :: Text
environmentIdentifier = Text
a} :: GetRoute)

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

instance Core.AWSRequest GetRoute where
  type AWSResponse GetRoute = GetRouteResponse
  request :: (Service -> Service) -> GetRoute -> Request GetRoute
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetRoute
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetRoute)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe ErrorResponse
-> Maybe Bool
-> Maybe POSIX
-> Maybe [HttpMethod]
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe RouteType
-> Maybe Text
-> Maybe Text
-> Maybe RouteState
-> Maybe (Sensitive (HashMap Text Text))
-> Int
-> GetRouteResponse
GetRouteResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ApplicationId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedByAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EnvironmentId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Error")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"IncludeChildPaths")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LastUpdatedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Methods" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"OwnerAccountId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"PathResourceToId"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RouteId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RouteType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ServiceId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SourcePath")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"State")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 GetRoute where
  hashWithSalt :: Int -> GetRoute -> Int
hashWithSalt Int
_salt GetRoute' {Text
routeIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:routeIdentifier:GetRoute' :: GetRoute -> Text
$sel:environmentIdentifier:GetRoute' :: GetRoute -> Text
$sel:applicationIdentifier:GetRoute' :: GetRoute -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routeIdentifier

instance Prelude.NFData GetRoute where
  rnf :: GetRoute -> ()
rnf GetRoute' {Text
routeIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:routeIdentifier:GetRoute' :: GetRoute -> Text
$sel:environmentIdentifier:GetRoute' :: GetRoute -> Text
$sel:applicationIdentifier:GetRoute' :: GetRoute -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
routeIdentifier

instance Data.ToHeaders GetRoute where
  toHeaders :: GetRoute -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetRoute where
  toPath :: GetRoute -> ByteString
toPath GetRoute' {Text
routeIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:routeIdentifier:GetRoute' :: GetRoute -> Text
$sel:environmentIdentifier:GetRoute' :: GetRoute -> Text
$sel:applicationIdentifier:GetRoute' :: GetRoute -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/environments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentIdentifier,
        ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationIdentifier,
        ByteString
"/routes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
routeIdentifier
      ]

instance Data.ToQuery GetRoute where
  toQuery :: GetRoute -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetRouteResponse' smart constructor.
data GetRouteResponse = GetRouteResponse'
  { -- | The ID of the application that the route belongs to.
    GetRouteResponse -> Maybe Text
applicationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the route.
    GetRouteResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services account ID of the route creator.
    GetRouteResponse -> Maybe Text
createdByAccountId :: Prelude.Maybe Prelude.Text,
    -- | The timestamp of when the route is created.
    GetRouteResponse -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | Unique identifier of the environment.
    GetRouteResponse -> Maybe Text
environmentId :: Prelude.Maybe Prelude.Text,
    -- | Any error associated with the route resource.
    GetRouteResponse -> Maybe ErrorResponse
error :: Prelude.Maybe ErrorResponse,
    -- | Indicates whether to match all subpaths of the given source path. If
    -- this value is @false@, requests must match the source path exactly
    -- before they are forwarded to this route\'s service.
    GetRouteResponse -> Maybe Bool
includeChildPaths :: Prelude.Maybe Prelude.Bool,
    -- | A timestamp that indicates when the route was last updated.
    GetRouteResponse -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | A list of HTTP methods to match. An empty list matches all values. If a
    -- method is present, only HTTP requests using that method are forwarded to
    -- this route’s service.
    GetRouteResponse -> Maybe [HttpMethod]
methods :: Prelude.Maybe [HttpMethod],
    -- | The Amazon Web Services account ID of the route owner.
    GetRouteResponse -> Maybe Text
ownerAccountId :: Prelude.Maybe Prelude.Text,
    -- | A mapping of Amazon API Gateway path resources to resource IDs.
    GetRouteResponse -> Maybe (HashMap Text Text)
pathResourceToId :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The unique identifier of the route.
    --
    -- __DEFAULT__: All traffic that does not match another route is forwarded
    -- to the default route. Applications must have a default route before any
    -- other routes can be created.
    --
    -- __URI_PATH__: A route that is based on a URI path.
    GetRouteResponse -> Maybe Text
routeId :: Prelude.Maybe Prelude.Text,
    -- | The type of route.
    GetRouteResponse -> Maybe RouteType
routeType :: Prelude.Maybe RouteType,
    -- | The unique identifier of the service.
    GetRouteResponse -> Maybe Text
serviceId :: Prelude.Maybe Prelude.Text,
    -- | The path to use to match traffic. Paths must start with @\/@ and are
    -- relative to the base of the application.
    GetRouteResponse -> Maybe Text
sourcePath :: Prelude.Maybe Prelude.Text,
    -- | The current state of the route.
    GetRouteResponse -> Maybe RouteState
state :: Prelude.Maybe RouteState,
    -- | The tags assigned to the route. A tag is a label that you assign to an
    -- Amazon Web Services resource. Each tag consists of a key-value pair.
    GetRouteResponse -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The response's http status code.
    GetRouteResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetRouteResponse -> GetRouteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRouteResponse -> GetRouteResponse -> Bool
$c/= :: GetRouteResponse -> GetRouteResponse -> Bool
== :: GetRouteResponse -> GetRouteResponse -> Bool
$c== :: GetRouteResponse -> GetRouteResponse -> Bool
Prelude.Eq, Int -> GetRouteResponse -> ShowS
[GetRouteResponse] -> ShowS
GetRouteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRouteResponse] -> ShowS
$cshowList :: [GetRouteResponse] -> ShowS
show :: GetRouteResponse -> String
$cshow :: GetRouteResponse -> String
showsPrec :: Int -> GetRouteResponse -> ShowS
$cshowsPrec :: Int -> GetRouteResponse -> ShowS
Prelude.Show, forall x. Rep GetRouteResponse x -> GetRouteResponse
forall x. GetRouteResponse -> Rep GetRouteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRouteResponse x -> GetRouteResponse
$cfrom :: forall x. GetRouteResponse -> Rep GetRouteResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetRouteResponse' 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:
--
-- 'applicationId', 'getRouteResponse_applicationId' - The ID of the application that the route belongs to.
--
-- 'arn', 'getRouteResponse_arn' - The Amazon Resource Name (ARN) of the route.
--
-- 'createdByAccountId', 'getRouteResponse_createdByAccountId' - The Amazon Web Services account ID of the route creator.
--
-- 'createdTime', 'getRouteResponse_createdTime' - The timestamp of when the route is created.
--
-- 'environmentId', 'getRouteResponse_environmentId' - Unique identifier of the environment.
--
-- 'error', 'getRouteResponse_error' - Any error associated with the route resource.
--
-- 'includeChildPaths', 'getRouteResponse_includeChildPaths' - Indicates whether to match all subpaths of the given source path. If
-- this value is @false@, requests must match the source path exactly
-- before they are forwarded to this route\'s service.
--
-- 'lastUpdatedTime', 'getRouteResponse_lastUpdatedTime' - A timestamp that indicates when the route was last updated.
--
-- 'methods', 'getRouteResponse_methods' - A list of HTTP methods to match. An empty list matches all values. If a
-- method is present, only HTTP requests using that method are forwarded to
-- this route’s service.
--
-- 'ownerAccountId', 'getRouteResponse_ownerAccountId' - The Amazon Web Services account ID of the route owner.
--
-- 'pathResourceToId', 'getRouteResponse_pathResourceToId' - A mapping of Amazon API Gateway path resources to resource IDs.
--
-- 'routeId', 'getRouteResponse_routeId' - The unique identifier of the route.
--
-- __DEFAULT__: All traffic that does not match another route is forwarded
-- to the default route. Applications must have a default route before any
-- other routes can be created.
--
-- __URI_PATH__: A route that is based on a URI path.
--
-- 'routeType', 'getRouteResponse_routeType' - The type of route.
--
-- 'serviceId', 'getRouteResponse_serviceId' - The unique identifier of the service.
--
-- 'sourcePath', 'getRouteResponse_sourcePath' - The path to use to match traffic. Paths must start with @\/@ and are
-- relative to the base of the application.
--
-- 'state', 'getRouteResponse_state' - The current state of the route.
--
-- 'tags', 'getRouteResponse_tags' - The tags assigned to the route. A tag is a label that you assign to an
-- Amazon Web Services resource. Each tag consists of a key-value pair.
--
-- 'httpStatus', 'getRouteResponse_httpStatus' - The response's http status code.
newGetRouteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetRouteResponse
newGetRouteResponse :: Int -> GetRouteResponse
newGetRouteResponse Int
pHttpStatus_ =
  GetRouteResponse'
    { $sel:applicationId:GetRouteResponse' :: Maybe Text
applicationId = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:GetRouteResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdByAccountId:GetRouteResponse' :: Maybe Text
createdByAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTime:GetRouteResponse' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentId:GetRouteResponse' :: Maybe Text
environmentId = forall a. Maybe a
Prelude.Nothing,
      $sel:error:GetRouteResponse' :: Maybe ErrorResponse
error = forall a. Maybe a
Prelude.Nothing,
      $sel:includeChildPaths:GetRouteResponse' :: Maybe Bool
includeChildPaths = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTime:GetRouteResponse' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:methods:GetRouteResponse' :: Maybe [HttpMethod]
methods = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerAccountId:GetRouteResponse' :: Maybe Text
ownerAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:pathResourceToId:GetRouteResponse' :: Maybe (HashMap Text Text)
pathResourceToId = forall a. Maybe a
Prelude.Nothing,
      $sel:routeId:GetRouteResponse' :: Maybe Text
routeId = forall a. Maybe a
Prelude.Nothing,
      $sel:routeType:GetRouteResponse' :: Maybe RouteType
routeType = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceId:GetRouteResponse' :: Maybe Text
serviceId = forall a. Maybe a
Prelude.Nothing,
      $sel:sourcePath:GetRouteResponse' :: Maybe Text
sourcePath = forall a. Maybe a
Prelude.Nothing,
      $sel:state:GetRouteResponse' :: Maybe RouteState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetRouteResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetRouteResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID of the application that the route belongs to.
getRouteResponse_applicationId :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_applicationId :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
applicationId :: Maybe Text
$sel:applicationId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
applicationId} -> Maybe Text
applicationId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:applicationId:GetRouteResponse' :: Maybe Text
applicationId = Maybe Text
a} :: GetRouteResponse)

-- | The Amazon Resource Name (ARN) of the route.
getRouteResponse_arn :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_arn :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:GetRouteResponse' :: GetRouteResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:arn:GetRouteResponse' :: Maybe Text
arn = Maybe Text
a} :: GetRouteResponse)

-- | The Amazon Web Services account ID of the route creator.
getRouteResponse_createdByAccountId :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_createdByAccountId :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_createdByAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
createdByAccountId :: Maybe Text
$sel:createdByAccountId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
createdByAccountId} -> Maybe Text
createdByAccountId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:createdByAccountId:GetRouteResponse' :: Maybe Text
createdByAccountId = Maybe Text
a} :: GetRouteResponse)

-- | The timestamp of when the route is created.
getRouteResponse_createdTime :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.UTCTime)
getRouteResponse_createdTime :: Lens' GetRouteResponse (Maybe UTCTime)
getRouteResponse_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:GetRouteResponse' :: GetRouteResponse -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe POSIX
a -> GetRouteResponse
s {$sel:createdTime:GetRouteResponse' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: GetRouteResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Unique identifier of the environment.
getRouteResponse_environmentId :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_environmentId :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
environmentId :: Maybe Text
$sel:environmentId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
environmentId} -> Maybe Text
environmentId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:environmentId:GetRouteResponse' :: Maybe Text
environmentId = Maybe Text
a} :: GetRouteResponse)

-- | Any error associated with the route resource.
getRouteResponse_error :: Lens.Lens' GetRouteResponse (Prelude.Maybe ErrorResponse)
getRouteResponse_error :: Lens' GetRouteResponse (Maybe ErrorResponse)
getRouteResponse_error = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe ErrorResponse
error :: Maybe ErrorResponse
$sel:error:GetRouteResponse' :: GetRouteResponse -> Maybe ErrorResponse
error} -> Maybe ErrorResponse
error) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe ErrorResponse
a -> GetRouteResponse
s {$sel:error:GetRouteResponse' :: Maybe ErrorResponse
error = Maybe ErrorResponse
a} :: GetRouteResponse)

-- | Indicates whether to match all subpaths of the given source path. If
-- this value is @false@, requests must match the source path exactly
-- before they are forwarded to this route\'s service.
getRouteResponse_includeChildPaths :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Bool)
getRouteResponse_includeChildPaths :: Lens' GetRouteResponse (Maybe Bool)
getRouteResponse_includeChildPaths = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Bool
includeChildPaths :: Maybe Bool
$sel:includeChildPaths:GetRouteResponse' :: GetRouteResponse -> Maybe Bool
includeChildPaths} -> Maybe Bool
includeChildPaths) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Bool
a -> GetRouteResponse
s {$sel:includeChildPaths:GetRouteResponse' :: Maybe Bool
includeChildPaths = Maybe Bool
a} :: GetRouteResponse)

-- | A timestamp that indicates when the route was last updated.
getRouteResponse_lastUpdatedTime :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.UTCTime)
getRouteResponse_lastUpdatedTime :: Lens' GetRouteResponse (Maybe UTCTime)
getRouteResponse_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe POSIX
lastUpdatedTime :: Maybe POSIX
$sel:lastUpdatedTime:GetRouteResponse' :: GetRouteResponse -> Maybe POSIX
lastUpdatedTime} -> Maybe POSIX
lastUpdatedTime) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe POSIX
a -> GetRouteResponse
s {$sel:lastUpdatedTime:GetRouteResponse' :: Maybe POSIX
lastUpdatedTime = Maybe POSIX
a} :: GetRouteResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A list of HTTP methods to match. An empty list matches all values. If a
-- method is present, only HTTP requests using that method are forwarded to
-- this route’s service.
getRouteResponse_methods :: Lens.Lens' GetRouteResponse (Prelude.Maybe [HttpMethod])
getRouteResponse_methods :: Lens' GetRouteResponse (Maybe [HttpMethod])
getRouteResponse_methods = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe [HttpMethod]
methods :: Maybe [HttpMethod]
$sel:methods:GetRouteResponse' :: GetRouteResponse -> Maybe [HttpMethod]
methods} -> Maybe [HttpMethod]
methods) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe [HttpMethod]
a -> GetRouteResponse
s {$sel:methods:GetRouteResponse' :: Maybe [HttpMethod]
methods = Maybe [HttpMethod]
a} :: GetRouteResponse) 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 Amazon Web Services account ID of the route owner.
getRouteResponse_ownerAccountId :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_ownerAccountId :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_ownerAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
ownerAccountId :: Maybe Text
$sel:ownerAccountId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
ownerAccountId} -> Maybe Text
ownerAccountId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:ownerAccountId:GetRouteResponse' :: Maybe Text
ownerAccountId = Maybe Text
a} :: GetRouteResponse)

-- | A mapping of Amazon API Gateway path resources to resource IDs.
getRouteResponse_pathResourceToId :: Lens.Lens' GetRouteResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getRouteResponse_pathResourceToId :: Lens' GetRouteResponse (Maybe (HashMap Text Text))
getRouteResponse_pathResourceToId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe (HashMap Text Text)
pathResourceToId :: Maybe (HashMap Text Text)
$sel:pathResourceToId:GetRouteResponse' :: GetRouteResponse -> Maybe (HashMap Text Text)
pathResourceToId} -> Maybe (HashMap Text Text)
pathResourceToId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe (HashMap Text Text)
a -> GetRouteResponse
s {$sel:pathResourceToId:GetRouteResponse' :: Maybe (HashMap Text Text)
pathResourceToId = Maybe (HashMap Text Text)
a} :: GetRouteResponse) 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 unique identifier of the route.
--
-- __DEFAULT__: All traffic that does not match another route is forwarded
-- to the default route. Applications must have a default route before any
-- other routes can be created.
--
-- __URI_PATH__: A route that is based on a URI path.
getRouteResponse_routeId :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_routeId :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_routeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
routeId :: Maybe Text
$sel:routeId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
routeId} -> Maybe Text
routeId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:routeId:GetRouteResponse' :: Maybe Text
routeId = Maybe Text
a} :: GetRouteResponse)

-- | The type of route.
getRouteResponse_routeType :: Lens.Lens' GetRouteResponse (Prelude.Maybe RouteType)
getRouteResponse_routeType :: Lens' GetRouteResponse (Maybe RouteType)
getRouteResponse_routeType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe RouteType
routeType :: Maybe RouteType
$sel:routeType:GetRouteResponse' :: GetRouteResponse -> Maybe RouteType
routeType} -> Maybe RouteType
routeType) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe RouteType
a -> GetRouteResponse
s {$sel:routeType:GetRouteResponse' :: Maybe RouteType
routeType = Maybe RouteType
a} :: GetRouteResponse)

-- | The unique identifier of the service.
getRouteResponse_serviceId :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_serviceId :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_serviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
serviceId :: Maybe Text
$sel:serviceId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
serviceId} -> Maybe Text
serviceId) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:serviceId:GetRouteResponse' :: Maybe Text
serviceId = Maybe Text
a} :: GetRouteResponse)

-- | The path to use to match traffic. Paths must start with @\/@ and are
-- relative to the base of the application.
getRouteResponse_sourcePath :: Lens.Lens' GetRouteResponse (Prelude.Maybe Prelude.Text)
getRouteResponse_sourcePath :: Lens' GetRouteResponse (Maybe Text)
getRouteResponse_sourcePath = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe Text
sourcePath :: Maybe Text
$sel:sourcePath:GetRouteResponse' :: GetRouteResponse -> Maybe Text
sourcePath} -> Maybe Text
sourcePath) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe Text
a -> GetRouteResponse
s {$sel:sourcePath:GetRouteResponse' :: Maybe Text
sourcePath = Maybe Text
a} :: GetRouteResponse)

-- | The current state of the route.
getRouteResponse_state :: Lens.Lens' GetRouteResponse (Prelude.Maybe RouteState)
getRouteResponse_state :: Lens' GetRouteResponse (Maybe RouteState)
getRouteResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe RouteState
state :: Maybe RouteState
$sel:state:GetRouteResponse' :: GetRouteResponse -> Maybe RouteState
state} -> Maybe RouteState
state) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe RouteState
a -> GetRouteResponse
s {$sel:state:GetRouteResponse' :: Maybe RouteState
state = Maybe RouteState
a} :: GetRouteResponse)

-- | The tags assigned to the route. A tag is a label that you assign to an
-- Amazon Web Services resource. Each tag consists of a key-value pair.
getRouteResponse_tags :: Lens.Lens' GetRouteResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getRouteResponse_tags :: Lens' GetRouteResponse (Maybe (HashMap Text Text))
getRouteResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetRouteResponse' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:GetRouteResponse' :: GetRouteResponse -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: GetRouteResponse
s@GetRouteResponse' {} Maybe (Sensitive (HashMap Text Text))
a -> GetRouteResponse
s {$sel:tags:GetRouteResponse' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: GetRouteResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

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

instance Prelude.NFData GetRouteResponse where
  rnf :: GetRouteResponse -> ()
rnf GetRouteResponse' {Int
Maybe Bool
Maybe [HttpMethod]
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text Text))
Maybe POSIX
Maybe ErrorResponse
Maybe RouteState
Maybe RouteType
httpStatus :: Int
tags :: Maybe (Sensitive (HashMap Text Text))
state :: Maybe RouteState
sourcePath :: Maybe Text
serviceId :: Maybe Text
routeType :: Maybe RouteType
routeId :: Maybe Text
pathResourceToId :: Maybe (HashMap Text Text)
ownerAccountId :: Maybe Text
methods :: Maybe [HttpMethod]
lastUpdatedTime :: Maybe POSIX
includeChildPaths :: Maybe Bool
error :: Maybe ErrorResponse
environmentId :: Maybe Text
createdTime :: Maybe POSIX
createdByAccountId :: Maybe Text
arn :: Maybe Text
applicationId :: Maybe Text
$sel:httpStatus:GetRouteResponse' :: GetRouteResponse -> Int
$sel:tags:GetRouteResponse' :: GetRouteResponse -> Maybe (Sensitive (HashMap Text Text))
$sel:state:GetRouteResponse' :: GetRouteResponse -> Maybe RouteState
$sel:sourcePath:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:serviceId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:routeType:GetRouteResponse' :: GetRouteResponse -> Maybe RouteType
$sel:routeId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:pathResourceToId:GetRouteResponse' :: GetRouteResponse -> Maybe (HashMap Text Text)
$sel:ownerAccountId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:methods:GetRouteResponse' :: GetRouteResponse -> Maybe [HttpMethod]
$sel:lastUpdatedTime:GetRouteResponse' :: GetRouteResponse -> Maybe POSIX
$sel:includeChildPaths:GetRouteResponse' :: GetRouteResponse -> Maybe Bool
$sel:error:GetRouteResponse' :: GetRouteResponse -> Maybe ErrorResponse
$sel:environmentId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:createdTime:GetRouteResponse' :: GetRouteResponse -> Maybe POSIX
$sel:createdByAccountId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:arn:GetRouteResponse' :: GetRouteResponse -> Maybe Text
$sel:applicationId:GetRouteResponse' :: GetRouteResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdByAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
environmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ErrorResponse
error
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeChildPaths
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [HttpMethod]
methods
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
pathResourceToId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
routeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RouteType
routeType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourcePath
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RouteState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus