{-# 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.AddThingToBillingGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds a thing to a billing group.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions AddThingToBillingGroup>
-- action.
module Amazonka.IoT.AddThingToBillingGroup
  ( -- * Creating a Request
    AddThingToBillingGroup (..),
    newAddThingToBillingGroup,

    -- * Request Lenses
    addThingToBillingGroup_billingGroupArn,
    addThingToBillingGroup_billingGroupName,
    addThingToBillingGroup_thingArn,
    addThingToBillingGroup_thingName,

    -- * Destructuring the Response
    AddThingToBillingGroupResponse (..),
    newAddThingToBillingGroupResponse,

    -- * Response Lenses
    addThingToBillingGroupResponse_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:/ 'newAddThingToBillingGroup' smart constructor.
data AddThingToBillingGroup = AddThingToBillingGroup'
  { -- | The ARN of the billing group.
    AddThingToBillingGroup -> Maybe Text
billingGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the billing group.
    --
    -- This call is asynchronous. It might take several seconds for the
    -- detachment to propagate.
    AddThingToBillingGroup -> Maybe Text
billingGroupName :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the thing to be added to the billing group.
    AddThingToBillingGroup -> Maybe Text
thingArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the thing to be added to the billing group.
    AddThingToBillingGroup -> Maybe Text
thingName :: Prelude.Maybe Prelude.Text
  }
  deriving (AddThingToBillingGroup -> AddThingToBillingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddThingToBillingGroup -> AddThingToBillingGroup -> Bool
$c/= :: AddThingToBillingGroup -> AddThingToBillingGroup -> Bool
== :: AddThingToBillingGroup -> AddThingToBillingGroup -> Bool
$c== :: AddThingToBillingGroup -> AddThingToBillingGroup -> Bool
Prelude.Eq, ReadPrec [AddThingToBillingGroup]
ReadPrec AddThingToBillingGroup
Int -> ReadS AddThingToBillingGroup
ReadS [AddThingToBillingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddThingToBillingGroup]
$creadListPrec :: ReadPrec [AddThingToBillingGroup]
readPrec :: ReadPrec AddThingToBillingGroup
$creadPrec :: ReadPrec AddThingToBillingGroup
readList :: ReadS [AddThingToBillingGroup]
$creadList :: ReadS [AddThingToBillingGroup]
readsPrec :: Int -> ReadS AddThingToBillingGroup
$creadsPrec :: Int -> ReadS AddThingToBillingGroup
Prelude.Read, Int -> AddThingToBillingGroup -> ShowS
[AddThingToBillingGroup] -> ShowS
AddThingToBillingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddThingToBillingGroup] -> ShowS
$cshowList :: [AddThingToBillingGroup] -> ShowS
show :: AddThingToBillingGroup -> String
$cshow :: AddThingToBillingGroup -> String
showsPrec :: Int -> AddThingToBillingGroup -> ShowS
$cshowsPrec :: Int -> AddThingToBillingGroup -> ShowS
Prelude.Show, forall x. Rep AddThingToBillingGroup x -> AddThingToBillingGroup
forall x. AddThingToBillingGroup -> Rep AddThingToBillingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddThingToBillingGroup x -> AddThingToBillingGroup
$cfrom :: forall x. AddThingToBillingGroup -> Rep AddThingToBillingGroup x
Prelude.Generic)

-- |
-- Create a value of 'AddThingToBillingGroup' 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', 'addThingToBillingGroup_billingGroupArn' - The ARN of the billing group.
--
-- 'billingGroupName', 'addThingToBillingGroup_billingGroupName' - The name of the billing group.
--
-- This call is asynchronous. It might take several seconds for the
-- detachment to propagate.
--
-- 'thingArn', 'addThingToBillingGroup_thingArn' - The ARN of the thing to be added to the billing group.
--
-- 'thingName', 'addThingToBillingGroup_thingName' - The name of the thing to be added to the billing group.
newAddThingToBillingGroup ::
  AddThingToBillingGroup
newAddThingToBillingGroup :: AddThingToBillingGroup
newAddThingToBillingGroup =
  AddThingToBillingGroup'
    { $sel:billingGroupArn:AddThingToBillingGroup' :: Maybe Text
billingGroupArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupName:AddThingToBillingGroup' :: Maybe Text
billingGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:thingArn:AddThingToBillingGroup' :: Maybe Text
thingArn = forall a. Maybe a
Prelude.Nothing,
      $sel:thingName:AddThingToBillingGroup' :: Maybe Text
thingName = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The name of the billing group.
--
-- This call is asynchronous. It might take several seconds for the
-- detachment to propagate.
addThingToBillingGroup_billingGroupName :: Lens.Lens' AddThingToBillingGroup (Prelude.Maybe Prelude.Text)
addThingToBillingGroup_billingGroupName :: Lens' AddThingToBillingGroup (Maybe Text)
addThingToBillingGroup_billingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddThingToBillingGroup' {Maybe Text
billingGroupName :: Maybe Text
$sel:billingGroupName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
billingGroupName} -> Maybe Text
billingGroupName) (\s :: AddThingToBillingGroup
s@AddThingToBillingGroup' {} Maybe Text
a -> AddThingToBillingGroup
s {$sel:billingGroupName:AddThingToBillingGroup' :: Maybe Text
billingGroupName = Maybe Text
a} :: AddThingToBillingGroup)

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

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

instance Core.AWSRequest AddThingToBillingGroup where
  type
    AWSResponse AddThingToBillingGroup =
      AddThingToBillingGroupResponse
  request :: (Service -> Service)
-> AddThingToBillingGroup -> Request AddThingToBillingGroup
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 AddThingToBillingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AddThingToBillingGroup)))
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 -> AddThingToBillingGroupResponse
AddThingToBillingGroupResponse'
            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 AddThingToBillingGroup where
  hashWithSalt :: Int -> AddThingToBillingGroup -> Int
hashWithSalt Int
_salt AddThingToBillingGroup' {Maybe Text
thingName :: Maybe Text
thingArn :: Maybe Text
billingGroupName :: Maybe Text
billingGroupArn :: Maybe Text
$sel:thingName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:thingArn:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:billingGroupName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:billingGroupArn:AddThingToBillingGroup' :: AddThingToBillingGroup -> 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 AddThingToBillingGroup where
  rnf :: AddThingToBillingGroup -> ()
rnf AddThingToBillingGroup' {Maybe Text
thingName :: Maybe Text
thingArn :: Maybe Text
billingGroupName :: Maybe Text
billingGroupArn :: Maybe Text
$sel:thingName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:thingArn:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:billingGroupName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:billingGroupArn:AddThingToBillingGroup' :: AddThingToBillingGroup -> 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 AddThingToBillingGroup where
  toHeaders :: AddThingToBillingGroup -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON AddThingToBillingGroup where
  toJSON :: AddThingToBillingGroup -> Value
toJSON AddThingToBillingGroup' {Maybe Text
thingName :: Maybe Text
thingArn :: Maybe Text
billingGroupName :: Maybe Text
billingGroupArn :: Maybe Text
$sel:thingName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:thingArn:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:billingGroupName:AddThingToBillingGroup' :: AddThingToBillingGroup -> Maybe Text
$sel:billingGroupArn:AddThingToBillingGroup' :: AddThingToBillingGroup -> 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 AddThingToBillingGroup where
  toPath :: AddThingToBillingGroup -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/billing-groups/addThingToBillingGroup"

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

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

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

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

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