{-# 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.CreateUsageLimit
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a usage limit for a specified Amazon Redshift Serverless usage
-- type. The usage limit is identified by the returned usage limit
-- identifier.
module Amazonka.RedshiftServerLess.CreateUsageLimit
  ( -- * Creating a Request
    CreateUsageLimit (..),
    newCreateUsageLimit,

    -- * Request Lenses
    createUsageLimit_breachAction,
    createUsageLimit_period,
    createUsageLimit_amount,
    createUsageLimit_resourceArn,
    createUsageLimit_usageType,

    -- * Destructuring the Response
    CreateUsageLimitResponse (..),
    newCreateUsageLimitResponse,

    -- * Response Lenses
    createUsageLimitResponse_usageLimit,
    createUsageLimitResponse_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:/ 'newCreateUsageLimit' smart constructor.
data CreateUsageLimit = CreateUsageLimit'
  { -- | The action that Amazon Redshift Serverless takes when the limit is
    -- reached. The default is log.
    CreateUsageLimit -> Maybe UsageLimitBreachAction
breachAction :: Prelude.Maybe UsageLimitBreachAction,
    -- | The time period that the amount applies to. A weekly period begins on
    -- Sunday. The default is monthly.
    CreateUsageLimit -> Maybe UsageLimitPeriod
period :: Prelude.Maybe UsageLimitPeriod,
    -- | The 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.
    CreateUsageLimit -> Integer
amount :: Prelude.Integer,
    -- | The Amazon Resource Name (ARN) of the Amazon Redshift Serverless
    -- resource to create the usage limit for.
    CreateUsageLimit -> Text
resourceArn :: Prelude.Text,
    -- | The type of Amazon Redshift Serverless usage to create a usage limit
    -- for.
    CreateUsageLimit -> UsageLimitUsageType
usageType :: UsageLimitUsageType
  }
  deriving (CreateUsageLimit -> CreateUsageLimit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateUsageLimit -> CreateUsageLimit -> Bool
$c/= :: CreateUsageLimit -> CreateUsageLimit -> Bool
== :: CreateUsageLimit -> CreateUsageLimit -> Bool
$c== :: CreateUsageLimit -> CreateUsageLimit -> Bool
Prelude.Eq, ReadPrec [CreateUsageLimit]
ReadPrec CreateUsageLimit
Int -> ReadS CreateUsageLimit
ReadS [CreateUsageLimit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateUsageLimit]
$creadListPrec :: ReadPrec [CreateUsageLimit]
readPrec :: ReadPrec CreateUsageLimit
$creadPrec :: ReadPrec CreateUsageLimit
readList :: ReadS [CreateUsageLimit]
$creadList :: ReadS [CreateUsageLimit]
readsPrec :: Int -> ReadS CreateUsageLimit
$creadsPrec :: Int -> ReadS CreateUsageLimit
Prelude.Read, Int -> CreateUsageLimit -> ShowS
[CreateUsageLimit] -> ShowS
CreateUsageLimit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateUsageLimit] -> ShowS
$cshowList :: [CreateUsageLimit] -> ShowS
show :: CreateUsageLimit -> String
$cshow :: CreateUsageLimit -> String
showsPrec :: Int -> CreateUsageLimit -> ShowS
$cshowsPrec :: Int -> CreateUsageLimit -> ShowS
Prelude.Show, forall x. Rep CreateUsageLimit x -> CreateUsageLimit
forall x. CreateUsageLimit -> Rep CreateUsageLimit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateUsageLimit x -> CreateUsageLimit
$cfrom :: forall x. CreateUsageLimit -> Rep CreateUsageLimit x
Prelude.Generic)

-- |
-- Create a value of 'CreateUsageLimit' 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:
--
-- 'breachAction', 'createUsageLimit_breachAction' - The action that Amazon Redshift Serverless takes when the limit is
-- reached. The default is log.
--
-- 'period', 'createUsageLimit_period' - The time period that the amount applies to. A weekly period begins on
-- Sunday. The default is monthly.
--
-- 'amount', 'createUsageLimit_amount' - The 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.
--
-- 'resourceArn', 'createUsageLimit_resourceArn' - The Amazon Resource Name (ARN) of the Amazon Redshift Serverless
-- resource to create the usage limit for.
--
-- 'usageType', 'createUsageLimit_usageType' - The type of Amazon Redshift Serverless usage to create a usage limit
-- for.
newCreateUsageLimit ::
  -- | 'amount'
  Prelude.Integer ->
  -- | 'resourceArn'
  Prelude.Text ->
  -- | 'usageType'
  UsageLimitUsageType ->
  CreateUsageLimit
newCreateUsageLimit :: Integer -> Text -> UsageLimitUsageType -> CreateUsageLimit
newCreateUsageLimit
  Integer
pAmount_
  Text
pResourceArn_
  UsageLimitUsageType
pUsageType_ =
    CreateUsageLimit'
      { $sel:breachAction:CreateUsageLimit' :: Maybe UsageLimitBreachAction
breachAction = forall a. Maybe a
Prelude.Nothing,
        $sel:period:CreateUsageLimit' :: Maybe UsageLimitPeriod
period = forall a. Maybe a
Prelude.Nothing,
        $sel:amount:CreateUsageLimit' :: Integer
amount = Integer
pAmount_,
        $sel:resourceArn:CreateUsageLimit' :: Text
resourceArn = Text
pResourceArn_,
        $sel:usageType:CreateUsageLimit' :: UsageLimitUsageType
usageType = UsageLimitUsageType
pUsageType_
      }

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

-- | The time period that the amount applies to. A weekly period begins on
-- Sunday. The default is monthly.
createUsageLimit_period :: Lens.Lens' CreateUsageLimit (Prelude.Maybe UsageLimitPeriod)
createUsageLimit_period :: Lens' CreateUsageLimit (Maybe UsageLimitPeriod)
createUsageLimit_period = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {Maybe UsageLimitPeriod
period :: Maybe UsageLimitPeriod
$sel:period:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitPeriod
period} -> Maybe UsageLimitPeriod
period) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} Maybe UsageLimitPeriod
a -> CreateUsageLimit
s {$sel:period:CreateUsageLimit' :: Maybe UsageLimitPeriod
period = Maybe UsageLimitPeriod
a} :: CreateUsageLimit)

