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

    -- * Request Lenses
    updateBillingGroup_expectedVersion,
    updateBillingGroup_billingGroupName,
    updateBillingGroup_billingGroupProperties,

    -- * Destructuring the Response
    UpdateBillingGroupResponse (..),
    newUpdateBillingGroupResponse,

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

-- |
-- Create a value of 'UpdateBillingGroup' 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', 'updateBillingGroup_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
-- @UpdateBillingGroup@ request is rejected with a
-- @VersionConflictException@.
--
-- 'billingGroupName', 'updateBillingGroup_billingGroupName' - The name of the billing group.
--
-- 'billingGroupProperties', 'updateBillingGroup_billingGroupProperties' - The properties of the billing group.
newUpdateBillingGroup ::
  -- | 'billingGroupName'
  Prelude.Text ->
  -- | 'billingGroupProperties'
  BillingGroupProperties ->
  UpdateBillingGroup
newUpdateBillingGroup :: Text -> BillingGroupProperties -> UpdateBillingGroup
newUpdateBillingGroup
  Text
pBillingGroupName_
  BillingGroupProperties
pBillingGroupProperties_ =
    UpdateBillingGroup'
      { $sel:expectedVersion:UpdateBillingGroup' :: Maybe Integer
expectedVersion =
          forall a. Maybe a
Prelude.Nothing,
        $sel:billingGroupName:UpdateBillingGroup' :: Text
billingGroupName = Text
pBillingGroupName_,
        $sel:billingGroupProperties:UpdateBillingGroup' :: BillingGroupProperties
billingGroupProperties = BillingGroupProperties
pBillingGroupProperties_
      }

-- | 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
-- @UpdateBillingGroup@ request is rejected with a
-- @VersionConflictException@.
updateBillingGroup_expectedVersion :: Lens.Lens' UpdateBillingGroup (Prelude.Maybe Prelude.Integer)
updateBillingGroup_expectedVersion :: Lens' UpdateBillingGroup (Maybe Integer)
updateBillingGroup_expectedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBillingGroup' {Maybe Integer
expectedVersion :: Maybe Integer
$sel:expectedVersion:UpdateBillingGroup' :: UpdateBillingGroup -> Maybe Integer
expectedVersion} -> Maybe Integer
expectedVersion) (\s :: UpdateBillingGroup
s@UpdateBillingGroup' {} Maybe Integer
a -> UpdateBillingGroup
s {$sel:expectedVersion:UpdateBillingGroup' :: Maybe Integer
expectedVersion = Maybe Integer
a} :: UpdateBillingGroup)

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

-- | The properties of the billing group.
updateBillingGroup_billingGroupProperties :: Lens.Lens' UpdateBillingGroup BillingGroupProperties
updateBillingGroup_billingGroupProperties :: Lens' UpdateBillingGroup BillingGroupProperties
updateBillingGroup_billingGroupProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBillingGroup' {BillingGroupProperties
billingGroupProperties :: BillingGroupProperties
$sel:billingGroupProperties:UpdateBillingGroup' :: UpdateBillingGroup -> BillingGroupProperties
billingGroupProperties} -> BillingGroupProperties
billingGroupProperties) (\s :: UpdateBillingGroup
s@UpdateBillingGroup' {} BillingGroupProperties
a -> UpdateBillingGroup
s {$sel:billingGroupProperties:UpdateBillingGroup' :: BillingGroupProperties
billingGroupProperties = BillingGroupProperties
a} :: UpdateBillingGroup)

instance Core.AWSRequest UpdateBillingGroup where
  type
    AWSResponse UpdateBillingGroup =
      UpdateBillingGroupResponse
  request :: (Service -> Service)
-> UpdateBillingGroup -> Request UpdateBillingGroup
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateBillingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateBillingGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Integer -> Int -> UpdateBillingGroupResponse
UpdateBillingGroupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"version")
            forall (f :: * -> *) a b. Applicative f => 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 UpdateBillingGroup where
  hashWithSalt :: Int -> UpdateBillingGroup -> Int
hashWithSalt Int
_salt UpdateBillingGroup' {Maybe Integer
Text
BillingGroupProperties
billingGroupProperties :: BillingGroupProperties
billingGroupName :: Text
expectedVersion :: Maybe Integer
$sel:billingGroupProperties:UpdateBillingGroup' :: UpdateBillingGroup -> BillingGroupProperties
$sel:billingGroupName:UpdateBillingGroup' :: UpdateBillingGroup -> Text
$sel:expectedVersion:UpdateBillingGroup' :: UpdateBillingGroup -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BillingGroupProperties
billingGroupProperties

