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

    -- * Request Lenses
    deleteBillingGroup_expectedVersion,
    deleteBillingGroup_billingGroupName,

    -- * Destructuring the Response
    DeleteBillingGroupResponse (..),
    newDeleteBillingGroupResponse,

    -- * Response Lenses
    deleteBillingGroupResponse_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:/ 'newDeleteBillingGroup' smart constructor.
data DeleteBillingGroup = DeleteBillingGroup'
  { -- | The expected version of the billing group. If the version of the billing
    -- group does not match the expected version specified in the request, the
    -- @DeleteBillingGroup@ request is rejected with a
    -- @VersionConflictException@.
    DeleteBillingGroup -> Maybe Integer
expectedVersion :: Prelude.Maybe Prelude.Integer,
    -- | The name of the billing group.
    DeleteBillingGroup -> Text
billingGroupName :: Prelude.Text
  }
  deriving (DeleteBillingGroup -> DeleteBillingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBillingGroup -> DeleteBillingGroup -> Bool
$c/= :: DeleteBillingGroup -> DeleteBillingGroup -> Bool
== :: DeleteBillingGroup -> DeleteBillingGroup -> Bool
$c== :: DeleteBillingGroup -> DeleteBillingGroup -> Bool
Prelude.Eq, ReadPrec [DeleteBillingGroup]
ReadPrec DeleteBillingGroup
Int -> ReadS DeleteBillingGroup
ReadS [DeleteBillingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBillingGroup]
$creadListPrec :: ReadPrec [DeleteBillingGroup]
readPrec :: ReadPrec DeleteBillingGroup
$creadPrec :: ReadPrec DeleteBillingGroup
readList :: ReadS [DeleteBillingGroup]
$creadList :: ReadS [DeleteBillingGroup]
readsPrec :: Int -> ReadS DeleteBillingGroup
$creadsPrec :: Int -> ReadS DeleteBillingGroup
Prelude.Read, Int -> DeleteBillingGroup -> ShowS
[DeleteBillingGroup] -> ShowS
DeleteBillingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBillingGroup] -> ShowS
$cshowList :: [DeleteBillingGroup] -> ShowS
show :: DeleteBillingGroup -> String
$cshow :: DeleteBillingGroup -> String
showsPrec :: Int -> DeleteBillingGroup -> ShowS
$cshowsPrec :: Int -> DeleteBillingGroup -> ShowS
Prelude.Show, forall x. Rep DeleteBillingGroup x -> DeleteBillingGroup
forall x. DeleteBillingGroup -> Rep DeleteBillingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBillingGroup x -> DeleteBillingGroup
$cfrom :: forall x. DeleteBillingGroup -> Rep DeleteBillingGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBillingGroup' 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', 'deleteBillingGroup_expectedVersion' - The expected version of the billing group. If the version of the billing
-- group does not match the expected version specified in the request, the
-- @DeleteBillingGroup@ request is rejected with a
-- @VersionConflictException@.
--
-- 'billingGroupName', 'deleteBillingGroup_billingGroupName' - The name of the billing group.
newDeleteBillingGroup ::
  -- | 'billingGroupName'
  Prelude.Text ->
  DeleteBillingGroup
newDeleteBillingGroup :: Text -> DeleteBillingGroup
newDeleteBillingGroup Text
pBillingGroupName_ =
  DeleteBillingGroup'
    { $sel:expectedVersion:DeleteBillingGroup' :: Maybe Integer
expectedVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupName:DeleteBillingGroup' :: Text
billingGroupName = Text
pBillingGroupName_
    }

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

-- | The name of the billing group.
deleteBillingGroup_billingGroupName :: Lens.Lens' DeleteBillingGroup Prelude.Text
deleteBillingGroup_billingGroupName :: Lens' DeleteBillingGroup Text
deleteBillingGroup_billingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBillingGroup' {Text
billingGroupName :: Text
$sel:billingGroupName:DeleteBillingGroup' :: DeleteBillingGroup -> Text
billingGroupName} -> Text
billingGroupName) (\s :: DeleteBillingGroup
s@DeleteBillingGroup' {} Text
a -> DeleteBillingGroup
s {$sel:billingGroupName:DeleteBillingGroup' :: Text
billingGroupName = Text
a} :: DeleteBillingGroup)

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

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

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

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

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

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

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

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

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