{-# 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.GetUsageLimit
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a usage limit.
module Amazonka.RedshiftServerLess.GetUsageLimit
  ( -- * Creating a Request
    GetUsageLimit (..),
    newGetUsageLimit,

    -- * Request Lenses
    getUsageLimit_usageLimitId,

    -- * Destructuring the Response
    GetUsageLimitResponse (..),
    newGetUsageLimitResponse,

    -- * Response Lenses
    getUsageLimitResponse_usageLimit,
    getUsageLimitResponse_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:/ 'newGetUsageLimit' smart constructor.
data GetUsageLimit = GetUsageLimit'
  { -- | The unique identifier of the usage limit to return information for.
    GetUsageLimit -> Text
usageLimitId :: Prelude.Text
  }
  deriving (GetUsageLimit -> GetUsageLimit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUsageLimit -> GetUsageLimit -> Bool
$c/= :: GetUsageLimit -> GetUsageLimit -> Bool
== :: GetUsageLimit -> GetUsageLimit -> Bool
$c== :: GetUsageLimit -> GetUsageLimit -> Bool
Prelude.Eq, ReadPrec [GetUsageLimit]
ReadPrec GetUsageLimit
Int -> ReadS GetUsageLimit
ReadS [GetUsageLimit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetUsageLimit]
$creadListPrec :: ReadPrec [GetUsageLimit]
readPrec :: ReadPrec GetUsageLimit
$creadPrec :: ReadPrec GetUsageLimit
readList :: ReadS [GetUsageLimit]
$creadList :: ReadS [GetUsageLimit]
readsPrec :: Int -> ReadS GetUsageLimit
$creadsPrec :: Int -> ReadS GetUsageLimit
Prelude.Read, Int -> GetUsageLimit -> ShowS
[GetUsageLimit] -> ShowS
GetUsageLimit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUsageLimit] -> ShowS
$cshowList :: [GetUsageLimit] -> ShowS
show :: GetUsageLimit -> String
$cshow :: GetUsageLimit -> String
showsPrec :: Int -> GetUsageLimit -> ShowS
$cshowsPrec :: Int -> GetUsageLimit -> ShowS
Prelude.Show, forall x. Rep GetUsageLimit x -> GetUsageLimit
forall x. GetUsageLimit -> Rep GetUsageLimit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUsageLimit x -> GetUsageLimit
$cfrom :: forall x. GetUsageLimit -> Rep GetUsageLimit x
Prelude.Generic)

-- |
-- Create a value of 'GetUsageLimit' 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:
--
-- 'usageLimitId', 'getUsageLimit_usageLimitId' - The unique identifier of the usage limit to return information for.
newGetUsageLimit ::
  -- | 'usageLimitId'
  Prelude.Text ->
  GetUsageLimit
newGetUsageLimit :: Text -> GetUsageLimit
newGetUsageLimit Text
pUsageLimitId_ =
  GetUsageLimit' {$sel:usageLimitId:GetUsageLimit' :: Text
usageLimitId = Text
pUsageLimitId_}

-- | The unique identifier of the usage limit to return information for.
getUsageLimit_usageLimitId :: Lens.Lens' GetUsageLimit Prelude.Text
getUsageLimit_usageLimitId :: Lens' GetUsageLimit Text
getUsageLimit_usageLimitId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetUsageLimit' {Text
usageLimitId :: Text
$sel:usageLimitId:GetUsageLimit' :: GetUsageLimit -> Text
usageLimitId} -> Text
usageLimitId) (\s :: GetUsageLimit
s@GetUsageLimit' {} Text
a -> GetUsageLimit
s {$sel:usageLimitId:GetUsageLimit' :: Text
usageLimitId = Text
a} :: GetUsageLimit)

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

instance Prelude.NFData GetUsageLimit where
  rnf :: GetUsageLimit -> ()
rnf GetUsageLimit' {Text
usageLimitId :: Text
$sel:usageLimitId:GetUsageLimit' :: GetUsageLimit -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
usageLimitId

instance Data.ToHeaders GetUsageLimit where
  toHeaders :: GetUsageLimit -> 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.GetUsageLimit" ::
                          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 GetUsageLimit where
  toJSON :: GetUsageLimit -> Value
toJSON GetUsageLimit' {Text
usageLimitId :: Text
$sel:usageLimitId:GetUsageLimit' :: GetUsageLimit -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [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 GetUsageLimit where
  toPath :: GetUsageLimit -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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

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