{-# 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.IoTWireless.DeleteDestination
-- 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 a destination.
module Amazonka.IoTWireless.DeleteDestination
  ( -- * Creating a Request
    DeleteDestination (..),
    newDeleteDestination,

    -- * Request Lenses
    deleteDestination_name,

    -- * Destructuring the Response
    DeleteDestinationResponse (..),
    newDeleteDestinationResponse,

    -- * Response Lenses
    deleteDestinationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteDestination' smart constructor.
data DeleteDestination = DeleteDestination'
  { -- | The name of the resource to delete.
    DeleteDestination -> Text
name :: Prelude.Text
  }
  deriving (DeleteDestination -> DeleteDestination -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDestination -> DeleteDestination -> Bool
$c/= :: DeleteDestination -> DeleteDestination -> Bool
== :: DeleteDestination -> DeleteDestination -> Bool
$c== :: DeleteDestination -> DeleteDestination -> Bool
Prelude.Eq, ReadPrec [DeleteDestination]
ReadPrec DeleteDestination
Int -> ReadS DeleteDestination
ReadS [DeleteDestination]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDestination]
$creadListPrec :: ReadPrec [DeleteDestination]
readPrec :: ReadPrec DeleteDestination
$creadPrec :: ReadPrec DeleteDestination
readList :: ReadS [DeleteDestination]
$creadList :: ReadS [DeleteDestination]
readsPrec :: Int -> ReadS DeleteDestination
$creadsPrec :: Int -> ReadS DeleteDestination
Prelude.Read, Int -> DeleteDestination -> ShowS
[DeleteDestination] -> ShowS
DeleteDestination -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDestination] -> ShowS
$cshowList :: [DeleteDestination] -> ShowS
show :: DeleteDestination -> String
$cshow :: DeleteDestination -> String
showsPrec :: Int -> DeleteDestination -> ShowS
$cshowsPrec :: Int -> DeleteDestination -> ShowS
Prelude.Show, forall x. Rep DeleteDestination x -> DeleteDestination
forall x. DeleteDestination -> Rep DeleteDestination x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDestination x -> DeleteDestination
$cfrom :: forall x. DeleteDestination -> Rep DeleteDestination x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDestination' 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:
--
-- 'name', 'deleteDestination_name' - The name of the resource to delete.
newDeleteDestination ::
  -- | 'name'
  Prelude.Text ->
  DeleteDestination
newDeleteDestination :: Text -> DeleteDestination
newDeleteDestination Text
pName_ =
  DeleteDestination' {$sel:name:DeleteDestination' :: Text
name = Text
pName_}

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

instance Core.AWSRequest DeleteDestination where
  type
    AWSResponse DeleteDestination =
      DeleteDestinationResponse
  request :: (Service -> Service)
-> DeleteDestination -> Request DeleteDestination
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 DeleteDestination
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteDestination)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteDestinationResponse
DeleteDestinationResponse'
            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))
      )

instance Prelude.Hashable DeleteDestination where
  hashWithSalt :: Int -> DeleteDestination -> Int
hashWithSalt Int
_salt DeleteDestination' {Text
name :: Text
$sel:name:DeleteDestination' :: DeleteDestination -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData DeleteDestination where
  rnf :: DeleteDestination -> ()
rnf DeleteDestination' {Text
name :: Text
$sel:name:DeleteDestination' :: DeleteDestination -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
name

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

instance Data.ToPath DeleteDestination where
  toPath :: DeleteDestination -> ByteString
toPath DeleteDestination' {Text
name :: Text
$sel:name:DeleteDestination' :: DeleteDestination -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/destinations/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

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

-- |
-- Create a value of 'DeleteDestinationResponse' 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', 'deleteDestinationResponse_httpStatus' - The response's http status code.
newDeleteDestinationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteDestinationResponse
newDeleteDestinationResponse :: Int -> DeleteDestinationResponse
newDeleteDestinationResponse Int
pHttpStatus_ =
  DeleteDestinationResponse'
    { $sel:httpStatus:DeleteDestinationResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DeleteDestinationResponse where
  rnf :: DeleteDestinationResponse -> ()
rnf DeleteDestinationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteDestinationResponse' :: DeleteDestinationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus