{-# 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.GetAWSDefaultServiceQuota
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the default value for the specified quota. The default value
-- does not reflect any quota increases.
module Amazonka.ServiceQuotas.GetAWSDefaultServiceQuota
  ( -- * Creating a Request
    GetAWSDefaultServiceQuota (..),
    newGetAWSDefaultServiceQuota,

    -- * Request Lenses
    getAWSDefaultServiceQuota_serviceCode,
    getAWSDefaultServiceQuota_quotaCode,

    -- * Destructuring the Response
    GetAWSDefaultServiceQuotaResponse (..),
    newGetAWSDefaultServiceQuotaResponse,

    -- * Response Lenses
    getAWSDefaultServiceQuotaResponse_quota,
    getAWSDefaultServiceQuotaResponse_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:/ 'newGetAWSDefaultServiceQuota' smart constructor.
data GetAWSDefaultServiceQuota = GetAWSDefaultServiceQuota'
  { -- | The service identifier.
    GetAWSDefaultServiceQuota -> Text
serviceCode :: Prelude.Text,
    -- | The quota identifier.
    GetAWSDefaultServiceQuota -> Text
quotaCode :: Prelude.Text
  }
  deriving (GetAWSDefaultServiceQuota -> GetAWSDefaultServiceQuota -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAWSDefaultServiceQuota -> GetAWSDefaultServiceQuota -> Bool
$c/= :: GetAWSDefaultServiceQuota -> GetAWSDefaultServiceQuota -> Bool
== :: GetAWSDefaultServiceQuota -> GetAWSDefaultServiceQuota -> Bool
$c== :: GetAWSDefaultServiceQuota -> GetAWSDefaultServiceQuota -> Bool
Prelude.Eq, ReadPrec [GetAWSDefaultServiceQuota]
ReadPrec GetAWSDefaultServiceQuota
Int -> ReadS GetAWSDefaultServiceQuota
ReadS [GetAWSDefaultServiceQuota]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAWSDefaultServiceQuota]
$creadListPrec :: ReadPrec [GetAWSDefaultServiceQuota]
readPrec :: ReadPrec GetAWSDefaultServiceQuota
$creadPrec :: ReadPrec GetAWSDefaultServiceQuota
readList :: ReadS [GetAWSDefaultServiceQuota]
$creadList :: ReadS [GetAWSDefaultServiceQuota]
readsPrec :: Int -> ReadS GetAWSDefaultServiceQuota
$creadsPrec :: Int -> ReadS GetAWSDefaultServiceQuota
Prelude.Read, Int -> GetAWSDefaultServiceQuota -> ShowS
[GetAWSDefaultServiceQuota] -> ShowS
GetAWSDefaultServiceQuota -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAWSDefaultServiceQuota] -> ShowS
$cshowList :: [GetAWSDefaultServiceQuota] -> ShowS
show :: GetAWSDefaultServiceQuota -> String
$cshow :: GetAWSDefaultServiceQuota -> String
showsPrec :: Int -> GetAWSDefaultServiceQuota -> ShowS
$cshowsPrec :: Int -> GetAWSDefaultServiceQuota -> ShowS
Prelude.Show, forall x.
Rep GetAWSDefaultServiceQuota x -> GetAWSDefaultServiceQuota
forall x.
GetAWSDefaultServiceQuota -> Rep GetAWSDefaultServiceQuota x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAWSDefaultServiceQuota x -> GetAWSDefaultServiceQuota
$cfrom :: forall x.
GetAWSDefaultServiceQuota -> Rep GetAWSDefaultServiceQuota x
Prelude.Generic)

-- |
-- Create a value of 'GetAWSDefaultServiceQuota' 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:
--
-- 'serviceCode', 'getAWSDefaultServiceQuota_serviceCode' - The service identifier.
--
-- 'quotaCode', 'getAWSDefaultServiceQuota_quotaCode' - The quota identifier.
newGetAWSDefaultServiceQuota ::
  -- | 'serviceCode'
  Prelude.Text ->
  -- | 'quotaCode'
  Prelude.Text ->
  GetAWSDefaultServiceQuota
newGetAWSDefaultServiceQuota :: Text -> Text -> GetAWSDefaultServiceQuota
newGetAWSDefaultServiceQuota
  Text
pServiceCode_
  Text
pQuotaCode_ =
    GetAWSDefaultServiceQuota'
      { $sel:serviceCode:GetAWSDefaultServiceQuota' :: Text
serviceCode =
          Text
pServiceCode_,
        $sel:quotaCode:GetAWSDefaultServiceQuota' :: Text
quotaCode = Text
pQuotaCode_
      }

-- | The service identifier.
getAWSDefaultServiceQuota_serviceCode :: Lens.Lens' GetAWSDefaultServiceQuota Prelude.Text
getAWSDefaultServiceQuota_serviceCode :: Lens' GetAWSDefaultServiceQuota Text
getAWSDefaultServiceQuota_serviceCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAWSDefaultServiceQuota' {Text
serviceCode :: Text
$sel:serviceCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
serviceCode} -> Text
serviceCode) (\s :: GetAWSDefaultServiceQuota
s@GetAWSDefaultServiceQuota' {} Text
a -> GetAWSDefaultServiceQuota
s {$sel:serviceCode:GetAWSDefaultServiceQuota' :: Text
serviceCode = Text
a} :: GetAWSDefaultServiceQuota)

-- | The quota identifier.
getAWSDefaultServiceQuota_quotaCode :: Lens.Lens' GetAWSDefaultServiceQuota Prelude.Text
getAWSDefaultServiceQuota_quotaCode :: Lens' GetAWSDefaultServiceQuota Text
getAWSDefaultServiceQuota_quotaCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAWSDefaultServiceQuota' {Text
quotaCode :: Text
$sel:quotaCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
quotaCode} -> Text
quotaCode) (\s :: GetAWSDefaultServiceQuota
s@GetAWSDefaultServiceQuota' {} Text
a -> GetAWSDefaultServiceQuota
s {$sel:quotaCode:GetAWSDefaultServiceQuota' :: Text
quotaCode = Text
a} :: GetAWSDefaultServiceQuota)

instance Core.AWSRequest GetAWSDefaultServiceQuota where
  type
    AWSResponse GetAWSDefaultServiceQuota =
      GetAWSDefaultServiceQuotaResponse
  request :: (Service -> Service)
-> GetAWSDefaultServiceQuota -> Request GetAWSDefaultServiceQuota
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 GetAWSDefaultServiceQuota
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAWSDefaultServiceQuota)))
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 ServiceQuota -> Int -> GetAWSDefaultServiceQuotaResponse
GetAWSDefaultServiceQuotaResponse'
            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
"Quota")
            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 GetAWSDefaultServiceQuota where
  hashWithSalt :: Int -> GetAWSDefaultServiceQuota -> Int
hashWithSalt Int
_salt GetAWSDefaultServiceQuota' {Text
quotaCode :: Text
serviceCode :: Text
$sel:quotaCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
$sel:serviceCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
quotaCode

instance Prelude.NFData GetAWSDefaultServiceQuota where
  rnf :: GetAWSDefaultServiceQuota -> ()
rnf GetAWSDefaultServiceQuota' {Text
quotaCode :: Text
serviceCode :: Text
$sel:quotaCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
$sel:serviceCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
serviceCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
quotaCode

instance Data.ToHeaders GetAWSDefaultServiceQuota where
  toHeaders :: GetAWSDefaultServiceQuota -> 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.GetAWSDefaultServiceQuota" ::
                          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 GetAWSDefaultServiceQuota where
  toJSON :: GetAWSDefaultServiceQuota -> Value
toJSON GetAWSDefaultServiceQuota' {Text
quotaCode :: Text
serviceCode :: Text
$sel:quotaCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
$sel:serviceCode:GetAWSDefaultServiceQuota' :: GetAWSDefaultServiceQuota -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"ServiceCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceCode),
            forall a. a -> Maybe a
Prelude.Just (Key
"QuotaCode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
quotaCode)
          ]
      )

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

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

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

-- |
-- Create a value of 'GetAWSDefaultServiceQuotaResponse' 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:
--
-- 'quota', 'getAWSDefaultServiceQuotaResponse_quota' - Information about the quota.
--
-- 'httpStatus', 'getAWSDefaultServiceQuotaResponse_httpStatus' - The response's http status code.
newGetAWSDefaultServiceQuotaResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAWSDefaultServiceQuotaResponse
newGetAWSDefaultServiceQuotaResponse :: Int -> GetAWSDefaultServiceQuotaResponse
newGetAWSDefaultServiceQuotaResponse Int
pHttpStatus_ =
  GetAWSDefaultServiceQuotaResponse'
    { $sel:quota:GetAWSDefaultServiceQuotaResponse' :: Maybe ServiceQuota
quota =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAWSDefaultServiceQuotaResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the quota.
getAWSDefaultServiceQuotaResponse_quota :: Lens.Lens' GetAWSDefaultServiceQuotaResponse (Prelude.Maybe ServiceQuota)
getAWSDefaultServiceQuotaResponse_quota :: Lens' GetAWSDefaultServiceQuotaResponse (Maybe ServiceQuota)
getAWSDefaultServiceQuotaResponse_quota = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAWSDefaultServiceQuotaResponse' {Maybe ServiceQuota
quota :: Maybe ServiceQuota
$sel:quota:GetAWSDefaultServiceQuotaResponse' :: GetAWSDefaultServiceQuotaResponse -> Maybe ServiceQuota
quota} -> Maybe ServiceQuota
quota) (\s :: GetAWSDefaultServiceQuotaResponse
s@GetAWSDefaultServiceQuotaResponse' {} Maybe ServiceQuota
a -> GetAWSDefaultServiceQuotaResponse
s {$sel:quota:GetAWSDefaultServiceQuotaResponse' :: Maybe ServiceQuota
quota = Maybe ServiceQuota
a} :: GetAWSDefaultServiceQuotaResponse)

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

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