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

    -- * Request Lenses
    deleteRoute_applicationIdentifier,
    deleteRoute_environmentIdentifier,
    deleteRoute_routeIdentifier,

    -- * Destructuring the Response
    DeleteRouteResponse (..),
    newDeleteRouteResponse,

    -- * Response Lenses
    deleteRouteResponse_applicationId,
    deleteRouteResponse_arn,
    deleteRouteResponse_lastUpdatedTime,
    deleteRouteResponse_routeId,
    deleteRouteResponse_serviceId,
    deleteRouteResponse_state,
    deleteRouteResponse_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:/ 'newDeleteRoute' smart constructor.
data DeleteRoute = DeleteRoute'
  { -- | The ID of the application to delete the route from.
    DeleteRoute -> Text
applicationIdentifier :: Prelude.Text,
    -- | The ID of the environment to delete the route from.
    DeleteRoute -> Text
environmentIdentifier :: Prelude.Text,
    -- | The ID of the route to delete.
    DeleteRoute -> Text
routeIdentifier :: Prelude.Text
  }
  deriving (DeleteRoute -> DeleteRoute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRoute -> DeleteRoute -> Bool
$c/= :: DeleteRoute -> DeleteRoute -> Bool
== :: DeleteRoute -> DeleteRoute -> Bool
$c== :: DeleteRoute -> DeleteRoute -> Bool
Prelude.Eq, ReadPrec [DeleteRoute]
ReadPrec DeleteRoute
Int -> ReadS DeleteRoute
ReadS [DeleteRoute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRoute]
$creadListPrec :: ReadPrec [DeleteRoute]
readPrec :: ReadPrec DeleteRoute
$creadPrec :: ReadPrec DeleteRoute
readList :: ReadS [DeleteRoute]
$creadList :: ReadS [DeleteRoute]
readsPrec :: Int -> ReadS DeleteRoute
$creadsPrec :: Int -> ReadS DeleteRoute
Prelude.Read, Int -> DeleteRoute -> ShowS
[DeleteRoute] -> ShowS
DeleteRoute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRoute] -> ShowS
$cshowList :: [DeleteRoute] -> ShowS
show :: DeleteRoute -> String
$cshow :: DeleteRoute -> String
showsPrec :: Int -> DeleteRoute -> ShowS
$cshowsPrec :: Int -> DeleteRoute -> ShowS
Prelude.Show, forall x. Rep DeleteRoute x -> DeleteRoute
forall x. DeleteRoute -> Rep DeleteRoute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRoute x -> DeleteRoute
$cfrom :: forall x. DeleteRoute -> Rep DeleteRoute x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRoute' 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', 'deleteRoute_applicationIdentifier' - The ID of the application to delete the route from.
--
-- 'environmentIdentifier', 'deleteRoute_environmentIdentifier' - The ID of the environment to delete the route from.
--
-- 'routeIdentifier', 'deleteRoute_routeIdentifier' - The ID of the route to delete.
newDeleteRoute ::
  -- | 'applicationIdentifier'
  Prelude.Text ->
  -- | 'environmentIdentifier'
  Prelude.Text ->
  -- | 'routeIdentifier'
  Prelude.Text ->
  DeleteRoute
newDeleteRoute :: Text -> Text -> Text -> DeleteRoute
newDeleteRoute
  Text
pApplicationIdentifier_
  Text
pEnvironmentIdentifier_
  Text
pRouteIdentifier_ =
    DeleteRoute'
      { $sel:applicationIdentifier:DeleteRoute' :: Text
applicationIdentifier =
          Text
pApplicationIdentifier_,
        $sel:environmentIdentifier:DeleteRoute' :: Text
environmentIdentifier = Text
pEnvironmentIdentifier_,
        $sel:routeIdentifier:DeleteRoute' :: Text
routeIdentifier = Text
pRouteIdentifier_
      }

-- | The ID of the application to delete the route from.
deleteRoute_applicationIdentifier :: Lens.Lens' DeleteRoute Prelude.Text
deleteRoute_applicationIdentifier :: Lens' DeleteRoute Text
deleteRoute_applicationIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Text
applicationIdentifier :: Text
$sel:applicationIdentifier:DeleteRoute' :: DeleteRoute -> Text
applicationIdentifier} -> Text
applicationIdentifier) (\s :: DeleteRoute
s@DeleteRoute' {} Text
a -> DeleteRoute
s {$sel:applicationIdentifier:DeleteRoute' :: Text
applicationIdentifier = Text
a} :: DeleteRoute)

