{-# 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.AppMesh.UpdateRoute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an existing route for a specified service mesh and virtual
-- router.
module Amazonka.AppMesh.UpdateRoute
  ( -- * Creating a Request
    UpdateRoute (..),
    newUpdateRoute,

    -- * Request Lenses
    updateRoute_clientToken,
    updateRoute_meshOwner,
    updateRoute_meshName,
    updateRoute_routeName,
    updateRoute_spec,
    updateRoute_virtualRouterName,

    -- * Destructuring the Response
    UpdateRouteResponse (..),
    newUpdateRouteResponse,

    -- * Response Lenses
    updateRouteResponse_httpStatus,
    updateRouteResponse_route,
  )
where

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

-- |
--
-- /See:/ 'newUpdateRoute' smart constructor.
data UpdateRoute = UpdateRoute'
  { -- | Unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the request. Up to 36 letters, numbers, hyphens, and
    -- underscores are allowed.
    UpdateRoute -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services IAM account ID of the service mesh owner. If the
    -- account ID is not your own, then it\'s the ID of the account that shared
    -- the mesh with your account. For more information about mesh sharing, see
    -- <https://docs.aws.amazon.com/app-mesh/latest/userguide/sharing.html Working with shared meshes>.
    UpdateRoute -> Maybe Text
meshOwner :: Prelude.Maybe Prelude.Text,
    -- | The name of the service mesh that the route resides in.
    UpdateRoute -> Text
meshName :: Prelude.Text,
    -- | The name of the route to update.
    UpdateRoute -> Text
routeName :: Prelude.Text,
    -- | The new route specification to apply. This overwrites the existing data.
    UpdateRoute -> RouteSpec
spec :: RouteSpec,
    -- | The name of the virtual router that the route is associated with.
    UpdateRoute -> Text
virtualRouterName :: Prelude.Text
  }
  deriving (UpdateRoute -> UpdateRoute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRoute -> UpdateRoute -> Bool
$c/= :: UpdateRoute -> UpdateRoute -> Bool
== :: UpdateRoute -> UpdateRoute -> Bool
$c== :: UpdateRoute -> UpdateRoute -> Bool
Prelude.Eq, ReadPrec [UpdateRoute]
ReadPrec UpdateRoute
Int -> ReadS UpdateRoute
ReadS [UpdateRoute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRoute]
$creadListPrec :: ReadPrec [UpdateRoute]
readPrec :: ReadPrec UpdateRoute
$creadPrec :: ReadPrec UpdateRoute
readList :: ReadS [UpdateRoute]
$creadList :: ReadS [UpdateRoute]
readsPrec :: Int -> ReadS UpdateRoute
$creadsPrec :: Int -> ReadS UpdateRoute
Prelude.Read, Int -> UpdateRoute -> ShowS
[UpdateRoute] -> ShowS
UpdateRoute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRoute] -> ShowS
$cshowList :: [UpdateRoute] -> ShowS
show :: UpdateRoute -> String
$cshow :: UpdateRoute -> String
showsPrec :: Int -> UpdateRoute -> ShowS
$cshowsPrec :: Int -> UpdateRoute -> ShowS
Prelude.Show, forall x. Rep UpdateRoute x -> UpdateRoute
forall x. UpdateRoute -> Rep UpdateRoute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRoute x -> UpdateRoute
$cfrom :: forall x. UpdateRoute -> Rep UpdateRoute x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRoute' 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:
--
-- 'clientToken', 'updateRoute_clientToken' - Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. Up to 36 letters, numbers, hyphens, and
-- underscores are allowed.
--
-- 'meshOwner', 'updateRoute_meshOwner' - The Amazon Web Services IAM account ID of the service mesh owner. If the
-- account ID is not your own, then it\'s the ID of the account that shared
-- the mesh with your account. For more information about mesh sharing, see
-- <https://docs.aws.amazon.com/app-mesh/latest/userguide/sharing.html Working with shared meshes>.
--
-- 'meshName', 'updateRoute_meshName' - The name of the service mesh that the route resides in.
--
-- 'routeName', 'updateRoute_routeName' - The name of the route to update.
--
-- 'spec', 'updateRoute_spec' - The new route specification to apply. This overwrites the existing data.
--
-- 'virtualRouterName', 'updateRoute_virtualRouterName' - The name of the virtual router that the route is associated with.
newUpdateRoute ::
  -- | 'meshName'
  Prelude.Text ->
  -- | 'routeName'
  Prelude.Text ->
  -- | 'spec'
  RouteSpec ->
  -- | 'virtualRouterName'
  Prelude.Text ->
  UpdateRoute
newUpdateRoute :: Text -> Text -> RouteSpec -> Text -> UpdateRoute
newUpdateRoute
  Text
pMeshName_
  Text
pRouteName_
  RouteSpec
pSpec_
  Text
pVirtualRouterName_ =
    UpdateRoute'
      { $sel:clientToken:UpdateRoute' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
        $sel:meshOwner:UpdateRoute' :: Maybe Text
meshOwner = forall a. Maybe a
Prelude.Nothing,
        $sel:meshName:UpdateRoute' :: Text
meshName = Text
pMeshName_,
        $sel:routeName:UpdateRoute' :: Text
routeName = Text
pRouteName_,
        $sel:spec:UpdateRoute' :: RouteSpec
spec = RouteSpec
pSpec_,
        $sel:virtualRouterName:UpdateRoute' :: Text
virtualRouterName = Text
pVirtualRouterName_
      }

-- | Unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the request. Up to 36 letters, numbers, hyphens, and
-- underscores are allowed.
updateRoute_clientToken :: Lens.Lens' UpdateRoute (Prelude.Maybe Prelude.Text)
updateRoute_clientToken :: Lens' UpdateRoute (Maybe Text)
updateRoute_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoute' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateRoute' :: UpdateRoute -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateRoute
s@UpdateRoute' {} Maybe Text
a -> UpdateRoute
s {$sel:clientToken:UpdateRoute' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateRoute)

-- | The Amazon Web Services IAM account ID of the service mesh owner. If the
-- account ID is not your own, then it\'s the ID of the account that shared
-- the mesh with your account. For more information about mesh sharing, see
-- <https://docs.aws.amazon.com/app-mesh/latest/userguide/sharing.html Working with shared meshes>.
updateRoute_meshOwner :: Lens.Lens' UpdateRoute (Prelude.Maybe Prelude.Text)
updateRoute_meshOwner :: Lens' UpdateRoute (Maybe Text)
updateRoute_meshOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoute' {Maybe Text
meshOwner :: Maybe Text
$sel:meshOwner:UpdateRoute' :: UpdateRoute -> Maybe Text
meshOwner} -> Maybe Text
meshOwner) (\s :: UpdateRoute
s@UpdateRoute' {} Maybe Text
a -> UpdateRoute
s {$sel:meshOwner:UpdateRoute' :: Maybe Text
meshOwner = Maybe Text
a} :: UpdateRoute)

