{-# 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.IoT.DeleteThing
-- 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 the specified thing. Returns successfully with no error if the
-- deletion is successful or you specify a thing that doesn\'t exist.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DeleteThing>
-- action.
module Amazonka.IoT.DeleteThing
  ( -- * Creating a Request
    DeleteThing (..),
    newDeleteThing,

    -- * Request Lenses
    deleteThing_expectedVersion,
    deleteThing_thingName,

    -- * Destructuring the Response
    DeleteThingResponse (..),
    newDeleteThingResponse,

    -- * Response Lenses
    deleteThingResponse_httpStatus,
  )
where

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

-- | The input for the DeleteThing operation.
--
-- /See:/ 'newDeleteThing' smart constructor.
data DeleteThing = DeleteThing'
  { -- | The expected version of the thing record in the registry. If the version
    -- of the record in the registry does not match the expected version
    -- specified in the request, the @DeleteThing@ request is rejected with a
    -- @VersionConflictException@.
    DeleteThing -> Maybe Integer
expectedVersion :: Prelude.Maybe Prelude.Integer,
    -- | The name of the thing to delete.
    DeleteThing -> Text
thingName :: Prelude.Text
  }
  deriving (DeleteThing -> DeleteThing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteThing -> DeleteThing -> Bool
$c/= :: DeleteThing -> DeleteThing -> Bool
== :: DeleteThing -> DeleteThing -> Bool
$c== :: DeleteThing -> DeleteThing -> Bool
Prelude.Eq, ReadPrec [DeleteThing]
ReadPrec DeleteThing
Int -> ReadS DeleteThing
ReadS [DeleteThing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteThing]
$creadListPrec :: ReadPrec [DeleteThing]
readPrec :: ReadPrec DeleteThing
$creadPrec :: ReadPrec DeleteThing
readList :: ReadS [DeleteThing]
$creadList :: ReadS [DeleteThing]
readsPrec :: Int -> ReadS DeleteThing
$creadsPrec :: Int -> ReadS DeleteThing
Prelude.Read, Int -> DeleteThing -> ShowS
[DeleteThing] -> ShowS
DeleteThing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteThing] -> ShowS
$cshowList :: [DeleteThing] -> ShowS
show :: DeleteThing -> String
$cshow :: DeleteThing -> String
showsPrec :: Int -> DeleteThing -> ShowS
$cshowsPrec :: Int -> DeleteThing -> ShowS
Prelude.Show, forall x. Rep DeleteThing x -> DeleteThing
forall x. DeleteThing -> Rep DeleteThing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteThing x -> DeleteThing
$cfrom :: forall x. DeleteThing -> Rep DeleteThing x
Prelude.Generic)

-- |
-- Create a value of 'DeleteThing' 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:
--
-- 'expectedVersion', 'deleteThing_expectedVersion' - The expected version of the thing record in the registry. If the version
-- of the record in the registry does not match the expected version
-- specified in the request, the @DeleteThing@ request is rejected with a
-- @VersionConflictException@.
--
-- 'thingName', 'deleteThing_thingName' - The name of the thing to delete.
newDeleteThing ::
  -- | 'thingName'
  Prelude.Text ->
  DeleteThing
newDeleteThing :: Text -> DeleteThing
newDeleteThing Text
pThingName_ =
  DeleteThing'
    { $sel:expectedVersion:DeleteThing' :: Maybe Integer
expectedVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:thingName:DeleteThing' :: Text
thingName = Text
pThingName_
    }

-- | The expected version of the thing record in the registry. If the version
-- of the record in the registry does not match the expected version
-- specified in the request, the @DeleteThing@ request is rejected with a
-- @VersionConflictException@.
deleteThing_expectedVersion :: Lens.Lens' DeleteThing (Prelude.Maybe Prelude.Integer)
deleteThing_expectedVersion :: Lens' DeleteThing (Maybe Integer)
deleteThing_expectedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteThing' {Maybe Integer
expectedVersion :: Maybe Integer
$sel:expectedVersion:DeleteThing' :: DeleteThing -> Maybe Integer
expectedVersion} -> Maybe Integer
expectedVersion) (\s :: DeleteThing
s@DeleteThing' {} Maybe Integer
a -> DeleteThing
s {$sel:expectedVersion:DeleteThing' :: Maybe Integer
expectedVersion = Maybe Integer
a} :: DeleteThing)

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

instance Core.AWSRequest DeleteThing where
  type AWSResponse DeleteThing = DeleteThingResponse
  request :: (Service -> Service) -> DeleteThing -> Request DeleteThing
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 DeleteThing
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteThing)))
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 -> DeleteThingResponse
DeleteThingResponse'
            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 DeleteThing where
  hashWithSalt :: Int -> DeleteThing -> Int
hashWithSalt Int
_salt DeleteThing' {Maybe Integer
Text
thingName :: Text
expectedVersion :: Maybe Integer
$sel:thingName:DeleteThing' :: DeleteThing -> Text
$sel:expectedVersion:DeleteThing' :: DeleteThing -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
expectedVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName

instance Prelude.NFData DeleteThing where
  rnf :: DeleteThing -> ()
rnf DeleteThing' {Maybe Integer
Text
thingName :: Text
expectedVersion :: Maybe Integer
$sel:thingName:DeleteThing' :: DeleteThing -> Text
$sel:expectedVersion:DeleteThing' :: DeleteThing -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
expectedVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingName

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

instance Data.ToPath DeleteThing where
  toPath :: DeleteThing -> ByteString
toPath DeleteThing' {Maybe Integer
Text
thingName :: Text
expectedVersion :: Maybe Integer
$sel:thingName:DeleteThing' :: DeleteThing -> Text
$sel:expectedVersion:DeleteThing' :: DeleteThing -> Maybe Integer
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/things/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingName]

instance Data.ToQuery DeleteThing where
  toQuery :: DeleteThing -> QueryString
toQuery DeleteThing' {Maybe Integer
Text
thingName :: Text
expectedVersion :: Maybe Integer
$sel:thingName:DeleteThing' :: DeleteThing -> Text
$sel:expectedVersion:DeleteThing' :: DeleteThing -> Maybe Integer
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"expectedVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Integer
expectedVersion]

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

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

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

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