{-# 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.Budgets.UpdateSubscriber
-- 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 a subscriber.
module Amazonka.Budgets.UpdateSubscriber
  ( -- * Creating a Request
    UpdateSubscriber (..),
    newUpdateSubscriber,

    -- * Request Lenses
    updateSubscriber_accountId,
    updateSubscriber_budgetName,
    updateSubscriber_notification,
    updateSubscriber_oldSubscriber,
    updateSubscriber_newSubscriber,

    -- * Destructuring the Response
    UpdateSubscriberResponse (..),
    newUpdateSubscriberResponse,

    -- * Response Lenses
    updateSubscriberResponse_httpStatus,
  )
where

import Amazonka.Budgets.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request of UpdateSubscriber
--
-- /See:/ 'newUpdateSubscriber' smart constructor.
data UpdateSubscriber = UpdateSubscriber'
  { -- | The @accountId@ that is associated with the budget whose subscriber you
    -- want to update.
    UpdateSubscriber -> Text
accountId :: Prelude.Text,
    -- | The name of the budget whose subscriber you want to update.
    UpdateSubscriber -> Text
budgetName :: Prelude.Text,
    -- | The notification whose subscriber you want to update.
    UpdateSubscriber -> Notification
notification :: Notification,
    -- | The previous subscriber that is associated with a budget notification.
    UpdateSubscriber -> Subscriber
oldSubscriber :: Subscriber,
    -- | The updated subscriber that is associated with a budget notification.
    UpdateSubscriber -> Subscriber
newSubscriber' :: Subscriber
  }
  deriving (UpdateSubscriber -> UpdateSubscriber -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSubscriber -> UpdateSubscriber -> Bool
$c/= :: UpdateSubscriber -> UpdateSubscriber -> Bool
== :: UpdateSubscriber -> UpdateSubscriber -> Bool
$c== :: UpdateSubscriber -> UpdateSubscriber -> Bool
Prelude.Eq, Int -> UpdateSubscriber -> ShowS
[UpdateSubscriber] -> ShowS
UpdateSubscriber -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSubscriber] -> ShowS
$cshowList :: [UpdateSubscriber] -> ShowS
show :: UpdateSubscriber -> String
$cshow :: UpdateSubscriber -> String
showsPrec :: Int -> UpdateSubscriber -> ShowS
$cshowsPrec :: Int -> UpdateSubscriber -> ShowS
Prelude.Show, forall x. Rep UpdateSubscriber x -> UpdateSubscriber
forall x. UpdateSubscriber -> Rep UpdateSubscriber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSubscriber x -> UpdateSubscriber
$cfrom :: forall x. UpdateSubscriber -> Rep UpdateSubscriber x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSubscriber' 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:
--
-- 'accountId', 'updateSubscriber_accountId' - The @accountId@ that is associated with the budget whose subscriber you
-- want to update.
--
-- 'budgetName', 'updateSubscriber_budgetName' - The name of the budget whose subscriber you want to update.
--
-- 'notification', 'updateSubscriber_notification' - The notification whose subscriber you want to update.
--
-- 'oldSubscriber', 'updateSubscriber_oldSubscriber' - The previous subscriber that is associated with a budget notification.
--
-- 'newSubscriber'', 'updateSubscriber_newSubscriber' - The updated subscriber that is associated with a budget notification.
newUpdateSubscriber ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'budgetName'
  Prelude.Text ->
  -- | 'notification'
  Notification ->
  -- | 'oldSubscriber'
  Subscriber ->
  -- | 'newSubscriber''
  Subscriber ->
  UpdateSubscriber
newUpdateSubscriber :: Text
-> Text
-> Notification
-> Subscriber
-> Subscriber
-> UpdateSubscriber
newUpdateSubscriber
  Text
pAccountId_
  Text
pBudgetName_
  Notification
pNotification_
  Subscriber
pOldSubscriber_
  Subscriber
pNewSubscriber_ =
    UpdateSubscriber'
      { $sel:accountId:UpdateSubscriber' :: Text
accountId = Text
pAccountId_,
        $sel:budgetName:UpdateSubscriber' :: Text
budgetName = Text
pBudgetName_,
        $sel:notification:UpdateSubscriber' :: Notification
notification = Notification
pNotification_,
        $sel:oldSubscriber:UpdateSubscriber' :: Subscriber
oldSubscriber = Subscriber
pOldSubscriber_,
        $sel:newSubscriber':UpdateSubscriber' :: Subscriber
newSubscriber' = Subscriber
pNewSubscriber_
      }

-- | The @accountId@ that is associated with the budget whose subscriber you
-- want to update.
updateSubscriber_accountId :: Lens.Lens' UpdateSubscriber Prelude.Text
updateSubscriber_accountId :: Lens' UpdateSubscriber Text
updateSubscriber_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubscriber' {Text
accountId :: Text
$sel:accountId:UpdateSubscriber' :: UpdateSubscriber -> Text
accountId} -> Text
accountId) (\s :: UpdateSubscriber
s@UpdateSubscriber' {} Text
a -> UpdateSubscriber
s {$sel:accountId:UpdateSubscriber' :: Text
accountId = Text
a} :: UpdateSubscriber)