-- | The name of the service mesh that the route resides in.
updateRoute_meshName :: Lens.Lens' UpdateRoute Prelude.Text
updateRoute_meshName :: Lens' UpdateRoute Text
updateRoute_meshName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoute' {Text
meshName :: Text
$sel:meshName:UpdateRoute' :: UpdateRoute -> Text
meshName} -> Text
meshName) (\s :: UpdateRoute
s@UpdateRoute' {} Text
a -> UpdateRoute
s {$sel:meshName:UpdateRoute' :: Text
meshName = Text
a} :: UpdateRoute)

-- | The name of the route to update.
updateRoute_routeName :: Lens.Lens' UpdateRoute Prelude.Text
updateRoute_routeName :: Lens' UpdateRoute Text
updateRoute_routeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoute' {Text
routeName :: Text
$sel:routeName:UpdateRoute' :: UpdateRoute -> Text
routeName} -> Text
routeName) (\s :: UpdateRoute
s@UpdateRoute' {} Text
a -> UpdateRoute
s {$sel:routeName:UpdateRoute' :: Text
routeName = Text
a} :: UpdateRoute)

-- | The new route specification to apply. This overwrites the existing data.
updateRoute_spec :: Lens.Lens' UpdateRoute RouteSpec
updateRoute_spec :: Lens' UpdateRoute RouteSpec
updateRoute_spec = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoute' {RouteSpec
spec :: RouteSpec
$sel:spec:UpdateRoute' :: UpdateRoute -> RouteSpec
spec} -> RouteSpec
spec) (\s :: UpdateRoute
s@UpdateRoute' {} RouteSpec
a -> UpdateRoute
s {$sel:spec:UpdateRoute' :: RouteSpec
spec = RouteSpec
a} :: UpdateRoute)

