{-# 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.DeleteThingGroup
-- 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 thing group.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DeleteThingGroup>
-- action.
module Amazonka.IoT.DeleteThingGroup
  ( -- * Creating a Request
    DeleteThingGroup (..),
    newDeleteThingGroup,

    -- * Request Lenses
    deleteThingGroup_expectedVersion,
    deleteThingGroup_thingGroupName,

    -- * Destructuring the Response
    DeleteThingGroupResponse (..),
    newDeleteThingGroupResponse,

    -- * Response Lenses
    deleteThingGroupResponse_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

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

-- |
-- Create a value of 'DeleteThingGroup' 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', 'deleteThingGroup_expectedVersion' - The expected version of the thing group to delete.
--
-- 'thingGroupName', 'deleteThingGroup_thingGroupName' - The name of the thing group to delete.
newDeleteThingGroup ::
  -- | 'thingGroupName'
  Prelude.Text ->
  DeleteThingGroup
newDeleteThingGroup :: Text -> DeleteThingGroup
newDeleteThingGroup Text
pThingGroupName_ =
  DeleteThingGroup'
    { $sel:expectedVersion:DeleteThingGroup' :: Maybe Integer
expectedVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:thingGroupName:DeleteThingGroup' :: Text
thingGroupName = Text
pThingGroupName_
    }

-- | The expected version of the thing group to delete.
deleteThingGroup_expectedVersion :: Lens.Lens' DeleteThingGroup (Prelude.Maybe Prelude.Integer)
deleteThingGroup_expectedVersion :: Lens' DeleteThingGroup (Maybe Integer)
deleteThingGroup_expectedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteThingGroup' {Maybe Integer
expectedVersion :: Maybe Integer
$sel:expectedVersion:DeleteThingGroup' :: DeleteThingGroup -> Maybe Integer
expectedVersion} -> Maybe Integer
expectedVersion) (\s :: DeleteThingGroup
s@DeleteThingGroup' {} Maybe Integer
a -> DeleteThingGroup
s {$sel:expectedVersion:DeleteThingGroup' :: Maybe Integer
expectedVersion = Maybe Integer
a} :: DeleteThingGroup)

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

instance Core.AWSRequest DeleteThingGroup where
  type
    AWSResponse DeleteThingGroup =
      DeleteThingGroupResponse
  request :: (Service -> Service)
-> DeleteThingGroup -> Request DeleteThingGroup
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 DeleteThingGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteThingGroup)))
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 -> DeleteThingGroupResponse
DeleteThingGroupResponse'
            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 DeleteThingGroup where
  hashWithSalt :: Int -> DeleteThingGroup -> Int
hashWithSalt Int
_salt DeleteThingGroup' {Maybe Integer
Text
thingGroupName :: Text
expectedVersion :: Maybe Integer
$sel:thingGroupName:DeleteThingGroup' :: DeleteThingGroup -> Text
$sel:expectedVersion:DeleteThingGroup' :: DeleteThingGroup -> 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
thingGroupName

instance Prelude.NFData DeleteThingGroup where
  rnf :: DeleteThingGroup -> ()
rnf DeleteThingGroup' {Maybe Integer
Text
thingGroupName :: Text
expectedVersion :: Maybe Integer
$sel:thingGroupName:DeleteThingGroup' :: DeleteThingGroup -> Text
$sel:expectedVersion:DeleteThingGroup' :: DeleteThingGroup -> 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
thingGroupName

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

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

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

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

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

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

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