{-# 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.RemoveThingFromBillingGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes the given thing from the billing group.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions RemoveThingFromBillingGroup>
-- action.
--
-- This call is asynchronous. It might take several seconds for the
-- detachment to propagate.
module Amazonka.IoT.RemoveThingFromBillingGroup
  ( -- * Creating a Request
    RemoveThingFromBillingGroup (..),
    newRemoveThingFromBillingGroup,

    -- * Request Lenses
    removeThingFromBillingGroup_billingGroupArn,
    removeThingFromBillingGroup_billingGroupName,
    removeThingFromBillingGroup_thingArn,
    removeThingFromBillingGroup_thingName,

    -- * Destructuring the Response
    RemoveThingFromBillingGroupResponse (..),
    newRemoveThingFromBillingGroupResponse,

    -- * Response Lenses
    removeThingFromBillingGroupResponse_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:/ 'newRemoveThingFromBillingGroup' smart constructor.
data RemoveThingFromBillingGroup = RemoveThingFromBillingGroup'
  { -- | The ARN of the billing group.
    RemoveThingFromBillingGroup -> Maybe Text
billingGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the billing group.
    RemoveThingFromBillingGroup -> Maybe Text
billingGroupName :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the thing to be removed from the billing group.
    RemoveThingFromBillingGroup -> Maybe Text
thingArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the thing to be removed from the billing group.
    RemoveThingFromBillingGroup -> Maybe Text
thingName :: Prelude.Maybe Prelude.Text
  }
  deriving (RemoveThingFromBillingGroup -> RemoveThingFromBillingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveThingFromBillingGroup -> RemoveThingFromBillingGroup -> Bool
$c/= :: RemoveThingFromBillingGroup -> RemoveThingFromBillingGroup -> Bool
== :: RemoveThingFromBillingGroup -> RemoveThingFromBillingGroup -> Bool
$c== :: RemoveThingFromBillingGroup -> RemoveThingFromBillingGroup -> Bool
Prelude.Eq, ReadPrec [RemoveThingFromBillingGroup]
ReadPrec RemoveThingFromBillingGroup
Int -> ReadS RemoveThingFromBillingGroup
ReadS [RemoveThingFromBillingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveThingFromBillingGroup]
$creadListPrec :: ReadPrec [RemoveThingFromBillingGroup]
readPrec :: ReadPrec RemoveThingFromBillingGroup
$creadPrec :: ReadPrec RemoveThingFromBillingGroup
readList :: ReadS [RemoveThingFromBillingGroup]
$creadList :: ReadS [RemoveThingFromBillingGroup]
readsPrec :: Int -> ReadS RemoveThingFromBillingGroup
$creadsPrec :: Int -> ReadS RemoveThingFromBillingGroup
Prelude.Read, Int -> RemoveThingFromBillingGroup -> ShowS
[RemoveThingFromBillingGroup] -> ShowS
RemoveThingFromBillingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveThingFromBillingGroup] -> ShowS
$cshowList :: [RemoveThingFromBillingGroup] -> ShowS
show :: RemoveThingFromBillingGroup -> String
$cshow :: RemoveThingFromBillingGroup -> String
showsPrec :: Int -> RemoveThingFromBillingGroup -> ShowS
$cshowsPrec :: Int -> RemoveThingFromBillingGroup -> ShowS
Prelude.Show, forall x.
Rep RemoveThingFromBillingGroup x -> RemoveThingFromBillingGroup
forall x.
RemoveThingFromBillingGroup -> Rep RemoveThingFromBillingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoveThingFromBillingGroup x -> RemoveThingFromBillingGroup
$cfrom :: forall x.
RemoveThingFromBillingGroup -> Rep RemoveThingFromBillingGroup x
Prelude.Generic)

-- |
-- Create a value of 'RemoveThingFromBillingGroup' 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:
--
-- 'billingGroupArn', 'removeThingFromBillingGroup_billingGroupArn' - The ARN of the billing group.
--
-- 'billingGroupName', 'removeThingFromBillingGroup_billingGroupName' - The name of the billing group.
--
-- 'thingArn', 'removeThingFromBillingGroup_thingArn' - The ARN of the thing to be removed from the billing group.
--
-- 'thingName', 'removeThingFromBillingGroup_thingName' - The name of the thing to be removed from the billing group.
newRemoveThingFromBillingGroup ::
  RemoveThingFromBillingGroup
newRemoveThingFromBillingGroup :: RemoveThingFromBillingGroup
newRemoveThingFromBillingGroup =
  RemoveThingFromBillingGroup'
    { $sel:billingGroupArn:RemoveThingFromBillingGroup' :: Maybe Text
billingGroupArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupName:RemoveThingFromBillingGroup' :: Maybe Text
billingGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:thingArn:RemoveThingFromBillingGroup' :: Maybe Text
thingArn = forall a. Maybe a
Prelude.Nothing,
      $sel:thingName:RemoveThingFromBillingGroup' :: Maybe Text
thingName = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the billing group.
removeThingFromBillingGroup_billingGroupArn :: Lens.Lens' RemoveThingFromBillingGroup (Prelude.Maybe Prelude.Text)
removeThingFromBillingGroup_billingGroupArn :: Lens' RemoveThingFromBillingGroup (Maybe Text)
removeThingFromBillingGroup_billingGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveThingFromBillingGroup' {Maybe Text
billingGroupArn :: Maybe Text
$sel:billingGroupArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
billingGroupArn} -> Maybe Text
billingGroupArn) (\s :: RemoveThingFromBillingGroup
s@RemoveThingFromBillingGroup' {} Maybe Text
a -> RemoveThingFromBillingGroup
s {$sel:billingGroupArn:RemoveThingFromBillingGroup' :: Maybe Text
billingGroupArn = Maybe Text
a} :: RemoveThingFromBillingGroup)

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

-- | The ARN of the thing to be removed from the billing group.
removeThingFromBillingGroup_thingArn :: Lens.Lens' RemoveThingFromBillingGroup (Prelude.Maybe Prelude.Text)
removeThingFromBillingGroup_thingArn :: Lens' RemoveThingFromBillingGroup (Maybe Text)
removeThingFromBillingGroup_thingArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveThingFromBillingGroup' {Maybe Text
thingArn :: Maybe Text
$sel:thingArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
thingArn} -> Maybe Text
thingArn) (\s :: RemoveThingFromBillingGroup
s@RemoveThingFromBillingGroup' {} Maybe Text
a -> RemoveThingFromBillingGroup
s {$sel:thingArn:RemoveThingFromBillingGroup' :: Maybe Text
thingArn = Maybe Text
a} :: RemoveThingFromBillingGroup)

-- | The name of the thing to be removed from the billing group.
removeThingFromBillingGroup_thingName :: Lens.Lens' RemoveThingFromBillingGroup (Prelude.Maybe Prelude.Text)
removeThingFromBillingGroup_thingName :: Lens' RemoveThingFromBillingGroup (Maybe Text)
removeThingFromBillingGroup_thingName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveThingFromBillingGroup' {Maybe Text
thingName :: Maybe Text
$sel:thingName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
thingName} -> Maybe Text
thingName) (\s :: RemoveThingFromBillingGroup
s@RemoveThingFromBillingGroup' {} Maybe Text
a -> RemoveThingFromBillingGroup
s {$sel:thingName:RemoveThingFromBillingGroup' :: Maybe Text
thingName = Maybe Text
a} :: RemoveThingFromBillingGroup)

instance Core.AWSRequest RemoveThingFromBillingGroup where
  type
    AWSResponse RemoveThingFromBillingGroup =
      RemoveThingFromBillingGroupResponse
  request :: (Service -> Service)
-> RemoveThingFromBillingGroup
-> Request RemoveThingFromBillingGroup
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RemoveThingFromBillingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RemoveThingFromBillingGroup)))
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 -> RemoveThingFromBillingGroupResponse
RemoveThingFromBillingGroupResponse'
            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 RemoveThingFromBillingGroup where
  hashWithSalt :: Int -> RemoveThingFromBillingGroup -> Int
hashWithSalt Int
_salt RemoveThingFromBillingGroup' {Maybe Text
thingName :: Maybe Text
thingArn :: Maybe Text
billingGroupName :: Maybe Text
billingGroupArn :: Maybe Text
$sel:thingName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:thingArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:billingGroupName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:billingGroupArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
billingGroupArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
billingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
thingArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
thingName

instance Prelude.NFData RemoveThingFromBillingGroup where
  rnf :: RemoveThingFromBillingGroup -> ()
rnf RemoveThingFromBillingGroup' {Maybe Text
thingName :: Maybe Text
thingArn :: Maybe Text
billingGroupName :: Maybe Text
billingGroupArn :: Maybe Text
$sel:thingName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:thingArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:billingGroupName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:billingGroupArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
billingGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
billingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingName

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

instance Data.ToJSON RemoveThingFromBillingGroup where
  toJSON :: RemoveThingFromBillingGroup -> Value
toJSON RemoveThingFromBillingGroup' {Maybe Text
thingName :: Maybe Text
thingArn :: Maybe Text
billingGroupName :: Maybe Text
billingGroupArn :: Maybe Text
$sel:thingName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:thingArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:billingGroupName:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
$sel:billingGroupArn:RemoveThingFromBillingGroup' :: RemoveThingFromBillingGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"billingGroupArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
billingGroupArn,
            (Key
"billingGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
billingGroupName,
            (Key
"thingArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
thingArn,
            (Key
"thingName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
thingName
          ]
      )

instance Data.ToPath RemoveThingFromBillingGroup where
  toPath :: RemoveThingFromBillingGroup -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/billing-groups/removeThingFromBillingGroup"

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

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

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

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

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