-- | The name of the virtual router that the route is associated with.
updateRoute_virtualRouterName :: Lens.Lens' UpdateRoute Prelude.Text
updateRoute_virtualRouterName :: Lens' UpdateRoute Text
updateRoute_virtualRouterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRoute' {Text
virtualRouterName :: Text
$sel:virtualRouterName:UpdateRoute' :: UpdateRoute -> Text
virtualRouterName} -> Text
virtualRouterName) (\s :: UpdateRoute
s@UpdateRoute' {} Text
a -> UpdateRoute
s {$sel:virtualRouterName:UpdateRoute' :: Text
virtualRouterName = Text
a} :: UpdateRoute)

instance Core.AWSRequest UpdateRoute where
  type AWSResponse UpdateRoute = UpdateRouteResponse
  request :: (Service -> Service) -> UpdateRoute -> Request UpdateRoute
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateRoute
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateRoute)))
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 ->
          Int -> RouteData -> UpdateRouteResponse
UpdateRouteResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable UpdateRoute where
  hashWithSalt :: Int -> UpdateRoute -> Int
hashWithSalt Int
_salt UpdateRoute' {Maybe Text
Text
RouteSpec
virtualRouterName :: Text
spec :: RouteSpec
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
clientToken :: Maybe Text
$sel:virtualRouterName:UpdateRoute' :: UpdateRoute -> Text
$sel:spec:UpdateRoute' :: UpdateRoute -> RouteSpec
$sel:routeName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshOwner:UpdateRoute' :: UpdateRoute -> Maybe Text
$sel:clientToken:UpdateRoute' :: UpdateRoute -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
meshOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
meshName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routeName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RouteSpec
spec
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
virtualRouterName

instance Prelude.NFData UpdateRoute where
  rnf :: UpdateRoute -> ()
rnf UpdateRoute' {Maybe Text
Text
RouteSpec
virtualRouterName :: Text
spec :: RouteSpec
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
clientToken :: Maybe Text
$sel:virtualRouterName:UpdateRoute' :: UpdateRoute -> Text
$sel:spec:UpdateRoute' :: UpdateRoute -> RouteSpec
$sel:routeName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshOwner:UpdateRoute' :: UpdateRoute -> Maybe Text
$sel:clientToken:UpdateRoute' :: UpdateRoute -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
meshOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
meshName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
routeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RouteSpec
spec
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
virtualRouterName

instance Data.ToHeaders UpdateRoute where
  toHeaders :: UpdateRoute -> 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.ToJSON UpdateRoute where
  toJSON :: UpdateRoute -> Value
toJSON UpdateRoute' {Maybe Text
Text
RouteSpec
virtualRouterName :: Text
spec :: RouteSpec
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
clientToken :: Maybe Text
$sel:virtualRouterName:UpdateRoute' :: UpdateRoute -> Text
$sel:spec:UpdateRoute' :: UpdateRoute -> RouteSpec
$sel:routeName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshOwner:UpdateRoute' :: UpdateRoute -> Maybe Text
$sel:clientToken:UpdateRoute' :: UpdateRoute -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
clientToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"spec" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= RouteSpec
spec)
          ]
      )

instance Data.ToPath UpdateRoute where
  toPath :: UpdateRoute -> ByteString
toPath UpdateRoute' {Maybe Text
Text
RouteSpec
virtualRouterName :: Text
spec :: RouteSpec
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
clientToken :: Maybe Text
$sel:virtualRouterName:UpdateRoute' :: UpdateRoute -> Text
$sel:spec:UpdateRoute' :: UpdateRoute -> RouteSpec
$sel:routeName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshOwner:UpdateRoute' :: UpdateRoute -> Maybe Text
$sel:clientToken:UpdateRoute' :: UpdateRoute -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v20190125/meshes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
meshName,
        ByteString
"/virtualRouter/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
virtualRouterName,
        ByteString
"/routes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
routeName
      ]

instance Data.ToQuery UpdateRoute where
  toQuery :: UpdateRoute -> QueryString
