{-# 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.Redshift.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 feature on a
-- cluster. The usage limit is identified by the returned usage limit
-- identifier.
module Amazonka.Redshift.CreateUsageLimit
  ( -- * Creating a Request
    CreateUsageLimit (..),
    newCreateUsageLimit,

    -- * Request Lenses
    createUsageLimit_breachAction,
    createUsageLimit_period,
    createUsageLimit_tags,
    createUsageLimit_clusterIdentifier,
    createUsageLimit_featureType,
    createUsageLimit_limitType,
    createUsageLimit_amount,

    -- * Destructuring the Response
    UsageLimit (..),
    newUsageLimit,

    -- * Response Lenses
    usageLimit_amount,
    usageLimit_breachAction,
    usageLimit_clusterIdentifier,
    usageLimit_featureType,
    usageLimit_limitType,
    usageLimit_period,
    usageLimit_tags,
    usageLimit_usageLimitId,
  )
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.Redshift.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 takes when the limit is reached. The
    -- default is log. For more information about this parameter, see
    -- UsageLimit.
    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,
    -- | A list of tag instances.
    CreateUsageLimit -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The identifier of the cluster that you want to limit usage.
    CreateUsageLimit -> Text
clusterIdentifier :: Prelude.Text,
    -- | The Amazon Redshift feature that you want to limit.
    CreateUsageLimit -> UsageLimitFeatureType
featureType :: UsageLimitFeatureType,
    -- | The type of limit. Depending on the feature type, this can be based on a
    -- time duration or data size. If @FeatureType@ is @spectrum@, then
    -- @LimitType@ must be @data-scanned@. If @FeatureType@ is
    -- @concurrency-scaling@, then @LimitType@ must be @time@. If @FeatureType@
    -- is @cross-region-datasharing@, then @LimitType@ must be @data-scanned@.
    CreateUsageLimit -> UsageLimitLimitType
limitType :: UsageLimitLimitType,
    -- | The limit amount. If time-based, this amount is in minutes. If
    -- data-based, this amount is in terabytes (TB). The value must be a
    -- positive number.
    CreateUsageLimit -> Integer
amount :: Prelude.Integer
  }
  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 takes when the limit is reached. The
-- default is log. For more information about this parameter, see
-- UsageLimit.
--
-- 'period', 'createUsageLimit_period' - The time period that the amount applies to. A @weekly@ period begins on
-- Sunday. The default is @monthly@.
--
-- 'tags', 'createUsageLimit_tags' - A list of tag instances.
--
-- 'clusterIdentifier', 'createUsageLimit_clusterIdentifier' - The identifier of the cluster that you want to limit usage.
--
-- 'featureType', 'createUsageLimit_featureType' - The Amazon Redshift feature that you want to limit.
--
-- 'limitType', 'createUsageLimit_limitType' - The type of limit. Depending on the feature type, this can be based on a
-- time duration or data size. If @FeatureType@ is @spectrum@, then
-- @LimitType@ must be @data-scanned@. If @FeatureType@ is
-- @concurrency-scaling@, then @LimitType@ must be @time@. If @FeatureType@
-- is @cross-region-datasharing@, then @LimitType@ must be @data-scanned@.
--
-- 'amount', 'createUsageLimit_amount' - The limit amount. If time-based, this amount is in minutes. If
-- data-based, this amount is in terabytes (TB). The value must be a
-- positive number.
newCreateUsageLimit ::
  -- | 'clusterIdentifier'
  Prelude.Text ->
  -- | 'featureType'
  UsageLimitFeatureType ->
  -- | 'limitType'
  UsageLimitLimitType ->
  -- | 'amount'
  Prelude.Integer ->
  CreateUsageLimit
newCreateUsageLimit :: Text
-> UsageLimitFeatureType
-> UsageLimitLimitType
-> Integer
-> CreateUsageLimit
newCreateUsageLimit
  Text
pClusterIdentifier_
  UsageLimitFeatureType
pFeatureType_
  UsageLimitLimitType
pLimitType_
  Integer
pAmount_ =
    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:tags:CreateUsageLimit' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:clusterIdentifier:CreateUsageLimit' :: Text
clusterIdentifier = Text
pClusterIdentifier_,
        $sel:featureType:CreateUsageLimit' :: UsageLimitFeatureType
featureType = UsageLimitFeatureType
pFeatureType_,
        $sel:limitType:CreateUsageLimit' :: UsageLimitLimitType
limitType = UsageLimitLimitType
pLimitType_,
        $sel:amount:CreateUsageLimit' :: Integer
amount = Integer
pAmount_
      }

-- | The action that Amazon Redshift takes when the limit is reached. The
-- default is log. For more information about this parameter, see
-- UsageLimit.
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)

-- | A list of tag instances.
createUsageLimit_tags :: Lens.Lens' CreateUsageLimit (Prelude.Maybe [Tag])
createUsageLimit_tags :: Lens' CreateUsageLimit (Maybe [Tag])
createUsageLimit_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateUsageLimit' :: CreateUsageLimit -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} Maybe [Tag]
a -> CreateUsageLimit
s {$sel:tags:CreateUsageLimit' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateUsageLimit) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The identifier of the cluster that you want to limit usage.
createUsageLimit_clusterIdentifier :: Lens.Lens' CreateUsageLimit Prelude.Text
createUsageLimit_clusterIdentifier :: Lens' CreateUsageLimit Text
createUsageLimit_clusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {Text
clusterIdentifier :: Text
$sel:clusterIdentifier:CreateUsageLimit' :: CreateUsageLimit -> Text
clusterIdentifier} -> Text
clusterIdentifier) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} Text
a -> CreateUsageLimit
s {$sel:clusterIdentifier:CreateUsageLimit' :: Text
clusterIdentifier = Text
a} :: CreateUsageLimit)

-- | The Amazon Redshift feature that you want to limit.
createUsageLimit_featureType :: Lens.Lens' CreateUsageLimit UsageLimitFeatureType
createUsageLimit_featureType :: Lens' CreateUsageLimit UsageLimitFeatureType
createUsageLimit_featureType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {UsageLimitFeatureType
featureType :: UsageLimitFeatureType
$sel:featureType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitFeatureType
featureType} -> UsageLimitFeatureType
featureType) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} UsageLimitFeatureType
a -> CreateUsageLimit
s {$sel:featureType:CreateUsageLimit' :: UsageLimitFeatureType
featureType = UsageLimitFeatureType
a} :: CreateUsageLimit)

-- | The type of limit. Depending on the feature type, this can be based on a
-- time duration or data size. If @FeatureType@ is @spectrum@, then
-- @LimitType@ must be @data-scanned@. If @FeatureType@ is
-- @concurrency-scaling@, then @LimitType@ must be @time@. If @FeatureType@
-- is @cross-region-datasharing@, then @LimitType@ must be @data-scanned@.
createUsageLimit_limitType :: Lens.Lens' CreateUsageLimit UsageLimitLimitType
createUsageLimit_limitType :: Lens' CreateUsageLimit UsageLimitLimitType
createUsageLimit_limitType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUsageLimit' {UsageLimitLimitType
limitType :: UsageLimitLimitType
$sel:limitType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitLimitType
limitType} -> UsageLimitLimitType
limitType) (\s :: CreateUsageLimit
s@CreateUsageLimit' {} UsageLimitLimitType
a -> CreateUsageLimit
s {$sel:limitType:CreateUsageLimit' :: UsageLimitLimitType
limitType = UsageLimitLimitType
a} :: CreateUsageLimit)

-- | The limit amount. If time-based, this amount is in minutes. If
-- data-based, this amount is in terabytes (TB). 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)

instance Core.AWSRequest CreateUsageLimit where
  type AWSResponse CreateUsageLimit = UsageLimit
  request :: (Service -> Service)
-> CreateUsageLimit -> Request CreateUsageLimit
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (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 =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"CreateUsageLimitResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable CreateUsageLimit where
  hashWithSalt :: Int -> CreateUsageLimit -> Int
hashWithSalt Int
_salt CreateUsageLimit' {Integer
Maybe [Tag]
Maybe UsageLimitBreachAction
Maybe UsageLimitPeriod
Text
UsageLimitFeatureType
UsageLimitLimitType
amount :: Integer
limitType :: UsageLimitLimitType
featureType :: UsageLimitFeatureType
clusterIdentifier :: Text
tags :: Maybe [Tag]
period :: Maybe UsageLimitPeriod
breachAction :: Maybe UsageLimitBreachAction
$sel:amount:CreateUsageLimit' :: CreateUsageLimit -> Integer
$sel:limitType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitLimitType
$sel:featureType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitFeatureType
$sel:clusterIdentifier:CreateUsageLimit' :: CreateUsageLimit -> Text
$sel:tags:CreateUsageLimit' :: CreateUsageLimit -> Maybe [Tag]
$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` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UsageLimitFeatureType
featureType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UsageLimitLimitType
limitType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
amount

instance Prelude.NFData CreateUsageLimit where
  rnf :: CreateUsageLimit -> ()
rnf CreateUsageLimit' {Integer
Maybe [Tag]
Maybe UsageLimitBreachAction
Maybe UsageLimitPeriod
Text
UsageLimitFeatureType
UsageLimitLimitType
amount :: Integer
limitType :: UsageLimitLimitType
featureType :: UsageLimitFeatureType
clusterIdentifier :: Text
tags :: Maybe [Tag]
period :: Maybe UsageLimitPeriod
breachAction :: Maybe UsageLimitBreachAction
$sel:amount:CreateUsageLimit' :: CreateUsageLimit -> Integer
$sel:limitType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitLimitType
$sel:featureType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitFeatureType
$sel:clusterIdentifier:CreateUsageLimit' :: CreateUsageLimit -> Text
$sel:tags:CreateUsageLimit' :: CreateUsageLimit -> Maybe [Tag]
$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 Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UsageLimitFeatureType
featureType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UsageLimitLimitType
limitType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
amount

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

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 CreateUsageLimit' {Integer
Maybe [Tag]
Maybe UsageLimitBreachAction
Maybe UsageLimitPeriod
Text
UsageLimitFeatureType
UsageLimitLimitType
amount :: Integer
limitType :: UsageLimitLimitType
featureType :: UsageLimitFeatureType
clusterIdentifier :: Text
tags :: Maybe [Tag]
period :: Maybe UsageLimitPeriod
breachAction :: Maybe UsageLimitBreachAction
$sel:amount:CreateUsageLimit' :: CreateUsageLimit -> Integer
$sel:limitType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitLimitType
$sel:featureType:CreateUsageLimit' :: CreateUsageLimit -> UsageLimitFeatureType
$sel:clusterIdentifier:CreateUsageLimit' :: CreateUsageLimit -> Text
$sel:tags:CreateUsageLimit' :: CreateUsageLimit -> Maybe [Tag]
$sel:period:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitPeriod
$sel:breachAction:CreateUsageLimit' :: CreateUsageLimit -> Maybe UsageLimitBreachAction
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateUsageLimit" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"BreachAction" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe UsageLimitBreachAction
breachAction,
        ByteString
"Period" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe UsageLimitPeriod
period,
        ByteString
"Tags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"ClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clusterIdentifier,
        ByteString
"FeatureType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: UsageLimitFeatureType
featureType,
        ByteString
"LimitType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: UsageLimitLimitType
limitType,
        ByteString
"Amount" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Integer
amount
      ]