-- | The 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.
createUsageLimit_amount :: Lens.Lens' CreateUsageLimit Prelude.Integer
createUsageLimit_amount :: Lens' CreateUsageLimit Integer
createUsageLimit_amount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {Integer
amount :: Integer
$sel:amount:CreateUsageLimit' :: CreateUsageLimit -> Integer
amount} -> Integer
amount) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} Integer
a -> CreateUsageLimit
s {$sel:amount:CreateUsageLimit' :: Integer
amount = Integer
a} :: CreateUsageLimit)

-- | The Amazon Resource Name (ARN) of the Amazon Redshift Serverless
-- resource to create the usage limit for.
createUsageLimit_resourceArn :: Lens.Lens' CreateUsageLimit Prelude.Text
createUsageLimit_resourceArn :: Lens' CreateUsageLimit Text
createUsageLimit_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {Text
resourceArn :: Text
$sel:resourceArn:CreateUsageLimit' :: CreateUsageLimit -> Text
resourceArn} -> Text
resourceArn) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} Text
a -> CreateUsageLimit
s {$sel:resourceArn:CreateUsageLimit' :: Text
resourceArn = Text
a} :: CreateUsageLimit)

-- | The type of Amazon Redshift Serverless usage to create a usage limit
-- for.
createUsageLimit_usageType :: Lens.Lens' CreateUsageLimit UsageLimitUsageType
createUsageLimit_usageType :: Lens' CreateUsageLimit UsageLimitUsageType
createUsageLimit_usageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {UsageLimitUsageType
usageType :: UsageLimitUsageType
$sel:usageType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitUsageType
usageType} -> UsageLimitUsageType
usageType) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} UsageLimitUsageType
a -> CreateUsageLimit
s {$sel:usageType:CreateUsageLimit' :: UsageLimitUsageType
usageType = UsageLimitUsageType
a} :: CreateUsageLimit)

instance Core.AWSRequest CreateUsageLimit where
  type
    AWSResponse CreateUsageLimit =
      CreateUsageLimitResponse
  request :: (Service -> Service)
-> CreateUsageLimit -> Request CreateUsageLimit
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 CreateUsageLimit
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateUsageLimit)))
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 -> CreateUsageLimitResponse
CreateUsageLimitResponse'
            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 CreateUsageLimit where
  hashWithSalt :: Int -> CreateUsageLimit -> Int
hashWithSalt Int
_salt CreateUsageLimit' {Integer
Maybe UsageLimitBreachAction
Maybe UsageLimitPeriod
Text
UsageLimitUsageType
usageType :: UsageLimitUsageType
resourceArn :: Text
amount :: Integer
period :: Maybe UsageLimitPeriod
breachAction :: Maybe UsageLimitBreachAction
$sel:usageType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitUsageType
$sel:resourceArn:CreateUsageLimit' :: CreateUsageLimit -> Text
$sel:amount:CreateUsageLimit' :: CreateUsageLimit -> Integer
$sel:period:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitPeriod
$sel:breachAction:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitBreachAction
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UsageLimitBreachAction
breachAction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UsageLimitPeriod
period
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
amount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UsageLimitUsageType
usageType

instance Prelude.NFData CreateUsageLimit where
  rnf :: CreateUsageLimit -> ()
rnf CreateUsageLimit' {Integer
Maybe UsageLimitBreachAction
Maybe UsageLimitPeriod
Text
UsageLimitUsageType
usageType :: UsageLimitUsageType
resourceArn :: Text
amount :: Integer
period :: Maybe UsageLimitPeriod
breachAction :: Maybe UsageLimitBreachAction
$sel:usageType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitUsageType
$sel:resourceArn:CreateUsageLimit' :: CreateUsageLimit -> Text
$sel:amount:CreateUsageLimit' :: CreateUsageLimit -> Integer
$sel:period:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitPeriod
$sel:breachAction:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitBreachAction
..} =
    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 Maybe UsageLimitPeriod
period
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
amount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UsageLimitUsageType
usageType

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

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

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

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

-- |
-- Create a value of 'CreateUsageLimitResponse' 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', 'createUsageLimitResponse_usageLimit' - The returned usage limit object.
--
-- 'httpStatus', 'createUsageLimitResponse_httpStatus' - The response's http status code.
newCreateUsageLimitResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateUsageLimitResponse
newCreateUsageLimitResponse :: Int -> CreateUsageLimitResponse
newCreateUsageLimitResponse Int
pHttpStatus_ =
  CreateUsageLimitResponse'
    { $sel:usageLimit:CreateUsageLimitResponse' :: Maybe UsageLimit
usageLimit =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateUsageLimitResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData CreateUsageLimitResponse where
  rnf :: CreateUsageLimitResponse -> ()
rnf CreateUsageLimitResponse' {Int
Maybe UsageLimit
httpStatus :: Int
usageLimit :: Maybe UsageLimit
$sel:httpStatus:CreateUsageLimitResponse' :: CreateUsageLimitResponse -> Int
$sel:usageLimit:CreateUsageLimitResponse' :: CreateUsageLimitResponse -> 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