toQuery UpdateRoute' {Maybe Text
Text
RouteSpec
virtualRouterName :: Text
spec :: RouteSpec
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
clientToken :: Maybe Text
$sel:virtualRouterName:UpdateRoute' :: UpdateRoute -> Text
$sel:spec:UpdateRoute' :: UpdateRoute -> RouteSpec
$sel:routeName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshName:UpdateRoute' :: UpdateRoute -> Text
$sel:meshOwner:UpdateRoute' :: UpdateRoute -> Maybe Text
$sel:clientToken:UpdateRoute' :: UpdateRoute -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"meshOwner" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
meshOwner]

-- |
--
-- /See:/ 'newUpdateRouteResponse' smart constructor.
data UpdateRouteResponse = UpdateRouteResponse'
  { -- | The response's http status code.
    UpdateRouteResponse -> Int
httpStatus :: Prelude.Int,
    -- | A full description of the route that was updated.
    UpdateRouteResponse -> RouteData
route :: RouteData
  }
  deriving (UpdateRouteResponse -> UpdateRouteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateRouteResponse -> UpdateRouteResponse -> Bool
$c/= :: UpdateRouteResponse -> UpdateRouteResponse -> Bool
== :: UpdateRouteResponse -> UpdateRouteResponse -> Bool
$c== :: UpdateRouteResponse -> UpdateRouteResponse -> Bool
Prelude.Eq, ReadPrec [UpdateRouteResponse]
ReadPrec UpdateRouteResponse
Int -> ReadS UpdateRouteResponse
ReadS [UpdateRouteResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateRouteResponse]
$creadListPrec :: ReadPrec [UpdateRouteResponse]
readPrec :: ReadPrec UpdateRouteResponse
$creadPrec :: ReadPrec UpdateRouteResponse
readList :: ReadS [UpdateRouteResponse]
$creadList :: ReadS [UpdateRouteResponse]
readsPrec :: Int -> ReadS UpdateRouteResponse
$creadsPrec :: Int -> ReadS UpdateRouteResponse
Prelude.Read, Int -> UpdateRouteResponse -> ShowS
[UpdateRouteResponse] -> ShowS
UpdateRouteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateRouteResponse] -> ShowS
$cshowList :: [UpdateRouteResponse] -> ShowS
show :: UpdateRouteResponse -> String
$cshow :: UpdateRouteResponse -> String
showsPrec :: Int -> UpdateRouteResponse -> ShowS
$cshowsPrec :: Int -> UpdateRouteResponse -> ShowS
Prelude.Show, forall x. Rep UpdateRouteResponse x -> UpdateRouteResponse
forall x. UpdateRouteResponse -> Rep UpdateRouteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateRouteResponse x -> UpdateRouteResponse
$cfrom :: forall x. UpdateRouteResponse -> Rep UpdateRouteResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateRouteResponse' 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:
--
-- 'httpStatus', 'updateRouteResponse_httpStatus' - The response's http status code.
--
-- 'route', 'updateRouteResponse_route' - A full description of the route that was updated.
newUpdateRouteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'route'
  RouteData ->
  UpdateRouteResponse
newUpdateRouteResponse :: Int -> RouteData -> UpdateRouteResponse
newUpdateRouteResponse Int
pHttpStatus_ RouteData
pRoute_ =
  UpdateRouteResponse'
    { $sel:httpStatus:UpdateRouteResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:route:UpdateRouteResponse' :: RouteData
route = RouteData
pRoute_
    }

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

-- | A full description of the route that was updated.
updateRouteResponse_route :: Lens.Lens' UpdateRouteResponse RouteData
updateRouteResponse_route :: Lens' UpdateRouteResponse RouteData
updateRouteResponse_route = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateRouteResponse' {RouteData
route :: RouteData
$sel:route:UpdateRouteResponse' :: UpdateRouteResponse -> RouteData
route} -> RouteData
route) (\s :: UpdateRouteResponse
s@UpdateRouteResponse' {} RouteData
a -> UpdateRouteResponse
s {$sel:route:UpdateRouteResponse' :: RouteData
route = RouteData
a} :: UpdateRouteResponse)

instance Prelude.NFData UpdateRouteResponse where
  rnf :: UpdateRouteResponse -> ()
rnf UpdateRouteResponse' {Int
RouteData
route :: RouteData
httpStatus :: Int
$sel:route:UpdateRouteResponse' :: UpdateRouteResponse -> RouteData
$sel:httpStatus:UpdateRouteResponse' :: UpdateRouteResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RouteData
route