-- | The ID of the environment to delete the route from.
deleteRoute_environmentIdentifier :: Lens.Lens' DeleteRoute Prelude.Text
deleteRoute_environmentIdentifier :: Lens' DeleteRoute Text
deleteRoute_environmentIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Text
environmentIdentifier :: Text
$sel:environmentIdentifier:DeleteRoute' :: DeleteRoute -> Text
environmentIdentifier} -> Text
environmentIdentifier) (\s :: DeleteRoute
s@DeleteRoute' {} Text
a -> DeleteRoute
s {$sel:environmentIdentifier:DeleteRoute' :: Text
environmentIdentifier = Text
a} :: DeleteRoute)

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

instance Core.AWSRequest DeleteRoute where
  type AWSResponse DeleteRoute = DeleteRouteResponse
  request :: (Service -> Service) -> DeleteRoute -> Request DeleteRoute
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteRoute
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteRoute)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe RouteState
-> Int
-> DeleteRouteResponse
DeleteRouteResponse'
            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
"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
"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
"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
"State")
            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 DeleteRoute where
  hashWithSalt :: Int -> DeleteRoute -> Int
hashWithSalt Int
_salt DeleteRoute' {Text
routeIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:routeIdentifier:DeleteRoute' :: DeleteRoute -> Text
$sel:environmentIdentifier:DeleteRoute' :: DeleteRoute -> Text
$sel:applicationIdentifier:DeleteRoute' :: DeleteRoute -> 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 DeleteRoute where
  rnf :: DeleteRoute -> ()
rnf DeleteRoute' {Text
routeIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:routeIdentifier:DeleteRoute' :: DeleteRoute -> Text
$sel:environmentIdentifier:DeleteRoute' :: DeleteRoute -> Text
$sel:applicationIdentifier:DeleteRoute' :: DeleteRoute -> 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 DeleteRoute where
  toHeaders :: DeleteRoute -> 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 DeleteRoute where
  toPath :: DeleteRoute -> ByteString
toPath DeleteRoute' {Text
routeIdentifier :: Text
environmentIdentifier :: Text
applicationIdentifier :: Text
$sel:routeIdentifier:DeleteRoute' :: DeleteRoute -> Text
$sel:environmentIdentifier:DeleteRoute' :: DeleteRoute -> Text
$sel:applicationIdentifier:DeleteRoute' :: DeleteRoute -> 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 DeleteRoute where
  toQuery :: DeleteRoute -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDeleteRouteResponse' smart constructor.