-- | The name of the budget whose subscriber you want to update.
updateSubscriber_budgetName :: Lens.Lens' UpdateSubscriber Prelude.Text
updateSubscriber_budgetName :: Lens' UpdateSubscriber Text
updateSubscriber_budgetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubscriber' {Text
budgetName :: Text
$sel:budgetName:UpdateSubscriber' :: UpdateSubscriber -> Text
budgetName} -> Text
budgetName) (\s :: UpdateSubscriber
s@UpdateSubscriber' {} Text
a -> UpdateSubscriber
s {$sel:budgetName:UpdateSubscriber' :: Text
budgetName = Text
a} :: UpdateSubscriber)

-- | The notification whose subscriber you want to update.
updateSubscriber_notification :: Lens.Lens' UpdateSubscriber Notification
updateSubscriber_notification :: Lens' UpdateSubscriber Notification
updateSubscriber_notification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubscriber' {Notification
notification :: Notification
$sel:notification:UpdateSubscriber' :: UpdateSubscriber -> Notification
notification} -> Notification
notification) (\s :: UpdateSubscriber
s@UpdateSubscriber' {} Notification
a -> UpdateSubscriber
s {$sel:notification:UpdateSubscriber' :: Notification
notification = Notification
a} :: UpdateSubscriber)

-- | The previous subscriber that is associated with a budget notification.
updateSubscriber_oldSubscriber :: Lens.Lens' UpdateSubscriber Subscriber
updateSubscriber_oldSubscriber :: Lens' UpdateSubscriber Subscriber
updateSubscriber_oldSubscriber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubscriber' {Subscriber
oldSubscriber :: Subscriber
$sel:oldSubscriber:UpdateSubscriber' :: UpdateSubscriber -> Subscriber
oldSubscriber} -> Subscriber
oldSubscriber) (\s :: UpdateSubscriber
s@UpdateSubscriber' {} Subscriber
a -> UpdateSubscriber
s {$sel:oldSubscriber:UpdateSubscriber' :: Subscriber
oldSubscriber = Subscriber
a} :: UpdateSubscriber)

-- | The updated subscriber that is associated with a budget notification.
updateSubscriber_newSubscriber :: Lens.Lens' UpdateSubscriber Subscriber
updateSubscriber_newSubscriber :: Lens' UpdateSubscriber Subscriber
updateSubscriber_newSubscriber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubscriber' {Subscriber
newSubscriber' :: Subscriber
$sel:newSubscriber':UpdateSubscriber' :: UpdateSubscriber -> Subscriber
newSubscriber'} -> Subscriber
newSubscriber') (\s :: UpdateSubscriber
s@UpdateSubscriber' {} Subscriber
a -> UpdateSubscriber
s {$sel:newSubscriber':UpdateSubscriber' :: Subscriber
newSubscriber' = Subscriber
a} :: UpdateSubscriber)

instance Core.AWSRequest UpdateSubscriber where
  type
    AWSResponse UpdateSubscriber =
      UpdateSubscriberResponse
  request :: (Service -> Service)
-> UpdateSubscriber -> Request UpdateSubscriber
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateSubscriber
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateSubscriber)))
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 -> UpdateSubscriberResponse
UpdateSubscriberResponse'
            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 UpdateSubscriber where
  hashWithSalt :: Int -> UpdateSubscriber -> Int
hashWithSalt Int
_salt UpdateSubscriber' {Text
Subscriber
Notification
newSubscriber' :: Subscriber
oldSubscriber :: Subscriber
notification :: Notification
budgetName :: Text
accountId :: Text
$sel:newSubscriber':UpdateSubscriber' :: UpdateSubscriber -> Subscriber
$sel:oldSubscriber:UpdateSubscriber' :: UpdateSubscriber -> Subscriber
$sel:notification:UpdateSubscriber' :: UpdateSubscriber -> Notification
$sel:budgetName:UpdateSubscriber' :: UpdateSubscriber -> Text
$sel:accountId:UpdateSubscriber' :: UpdateSubscriber -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
budgetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Notification
notification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Subscriber
oldSubscriber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Subscriber
newSubscriber'

instance Prelude.NFData UpdateSubscriber where
  rnf :: UpdateSubscriber -> ()
rnf UpdateSubscriber' {Text
Subscriber
Notification
newSubscriber' :: Subscriber
oldSubscriber :: Subscriber
notification :: Notification
budgetName :: Text
accountId :: Text
$sel:newSubscriber':UpdateSubscriber' :: UpdateSubscriber -> Subscriber
$sel:oldSubscriber:UpdateSubscriber' :: UpdateSubscriber -> Subscriber
$sel:notification:UpdateSubscriber' :: UpdateSubscriber -> Notification
$sel:budgetName:UpdateSubscriber' :: UpdateSubscriber -> Text
$sel:accountId:UpdateSubscriber' :: UpdateSubscriber -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
budgetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Notification
notification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Subscriber
oldSubscriber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Subscriber
newSubscriber'

instance Data.ToHeaders UpdateSubscriber where
  toHeaders :: UpdateSubscriber -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSBudgetServiceGateway.UpdateSubscriber" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateSubscriber where
  toJSON :: UpdateSubscriber -> Value
toJSON UpdateSubscriber' {Text
Subscriber
Notification
newSubscriber' :: Subscriber
oldSubscriber :: Subscriber
notification :: Notification
budgetName :: Text
accountId :: Text
$sel:newSubscriber':UpdateSubscriber' :: UpdateSubscriber -> Subscriber
$sel:oldSubscriber:UpdateSubscriber' :: UpdateSubscriber -> Subscriber
$sel:notification:UpdateSubscriber' :: UpdateSubscriber -> Notification
$sel:budgetName:UpdateSubscriber' :: UpdateSubscriber -> Text
$sel:accountId:UpdateSubscriber' :: UpdateSubscriber -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"AccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
accountId),
            forall a. a -> Maybe a
Prelude.Just (Key
"BudgetName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
budgetName),
            forall a. a -> Maybe a
Prelude.Just (Key
"Notification" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Notification
notification),
            forall a. a -> Maybe a
Prelude.Just (Key
"OldSubscriber" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Subscriber
oldSubscriber),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"NewSubscriber" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Subscriber
newSubscriber')
          ]
      )

instance Data.ToPath UpdateSubscriber where
  toPath :: UpdateSubscriber -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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