{-# 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.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 existing route.
module Amazonka.AppMesh.DeleteRoute
  ( -- * Creating a Request
    DeleteRoute (..),
    newDeleteRoute,

    -- * Request Lenses
    deleteRoute_meshOwner,
    deleteRoute_meshName,
    deleteRoute_routeName,
    deleteRoute_virtualRouterName,

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

    -- * Response Lenses
    deleteRouteResponse_httpStatus,
    deleteRouteResponse_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:/ 'newDeleteRoute' smart constructor.
data DeleteRoute = DeleteRoute'
  { -- | 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>.
    DeleteRoute -> Maybe Text
meshOwner :: Prelude.Maybe Prelude.Text,
    -- | The name of the service mesh to delete the route in.
    DeleteRoute -> Text
meshName :: Prelude.Text,
    -- | The name of the route to delete.
    DeleteRoute -> Text
routeName :: Prelude.Text,
    -- | The name of the virtual router to delete the route in.
    DeleteRoute -> Text
virtualRouterName :: 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:
--
-- 'meshOwner', 'deleteRoute_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', 'deleteRoute_meshName' - The name of the service mesh to delete the route in.
--
-- 'routeName', 'deleteRoute_routeName' - The name of the route to delete.
--
-- 'virtualRouterName', 'deleteRoute_virtualRouterName' - The name of the virtual router to delete the route in.
newDeleteRoute ::
  -- | 'meshName'
  Prelude.Text ->
  -- | 'routeName'
  Prelude.Text ->
  -- | 'virtualRouterName'
  Prelude.Text ->
  DeleteRoute
newDeleteRoute :: Text -> Text -> Text -> DeleteRoute
newDeleteRoute
  Text
pMeshName_
  Text
pRouteName_
  Text
pVirtualRouterName_ =
    DeleteRoute'
      { $sel:meshOwner:DeleteRoute' :: Maybe Text
meshOwner = forall a. Maybe a
Prelude.Nothing,
        $sel:meshName:DeleteRoute' :: Text
meshName = Text
pMeshName_,
        $sel:routeName:DeleteRoute' :: Text
routeName = Text
pRouteName_,
        $sel:virtualRouterName:DeleteRoute' :: Text
virtualRouterName = Text
pVirtualRouterName_
      }

-- | 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>.
deleteRoute_meshOwner :: Lens.Lens' DeleteRoute (Prelude.Maybe Prelude.Text)
deleteRoute_meshOwner :: Lens' DeleteRoute (Maybe Text)
deleteRoute_meshOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Maybe Text
meshOwner :: Maybe Text
$sel:meshOwner:DeleteRoute' :: DeleteRoute -> Maybe Text
meshOwner} -> Maybe Text
meshOwner) (\s :: DeleteRoute
s@DeleteRoute' {} Maybe Text
a -> DeleteRoute
s {$sel:meshOwner:DeleteRoute' :: Maybe Text
meshOwner = Maybe Text
a} :: DeleteRoute)

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

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

-- | The name of the virtual router to delete the route in.
deleteRoute_virtualRouterName :: Lens.Lens' DeleteRoute Prelude.Text
deleteRoute_virtualRouterName :: Lens' DeleteRoute Text
deleteRoute_virtualRouterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoute' {Text
virtualRouterName :: Text
$sel:virtualRouterName:DeleteRoute' :: DeleteRoute -> Text
virtualRouterName} -> Text
virtualRouterName) (\s :: DeleteRoute
s@DeleteRoute' {} Text
a -> DeleteRoute
s {$sel:virtualRouterName:DeleteRoute' :: Text
virtualRouterName = 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 ->
          Int -> RouteData -> DeleteRouteResponse
DeleteRouteResponse'
            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 DeleteRoute where
  hashWithSalt :: Int -> DeleteRoute -> Int
hashWithSalt Int
_salt DeleteRoute' {Maybe Text
Text
virtualRouterName :: Text
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
$sel:virtualRouterName:DeleteRoute' :: DeleteRoute -> Text
$sel:routeName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshOwner:DeleteRoute' :: DeleteRoute -> Maybe Text
..} =
    Int
_salt
      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` Text
virtualRouterName

instance Prelude.NFData DeleteRoute where
  rnf :: DeleteRoute -> ()
rnf DeleteRoute' {Maybe Text
Text
virtualRouterName :: Text
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
$sel:virtualRouterName:DeleteRoute' :: DeleteRoute -> Text
$sel:routeName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshOwner:DeleteRoute' :: DeleteRoute -> Maybe Text
..} =
    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 Text
virtualRouterName

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' {Maybe Text
Text
virtualRouterName :: Text
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
$sel:virtualRouterName:DeleteRoute' :: DeleteRoute -> Text
$sel:routeName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshOwner:DeleteRoute' :: DeleteRoute -> 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 DeleteRoute where
  toQuery :: DeleteRoute -> QueryString
toQuery DeleteRoute' {Maybe Text
Text
virtualRouterName :: Text
routeName :: Text
meshName :: Text
meshOwner :: Maybe Text
$sel:virtualRouterName:DeleteRoute' :: DeleteRoute -> Text
$sel:routeName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshName:DeleteRoute' :: DeleteRoute -> Text
$sel:meshOwner:DeleteRoute' :: DeleteRoute -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"meshOwner" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
meshOwner]

-- |
--
-- /See:/ 'newDeleteRouteResponse' smart constructor.
data DeleteRouteResponse = DeleteRouteResponse'
  { -- | The response's http status code.
    DeleteRouteResponse -> Int
httpStatus :: Prelude.Int,
    -- | The route that was deleted.
    DeleteRouteResponse -> RouteData
route :: RouteData
  }
  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:
--
-- 'httpStatus', 'deleteRouteResponse_httpStatus' - The response's http status code.
--
-- 'route', 'deleteRouteResponse_route' - The route that was deleted.
newDeleteRouteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'route'
  RouteData ->
  DeleteRouteResponse
newDeleteRouteResponse :: Int -> RouteData -> DeleteRouteResponse
newDeleteRouteResponse Int
pHttpStatus_ RouteData
pRoute_ =
  DeleteRouteResponse'
    { $sel:httpStatus:DeleteRouteResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:route:DeleteRouteResponse' :: RouteData
route = RouteData
pRoute_
    }

-- | 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)

-- | The route that was deleted.
deleteRouteResponse_route :: Lens.Lens' DeleteRouteResponse RouteData
deleteRouteResponse_route :: Lens' DeleteRouteResponse RouteData
deleteRouteResponse_route = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRouteResponse' {RouteData
route :: RouteData
$sel:route:DeleteRouteResponse' :: DeleteRouteResponse -> RouteData
route} -> RouteData
route) (\s :: DeleteRouteResponse
s@DeleteRouteResponse' {} RouteData
a -> DeleteRouteResponse
s {$sel:route:DeleteRouteResponse' :: RouteData
route = RouteData
a} :: DeleteRouteResponse)

instance Prelude.NFData DeleteRouteResponse where
  rnf :: DeleteRouteResponse -> ()
rnf DeleteRouteResponse' {Int
RouteData
route :: RouteData
httpStatus :: Int
$sel:route:DeleteRouteResponse' :: DeleteRouteResponse -> RouteData
$sel:httpStatus:DeleteRouteResponse' :: DeleteRouteResponse -> 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