data DeleteRouteResponse = DeleteRouteResponse'
  { -- | The ID of the application that the route belongs to.
    DeleteRouteResponse -> Maybe Text
applicationId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the route.
    DeleteRouteResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | A timestamp that indicates when the route was last updated.
    DeleteRouteResponse -> Maybe POSIX
lastUpdatedTime :: Prelude.Maybe Data.POSIX,
    -- | The ID of the route to delete.
    DeleteRouteResponse -> Maybe Text
routeId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the service that the route belongs to.
    DeleteRouteResponse -> Maybe Text
serviceId :: Prelude.Maybe Prelude.Text,
    -- | The current state of the route.
    DeleteRouteResponse -> Maybe RouteState
state :: Prelude.Maybe RouteState,
    -- | The response's http status code.
    DeleteRouteResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteRouteResponse -> DeleteRouteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
$c/= :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
== :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
$c== :: DeleteRouteResponse -> DeleteRouteResponse -> Bool
Prelude.Eq, ReadPrec [DeleteRouteResponse]
ReadPrec DeleteRouteResponse
Int -> ReadS DeleteRouteResponse
ReadS [DeleteRouteResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRouteResponse]
$creadListPrec :: ReadPrec [DeleteRouteResponse]
readPrec :: ReadPrec DeleteRouteResponse
$creadPrec :: ReadPrec DeleteRouteResponse
readList :: ReadS [DeleteRouteResponse]
$creadList :: ReadS [DeleteRouteResponse]
readsPrec :: Int -> ReadS DeleteRouteResponse
$creadsPrec :: Int -> ReadS DeleteRouteResponse
Prelude.Read, Int -> DeleteRouteResponse -> ShowS
[DeleteRouteResponse] -> ShowS
DeleteRouteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRouteResponse] -> ShowS
$cshowList :: [DeleteRouteResponse] -> ShowS
show :: DeleteRouteResponse -> String
$cshow :: DeleteRouteResponse -> String
showsPrec :: Int -> DeleteRouteResponse -> ShowS
$cshowsPrec :: Int -> DeleteRouteResponse -> ShowS
Prelude.Show, forall x. Rep DeleteRouteResponse x -> DeleteRouteResponse
forall x. DeleteRouteResponse -> Rep DeleteRouteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRouteResponse x -> DeleteRouteResponse
$cfrom :: forall x. DeleteRouteResponse -> Rep DeleteRouteResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRouteResponse' 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', 'deleteRouteResponse_applicationId' - The ID of the application that the route belongs to.
--
-- 'arn', 'deleteRouteResponse_arn' - The Amazon Resource Name (ARN) of the route.
--
-- 'lastUpdatedTime', 'deleteRouteResponse_lastUpdatedTime' - A timestamp that indicates when the route was last updated.
--
-- 'routeId', 'deleteRouteResponse_routeId' - The ID of the route to delete.
--
-- 'serviceId', 'deleteRouteResponse_serviceId' - The ID of the service that the route belongs to.
--
-- 'state', 'deleteRouteResponse_state' - The current state of the route.
--
-- 'httpStatus', 'deleteRouteResponse_httpStatus' - The response's http status code.
newDeleteRouteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteRouteResponse
newDeleteRouteResponse :: Int -> DeleteRouteResponse
newDeleteRouteResponse Int
pHttpStatus_ =
  DeleteRouteResponse'
    { $sel:applicationId:DeleteRouteResponse' :: Maybe Text
applicationId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:arn:DeleteRouteResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedTime:DeleteRouteResponse' :: Maybe POSIX
lastUpdatedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:routeId:DeleteRouteResponse' :: Maybe Text
routeId = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceId:DeleteRouteResponse' :: Maybe Text
serviceId = forall a. Maybe a
Prelude.Nothing,
      $sel:state:DeleteRouteResponse' :: Maybe RouteState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteRouteResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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

-- | The ID of the route to delete.
deleteRouteResponse_routeId :: Lens.Lens' DeleteRouteResponse (Prelude.Maybe Prelude.Text)
deleteRouteResponse_routeId :: Lens' DeleteRouteResponse (Maybe Text)
deleteRouteResponse_routeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRouteResponse' {Maybe Text
routeId :: Maybe Text
$sel:routeId:DeleteRouteResponse' :: DeleteRouteResponse -> Maybe Text
routeId} -> Maybe Text
routeId) (\s :: DeleteRouteResponse
s@DeleteRouteResponse' {} Maybe Text
a -> DeleteRouteResponse
s {$sel:routeId:DeleteRouteResponse' :: Maybe Text
routeId = Maybe Text
a} :: DeleteRouteResponse)

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

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

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

instance Prelude.NFData DeleteRouteResponse where
  rnf :: DeleteRouteResponse -> ()
rnf DeleteRouteResponse' {Int
Maybe Text
Maybe POSIX
Maybe RouteState
httpStatus :: Int
state :: Maybe RouteState
serviceId :: Maybe Text
routeId :: Maybe Text
lastUpdatedTime :: Maybe POSIX
arn :: Maybe Text
applicationId :: Maybe Text
$sel:httpStatus:DeleteRouteResponse' :: DeleteRouteResponse -> Int
$sel:state:DeleteRouteResponse' :: DeleteRouteResponse -> Maybe RouteState
$sel:serviceId:DeleteRouteResponse' :: DeleteRouteResponse -> Maybe Text
$sel:routeId:DeleteRouteResponse' :: DeleteRouteResponse -> Maybe Text
$sel:lastUpdatedTime:DeleteRouteResponse' :: DeleteRouteResponse -> Maybe POSIX
$sel:arn:DeleteRouteResponse' :: DeleteRouteResponse -> Maybe Text
$sel:applicationId:DeleteRouteResponse' :: DeleteRouteResponse -> 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 POSIX
lastUpdatedTime
      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 Text
serviceId
      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 Int
httpStatus