{-# 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.ServiceQuotas.AssociateServiceQuotaTemplate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates your quota request template with your organization. When a
-- new account is created in your organization, the quota increase requests
-- in the template are automatically applied to the account. You can add a
-- quota increase request for any adjustable quota to your template.
module Amazonka.ServiceQuotas.AssociateServiceQuotaTemplate
  ( -- * Creating a Request
    AssociateServiceQuotaTemplate (..),
    newAssociateServiceQuotaTemplate,

    -- * Destructuring the Response
    AssociateServiceQuotaTemplateResponse (..),
    newAssociateServiceQuotaTemplateResponse,

    -- * Response Lenses
    associateServiceQuotaTemplateResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.ServiceQuotas.Types

-- | /See:/ 'newAssociateServiceQuotaTemplate' smart constructor.
data AssociateServiceQuotaTemplate = AssociateServiceQuotaTemplate'
  {
  }
  deriving (AssociateServiceQuotaTemplate
-> AssociateServiceQuotaTemplate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateServiceQuotaTemplate
-> AssociateServiceQuotaTemplate -> Bool
$c/= :: AssociateServiceQuotaTemplate
-> AssociateServiceQuotaTemplate -> Bool
== :: AssociateServiceQuotaTemplate
-> AssociateServiceQuotaTemplate -> Bool
$c== :: AssociateServiceQuotaTemplate
-> AssociateServiceQuotaTemplate -> Bool
Prelude.Eq, ReadPrec [AssociateServiceQuotaTemplate]
ReadPrec AssociateServiceQuotaTemplate
Int -> ReadS AssociateServiceQuotaTemplate
ReadS [AssociateServiceQuotaTemplate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateServiceQuotaTemplate]
$creadListPrec :: ReadPrec [AssociateServiceQuotaTemplate]
readPrec :: ReadPrec AssociateServiceQuotaTemplate
$creadPrec :: ReadPrec AssociateServiceQuotaTemplate
readList :: ReadS [AssociateServiceQuotaTemplate]
$creadList :: ReadS [AssociateServiceQuotaTemplate]
readsPrec :: Int -> ReadS AssociateServiceQuotaTemplate
$creadsPrec :: Int -> ReadS AssociateServiceQuotaTemplate
Prelude.Read, Int -> AssociateServiceQuotaTemplate -> ShowS
[AssociateServiceQuotaTemplate] -> ShowS
AssociateServiceQuotaTemplate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateServiceQuotaTemplate] -> ShowS
$cshowList :: [AssociateServiceQuotaTemplate] -> ShowS
show :: AssociateServiceQuotaTemplate -> String
$cshow :: AssociateServiceQuotaTemplate -> String
showsPrec :: Int -> AssociateServiceQuotaTemplate -> ShowS
$cshowsPrec :: Int -> AssociateServiceQuotaTemplate -> ShowS
Prelude.Show, forall x.
Rep AssociateServiceQuotaTemplate x
-> AssociateServiceQuotaTemplate
forall x.
AssociateServiceQuotaTemplate
-> Rep AssociateServiceQuotaTemplate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AssociateServiceQuotaTemplate x
-> AssociateServiceQuotaTemplate
$cfrom :: forall x.
AssociateServiceQuotaTemplate
-> Rep AssociateServiceQuotaTemplate x
Prelude.Generic)

-- |
-- Create a value of 'AssociateServiceQuotaTemplate' 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.
newAssociateServiceQuotaTemplate ::
  AssociateServiceQuotaTemplate
newAssociateServiceQuotaTemplate :: AssociateServiceQuotaTemplate
newAssociateServiceQuotaTemplate =
  AssociateServiceQuotaTemplate
AssociateServiceQuotaTemplate'

instance
  Core.AWSRequest
    AssociateServiceQuotaTemplate
  where
  type
    AWSResponse AssociateServiceQuotaTemplate =
      AssociateServiceQuotaTemplateResponse
  request :: (Service -> Service)
-> AssociateServiceQuotaTemplate
-> Request AssociateServiceQuotaTemplate
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 AssociateServiceQuotaTemplate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateServiceQuotaTemplate)))
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 -> AssociateServiceQuotaTemplateResponse
AssociateServiceQuotaTemplateResponse'
            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
    AssociateServiceQuotaTemplate
  where
  hashWithSalt :: Int -> AssociateServiceQuotaTemplate -> Int
hashWithSalt Int
_salt AssociateServiceQuotaTemplate
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

instance Prelude.NFData AssociateServiceQuotaTemplate where
  rnf :: AssociateServiceQuotaTemplate -> ()
rnf AssociateServiceQuotaTemplate
_ = ()

instance Data.ToHeaders AssociateServiceQuotaTemplate where
  toHeaders :: AssociateServiceQuotaTemplate -> 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
"ServiceQuotasV20190624.AssociateServiceQuotaTemplate" ::
                          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 AssociateServiceQuotaTemplate where
  toJSON :: AssociateServiceQuotaTemplate -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

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

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

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