instance Prelude.NFData UpdateBillingGroup where
  rnf :: UpdateBillingGroup -> ()
rnf UpdateBillingGroup' {Maybe Integer
Text
BillingGroupProperties
billingGroupProperties :: BillingGroupProperties
billingGroupName :: Text
expectedVersion :: Maybe Integer
$sel:billingGroupProperties:UpdateBillingGroup' :: UpdateBillingGroup -> BillingGroupProperties
$sel:billingGroupName:UpdateBillingGroup' :: UpdateBillingGroup -> Text
$sel:expectedVersion:UpdateBillingGroup' :: UpdateBillingGroup -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BillingGroupProperties
billingGroupProperties

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

instance Data.ToJSON UpdateBillingGroup where
  toJSON :: UpdateBillingGroup -> Value
toJSON UpdateBillingGroup' {Maybe Integer
Text
BillingGroupProperties
billingGroupProperties :: BillingGroupProperties
billingGroupName :: Text
expectedVersion :: Maybe Integer
$sel:billingGroupProperties:UpdateBillingGroup' :: UpdateBillingGroup -> BillingGroupProperties
$sel:billingGroupName:UpdateBillingGroup' :: UpdateBillingGroup -> Text
$sel:expectedVersion:UpdateBillingGroup' :: UpdateBillingGroup -> Maybe Integer
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"expectedVersion" 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 Integer
expectedVersion,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"billingGroupProperties"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= BillingGroupProperties
billingGroupProperties
              )
          ]
      )

instance Data.ToPath UpdateBillingGroup where
  toPath :: UpdateBillingGroup -> ByteString
toPath UpdateBillingGroup' {Maybe Integer
Text
BillingGroupProperties
billingGroupProperties :: BillingGroupProperties
billingGroupName :: Text
expectedVersion :: Maybe Integer
$sel:billingGroupProperties:UpdateBillingGroup' :: UpdateBillingGroup -> BillingGroupProperties
$sel:billingGroupName:UpdateBillingGroup' :: UpdateBillingGroup -> Text
$sel:expectedVersion:UpdateBillingGroup' :: UpdateBillingGroup -> 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 UpdateBillingGroup where
  toQuery :: UpdateBillingGroup -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

-- |
-- Create a value of 'UpdateBillingGroupResponse' 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:
--
-- 'version', 'updateBillingGroupResponse_version' - The latest version of the billing group.
--
-- 'httpStatus', 'updateBillingGroupResponse_httpStatus' - The response's http status code.
newUpdateBillingGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateBillingGroupResponse
newUpdateBillingGroupResponse :: Int -> UpdateBillingGroupResponse
newUpdateBillingGroupResponse Int
pHttpStatus_ =
  UpdateBillingGroupResponse'
    { $sel:version:UpdateBillingGroupResponse' :: Maybe Integer
version =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateBillingGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The latest version of the billing group.
updateBillingGroupResponse_version :: Lens.Lens' UpdateBillingGroupResponse (Prelude.Maybe Prelude.Integer)
updateBillingGroupResponse_version :: Lens' UpdateBillingGroupResponse (Maybe Integer)
updateBillingGroupResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBillingGroupResponse' {Maybe Integer
version :: Maybe Integer
$sel:version:UpdateBillingGroupResponse' :: UpdateBillingGroupResponse -> Maybe Integer
version} -> Maybe Integer
version) (\s :: UpdateBillingGroupResponse
s@UpdateBillingGroupResponse' {} Maybe Integer
a -> UpdateBillingGroupResponse
s {$sel:version:UpdateBillingGroupResponse' :: Maybe Integer
version = Maybe Integer
a} :: UpdateBillingGroupResponse)

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

instance Prelude.NFData UpdateBillingGroupResponse where
  rnf :: UpdateBillingGroupResponse -> ()
rnf UpdateBillingGroupResponse' {Int
Maybe Integer
httpStatus :: Int
version :: Maybe Integer
$sel:httpStatus:UpdateBillingGroupResponse' :: UpdateBillingGroupResponse -> Int
$sel:version:UpdateBillingGroupResponse' :: UpdateBillingGroupResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus