{-# 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.RedshiftServerLess.UpdateUsageLimit
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Update a usage limit in Amazon Redshift Serverless. You can\'t update
-- the usage type or period of a usage limit.
module Amazonka.RedshiftServerLess.UpdateUsageLimit
  ( -- * Creating a Request
    UpdateUsageLimit (..),
    newUpdateUsageLimit,

    -- * Request Lenses
    updateUsageLimit_amount,
    updateUsageLimit_breachAction,
    updateUsageLimit_usageLimitId,

    -- * Destructuring the Response
    UpdateUsageLimitResponse (..),
    newUpdateUsageLimitResponse,

    -- * Response Lenses
    updateUsageLimitResponse_usageLimit,
    updateUsageLimitResponse_httpStatus,
  )
where

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 Amazonka.RedshiftServerLess.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateUsageLimit' smart constructor.
data UpdateUsageLimit = UpdateUsageLimit'
  { -- | The new limit amount. If time-based, this amount is in Redshift
    -- Processing Units (RPU) consumed per hour. If data-based, this amount is
    -- in terabytes (TB) of data transferred between Regions in cross-account
    -- sharing. The value must be a positive number.
    UpdateUsageLimit -> Maybe Integer
amount :: Prelude.Maybe Prelude.Integer,
    -- | The new action that Amazon Redshift Serverless takes when the limit is
    -- reached.
    UpdateUsageLimit -> Maybe UsageLimitBreachAction
breachAction :: Prelude.Maybe UsageLimitBreachAction,
    -- | The identifier of the usage limit to update.
    UpdateUsageLimit -> Text
usageLimitId :: Prelude.Text
  }
  deriving (UpdateUsageLimit -> UpdateUsageLimit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUsageLimit -> UpdateUsageLimit -> Bool
$c/= :: UpdateUsageLimit -> UpdateUsageLimit -> Bool
== :: UpdateUsageLimit -> UpdateUsageLimit -> Bool
$c== :: UpdateUsageLimit -> UpdateUsageLimit -> Bool
Prelude.Eq, ReadPrec [UpdateUsageLimit]
ReadPrec UpdateUsageLimit
Int -> ReadS UpdateUsageLimit
ReadS [UpdateUsageLimit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUsageLimit]
$creadListPrec :: ReadPrec [UpdateUsageLimit]
readPrec :: ReadPrec UpdateUsageLimit
$creadPrec :: ReadPrec UpdateUsageLimit
readList :: ReadS [UpdateUsageLimit]
$creadList :: ReadS [UpdateUsageLimit]
readsPrec :: Int -> ReadS UpdateUsageLimit
$creadsPrec :: Int -> ReadS UpdateUsageLimit
Prelude.Read, Int -> UpdateUsageLimit -> ShowS
[UpdateUsageLimit] -> ShowS
UpdateUsageLimit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUsageLimit] -> ShowS
$cshowList :: [UpdateUsageLimit] -> ShowS
show :: UpdateUsageLimit -> String
$cshow :: UpdateUsageLimit -> String
showsPrec :: Int -> UpdateUsageLimit -> ShowS
$cshowsPrec :: Int -> UpdateUsageLimit -> ShowS
Prelude.Show, forall x. Rep UpdateUsageLimit x -> UpdateUsageLimit
forall x. UpdateUsageLimit -> Rep UpdateUsageLimit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUsageLimit x -> UpdateUsageLimit
$cfrom :: forall x. UpdateUsageLimit -> Rep UpdateUsageLimit x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUsageLimit' 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:
--
-- 'amount', 'updateUsageLimit_amount' - The new limit amount. If time-based, this amount is in Redshift
-- Processing Units (RPU) consumed per hour. If data-based, this amount is
-- in terabytes (TB) of data transferred between Regions in cross-account
-- sharing. The value must be a positive number.
--
-- 'breachAction', 'updateUsageLimit_breachAction' - The new action that Amazon Redshift Serverless takes when the limit is
-- reached.
--
-- 'usageLimitId', 'updateUsageLimit_usageLimitId' - The identifier of the usage limit to update.
newUpdateUsageLimit ::
  -- | 'usageLimitId'
  Prelude.Text ->
  UpdateUsageLimit
newUpdateUsageLimit :: Text -> UpdateUsageLimit
newUpdateUsageLimit Text
pUsageLimitId_ =
  UpdateUsageLimit'
    { $sel:amount:UpdateUsageLimit' :: Maybe Integer
amount = forall a. Maybe a
Prelude.Nothing,
      $sel:breachAction:UpdateUsageLimit' :: Maybe UsageLimitBreachAction
breachAction = forall a. Maybe a
Prelude.Nothing,
      $sel:usageLimitId:UpdateUsageLimit' :: Text
usageLimitId = Text
pUsageLimitId_
    }

-- | The new limit amount. If time-based, this amount is in Redshift
-- Processing Units (RPU) consumed per hour. If data-based, this amount is
-- in terabytes (TB) of data transferred between Regions in cross-account
-- sharing. The value must be a positive number.
updateUsageLimit_amount :: Lens.Lens' UpdateUsageLimit (Prelude.Maybe Prelude.Integer)
updateUsageLimit_amount :: Lens' UpdateUsageLimit (Maybe Integer)
updateUsageLimit_amount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUsageLimit' {Maybe Integer
amount :: Maybe Integer
$sel:amount:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe Integer
amount} -> Maybe Integer
amount) (\s :: UpdateUsageLimit
s@UpdateUsageLimit' {} Maybe Integer
a -> UpdateUsageLimit
s {$sel:amount:UpdateUsageLimit' :: Maybe Integer
amount = Maybe Integer
a} :: UpdateUsageLimit)

-- | The new action that Amazon Redshift Serverless takes when the limit is
-- reached.
updateUsageLimit_breachAction :: Lens.Lens' UpdateUsageLimit (Prelude.Maybe UsageLimitBreachAction)
updateUsageLimit_breachAction :: Lens' UpdateUsageLimit (Maybe UsageLimitBreachAction)
updateUsageLimit_breachAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUsageLimit' {Maybe UsageLimitBreachAction
breachAction :: Maybe UsageLimitBreachAction
$sel:breachAction:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe UsageLimitBreachAction
breachAction} -> Maybe UsageLimitBreachAction
breachAction) (\s :: UpdateUsageLimit
s@UpdateUsageLimit' {} Maybe UsageLimitBreachAction
a -> UpdateUsageLimit
s {$sel:breachAction:UpdateUsageLimit' :: Maybe UsageLimitBreachAction
breachAction = Maybe UsageLimitBreachAction
a} :: UpdateUsageLimit)

-- | The identifier of the usage limit to update.
updateUsageLimit_usageLimitId :: Lens.Lens' UpdateUsageLimit Prelude.Text
updateUsageLimit_usageLimitId :: Lens' UpdateUsageLimit Text
updateUsageLimit_usageLimitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUsageLimit' {Text
usageLimitId :: Text
$sel:usageLimitId:UpdateUsageLimit' :: UpdateUsageLimit -> Text
usageLimitId} -> Text
usageLimitId) (\s :: UpdateUsageLimit
s@UpdateUsageLimit' {} Text
a -> UpdateUsageLimit
s {$sel:usageLimitId:UpdateUsageLimit' :: Text
usageLimitId = Text
a} :: UpdateUsageLimit)

instance Core.AWSRequest UpdateUsageLimit where
  type
    AWSResponse UpdateUsageLimit =
      UpdateUsageLimitResponse
  request :: (Service -> Service)
-> UpdateUsageLimit -> Request UpdateUsageLimit
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 UpdateUsageLimit
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateUsageLimit)))
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 UsageLimit -> Int -> UpdateUsageLimitResponse
UpdateUsageLimitResponse'
            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
"usageLimit")
            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 UpdateUsageLimit where
  hashWithSalt :: Int -> UpdateUsageLimit -> Int
hashWithSalt Int
_salt UpdateUsageLimit' {Maybe Integer
Maybe UsageLimitBreachAction
Text
usageLimitId :: Text
breachAction :: Maybe UsageLimitBreachAction
amount :: Maybe Integer
$sel:usageLimitId:UpdateUsageLimit' :: UpdateUsageLimit -> Text
$sel:breachAction:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe UsageLimitBreachAction
$sel:amount:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
amount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UsageLimitBreachAction
breachAction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
usageLimitId

instance Prelude.NFData UpdateUsageLimit where
  rnf :: UpdateUsageLimit -> ()
rnf UpdateUsageLimit' {Maybe Integer
Maybe UsageLimitBreachAction
Text
usageLimitId :: Text
breachAction :: Maybe UsageLimitBreachAction
amount :: Maybe Integer
$sel:usageLimitId:UpdateUsageLimit' :: UpdateUsageLimit -> Text
$sel:breachAction:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe UsageLimitBreachAction
$sel:amount:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
amount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UsageLimitBreachAction
breachAction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
usageLimitId

instance Data.ToHeaders UpdateUsageLimit where
  toHeaders :: UpdateUsageLimit -> 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
"RedshiftServerless.UpdateUsageLimit" ::
                          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 UpdateUsageLimit where
  toJSON :: UpdateUsageLimit -> Value
toJSON UpdateUsageLimit' {Maybe Integer
Maybe UsageLimitBreachAction
Text
usageLimitId :: Text
breachAction :: Maybe UsageLimitBreachAction
amount :: Maybe Integer
$sel:usageLimitId:UpdateUsageLimit' :: UpdateUsageLimit -> Text
$sel:breachAction:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe UsageLimitBreachAction
$sel:amount:UpdateUsageLimit' :: UpdateUsageLimit -> Maybe Integer
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"amount" 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
amount,
            (Key
"breachAction" 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 UsageLimitBreachAction
breachAction,
            forall a. a -> Maybe a
Prelude.Just (Key
"usageLimitId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
usageLimitId)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateUsageLimitResponse' 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:
--
-- 'usageLimit', 'updateUsageLimitResponse_usageLimit' - The updated usage limit object.
--
-- 'httpStatus', 'updateUsageLimitResponse_httpStatus' - The response's http status code.
newUpdateUsageLimitResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateUsageLimitResponse
newUpdateUsageLimitResponse :: Int -> UpdateUsageLimitResponse
newUpdateUsageLimitResponse Int
pHttpStatus_ =
  UpdateUsageLimitResponse'
    { $sel:usageLimit:UpdateUsageLimitResponse' :: Maybe UsageLimit
usageLimit =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateUsageLimitResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The updated usage limit object.
updateUsageLimitResponse_usageLimit :: Lens.Lens' UpdateUsageLimitResponse (Prelude.Maybe UsageLimit)
updateUsageLimitResponse_usageLimit :: Lens' UpdateUsageLimitResponse (Maybe UsageLimit)
updateUsageLimitResponse_usageLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUsageLimitResponse' {Maybe UsageLimit
usageLimit :: Maybe UsageLimit
$sel:usageLimit:UpdateUsageLimitResponse' :: UpdateUsageLimitResponse -> Maybe UsageLimit
usageLimit} -> Maybe UsageLimit
usageLimit) (\s :: UpdateUsageLimitResponse
s@UpdateUsageLimitResponse' {} Maybe UsageLimit
a -> UpdateUsageLimitResponse
s {$sel:usageLimit:UpdateUsageLimitResponse' :: Maybe UsageLimit
usageLimit = Maybe UsageLimit
a} :: UpdateUsageLimitResponse)

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

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