{-# 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.StorageGateway.DescribeBandwidthRateLimitSchedule
-- 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 the bandwidth rate limit schedule of a
-- gateway. By default, gateways do not have bandwidth rate limit
-- schedules, which means no bandwidth rate limiting is in effect. This
-- operation is supported only for volume, tape and S3 file gateways. FSx
-- file gateways do not support bandwidth rate limits.
--
-- This operation returns information about a gateway\'s bandwidth rate
-- limit schedule. A bandwidth rate limit schedule consists of one or more
-- bandwidth rate limit intervals. A bandwidth rate limit interval defines
-- a period of time on one or more days of the week, during which bandwidth
-- rate limits are specified for uploading, downloading, or both.
--
-- A bandwidth rate limit interval consists of one or more days of the
-- week, a start hour and minute, an ending hour and minute, and bandwidth
-- rate limits for uploading and downloading
--
-- If no bandwidth rate limit schedule intervals are set for the gateway,
-- this operation returns an empty response. To specify which gateway to
-- describe, use the Amazon Resource Name (ARN) of the gateway in your
-- request.
module Amazonka.StorageGateway.DescribeBandwidthRateLimitSchedule
  ( -- * Creating a Request
    DescribeBandwidthRateLimitSchedule (..),
    newDescribeBandwidthRateLimitSchedule,

    -- * Request Lenses
    describeBandwidthRateLimitSchedule_gatewayARN,

    -- * Destructuring the Response
    DescribeBandwidthRateLimitScheduleResponse (..),
    newDescribeBandwidthRateLimitScheduleResponse,

    -- * Response Lenses
    describeBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals,
    describeBandwidthRateLimitScheduleResponse_gatewayARN,
    describeBandwidthRateLimitScheduleResponse_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.StorageGateway.Types

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

-- |
-- Create a value of 'DescribeBandwidthRateLimitSchedule' 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:
--
-- 'gatewayARN', 'describeBandwidthRateLimitSchedule_gatewayARN' - Undocumented member.
newDescribeBandwidthRateLimitSchedule ::
  -- | 'gatewayARN'
  Prelude.Text ->
  DescribeBandwidthRateLimitSchedule
newDescribeBandwidthRateLimitSchedule :: Text -> DescribeBandwidthRateLimitSchedule
newDescribeBandwidthRateLimitSchedule Text
pGatewayARN_ =
  DescribeBandwidthRateLimitSchedule'
    { $sel:gatewayARN:DescribeBandwidthRateLimitSchedule' :: Text
gatewayARN =
        Text
pGatewayARN_
    }

-- | Undocumented member.
describeBandwidthRateLimitSchedule_gatewayARN :: Lens.Lens' DescribeBandwidthRateLimitSchedule Prelude.Text
describeBandwidthRateLimitSchedule_gatewayARN :: Lens' DescribeBandwidthRateLimitSchedule Text
describeBandwidthRateLimitSchedule_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBandwidthRateLimitSchedule' {Text
gatewayARN :: Text
$sel:gatewayARN:DescribeBandwidthRateLimitSchedule' :: DescribeBandwidthRateLimitSchedule -> Text
gatewayARN} -> Text
gatewayARN) (\s :: DescribeBandwidthRateLimitSchedule
s@DescribeBandwidthRateLimitSchedule' {} Text
a -> DescribeBandwidthRateLimitSchedule
s {$sel:gatewayARN:DescribeBandwidthRateLimitSchedule' :: Text
gatewayARN = Text
a} :: DescribeBandwidthRateLimitSchedule)

instance
  Core.AWSRequest
    DescribeBandwidthRateLimitSchedule
  where
  type
    AWSResponse DescribeBandwidthRateLimitSchedule =
      DescribeBandwidthRateLimitScheduleResponse
  request :: (Service -> Service)
-> DescribeBandwidthRateLimitSchedule
-> Request DescribeBandwidthRateLimitSchedule
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 DescribeBandwidthRateLimitSchedule
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeBandwidthRateLimitSchedule)))
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 [BandwidthRateLimitInterval]
-> Maybe Text -> Int -> DescribeBandwidthRateLimitScheduleResponse
DescribeBandwidthRateLimitScheduleResponse'
            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
"BandwidthRateLimitIntervals"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GatewayARN")
            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
    DescribeBandwidthRateLimitSchedule
  where
  hashWithSalt :: Int -> DescribeBandwidthRateLimitSchedule -> Int
hashWithSalt
    Int
_salt
    DescribeBandwidthRateLimitSchedule' {Text
gatewayARN :: Text
$sel:gatewayARN:DescribeBandwidthRateLimitSchedule' :: DescribeBandwidthRateLimitSchedule -> Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayARN

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

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

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

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

-- | /See:/ 'newDescribeBandwidthRateLimitScheduleResponse' smart constructor.
data DescribeBandwidthRateLimitScheduleResponse = DescribeBandwidthRateLimitScheduleResponse'
  { -- | An array that contains the bandwidth rate limit intervals for a tape or
    -- volume gateway.
    DescribeBandwidthRateLimitScheduleResponse
-> Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals :: Prelude.Maybe [BandwidthRateLimitInterval],
    DescribeBandwidthRateLimitScheduleResponse -> Maybe Text
gatewayARN :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeBandwidthRateLimitScheduleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeBandwidthRateLimitScheduleResponse
-> DescribeBandwidthRateLimitScheduleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBandwidthRateLimitScheduleResponse
-> DescribeBandwidthRateLimitScheduleResponse -> Bool
$c/= :: DescribeBandwidthRateLimitScheduleResponse
-> DescribeBandwidthRateLimitScheduleResponse -> Bool
== :: DescribeBandwidthRateLimitScheduleResponse
-> DescribeBandwidthRateLimitScheduleResponse -> Bool
$c== :: DescribeBandwidthRateLimitScheduleResponse
-> DescribeBandwidthRateLimitScheduleResponse -> Bool
Prelude.Eq, ReadPrec [DescribeBandwidthRateLimitScheduleResponse]
ReadPrec DescribeBandwidthRateLimitScheduleResponse
Int -> ReadS DescribeBandwidthRateLimitScheduleResponse
ReadS [DescribeBandwidthRateLimitScheduleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBandwidthRateLimitScheduleResponse]
$creadListPrec :: ReadPrec [DescribeBandwidthRateLimitScheduleResponse]
readPrec :: ReadPrec DescribeBandwidthRateLimitScheduleResponse
$creadPrec :: ReadPrec DescribeBandwidthRateLimitScheduleResponse
readList :: ReadS [DescribeBandwidthRateLimitScheduleResponse]
$creadList :: ReadS [DescribeBandwidthRateLimitScheduleResponse]
readsPrec :: Int -> ReadS DescribeBandwidthRateLimitScheduleResponse
$creadsPrec :: Int -> ReadS DescribeBandwidthRateLimitScheduleResponse
Prelude.Read, Int -> DescribeBandwidthRateLimitScheduleResponse -> ShowS
[DescribeBandwidthRateLimitScheduleResponse] -> ShowS
DescribeBandwidthRateLimitScheduleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBandwidthRateLimitScheduleResponse] -> ShowS
$cshowList :: [DescribeBandwidthRateLimitScheduleResponse] -> ShowS
show :: DescribeBandwidthRateLimitScheduleResponse -> String
$cshow :: DescribeBandwidthRateLimitScheduleResponse -> String
showsPrec :: Int -> DescribeBandwidthRateLimitScheduleResponse -> ShowS
$cshowsPrec :: Int -> DescribeBandwidthRateLimitScheduleResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeBandwidthRateLimitScheduleResponse x
-> DescribeBandwidthRateLimitScheduleResponse
forall x.
DescribeBandwidthRateLimitScheduleResponse
-> Rep DescribeBandwidthRateLimitScheduleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeBandwidthRateLimitScheduleResponse x
-> DescribeBandwidthRateLimitScheduleResponse
$cfrom :: forall x.
DescribeBandwidthRateLimitScheduleResponse
-> Rep DescribeBandwidthRateLimitScheduleResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBandwidthRateLimitScheduleResponse' 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:
--
-- 'bandwidthRateLimitIntervals', 'describeBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals' - An array that contains the bandwidth rate limit intervals for a tape or
-- volume gateway.
--
-- 'gatewayARN', 'describeBandwidthRateLimitScheduleResponse_gatewayARN' - Undocumented member.
--
-- 'httpStatus', 'describeBandwidthRateLimitScheduleResponse_httpStatus' - The response's http status code.
newDescribeBandwidthRateLimitScheduleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeBandwidthRateLimitScheduleResponse
newDescribeBandwidthRateLimitScheduleResponse :: Int -> DescribeBandwidthRateLimitScheduleResponse
newDescribeBandwidthRateLimitScheduleResponse
  Int
pHttpStatus_ =
    DescribeBandwidthRateLimitScheduleResponse'
      { $sel:bandwidthRateLimitIntervals:DescribeBandwidthRateLimitScheduleResponse' :: Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals =
          forall a. Maybe a
Prelude.Nothing,
        $sel:gatewayARN:DescribeBandwidthRateLimitScheduleResponse' :: Maybe Text
gatewayARN = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeBandwidthRateLimitScheduleResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | An array that contains the bandwidth rate limit intervals for a tape or
-- volume gateway.
describeBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals :: Lens.Lens' DescribeBandwidthRateLimitScheduleResponse (Prelude.Maybe [BandwidthRateLimitInterval])
describeBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals :: Lens'
  DescribeBandwidthRateLimitScheduleResponse
  (Maybe [BandwidthRateLimitInterval])
describeBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBandwidthRateLimitScheduleResponse' {Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals :: Maybe [BandwidthRateLimitInterval]
$sel:bandwidthRateLimitIntervals:DescribeBandwidthRateLimitScheduleResponse' :: DescribeBandwidthRateLimitScheduleResponse
-> Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals} -> Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals) (\s :: DescribeBandwidthRateLimitScheduleResponse
s@DescribeBandwidthRateLimitScheduleResponse' {} Maybe [BandwidthRateLimitInterval]
a -> DescribeBandwidthRateLimitScheduleResponse
s {$sel:bandwidthRateLimitIntervals:DescribeBandwidthRateLimitScheduleResponse' :: Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals = Maybe [BandwidthRateLimitInterval]
a} :: DescribeBandwidthRateLimitScheduleResponse) 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

-- | Undocumented member.
describeBandwidthRateLimitScheduleResponse_gatewayARN :: Lens.Lens' DescribeBandwidthRateLimitScheduleResponse (Prelude.Maybe Prelude.Text)
describeBandwidthRateLimitScheduleResponse_gatewayARN :: Lens' DescribeBandwidthRateLimitScheduleResponse (Maybe Text)
describeBandwidthRateLimitScheduleResponse_gatewayARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBandwidthRateLimitScheduleResponse' {Maybe Text
gatewayARN :: Maybe Text
$sel:gatewayARN:DescribeBandwidthRateLimitScheduleResponse' :: DescribeBandwidthRateLimitScheduleResponse -> Maybe Text
gatewayARN} -> Maybe Text
gatewayARN) (\s :: DescribeBandwidthRateLimitScheduleResponse
s@DescribeBandwidthRateLimitScheduleResponse' {} Maybe Text
a -> DescribeBandwidthRateLimitScheduleResponse
s {$sel:gatewayARN:DescribeBandwidthRateLimitScheduleResponse' :: Maybe Text
gatewayARN = Maybe Text
a} :: DescribeBandwidthRateLimitScheduleResponse)

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

instance
  Prelude.NFData
    DescribeBandwidthRateLimitScheduleResponse
  where
  rnf :: DescribeBandwidthRateLimitScheduleResponse -> ()
rnf DescribeBandwidthRateLimitScheduleResponse' {Int
Maybe [BandwidthRateLimitInterval]
Maybe Text
httpStatus :: Int
gatewayARN :: Maybe Text
bandwidthRateLimitIntervals :: Maybe [BandwidthRateLimitInterval]
$sel:httpStatus:DescribeBandwidthRateLimitScheduleResponse' :: DescribeBandwidthRateLimitScheduleResponse -> Int
$sel:gatewayARN:DescribeBandwidthRateLimitScheduleResponse' :: DescribeBandwidthRateLimitScheduleResponse -> Maybe Text
$sel:bandwidthRateLimitIntervals:DescribeBandwidthRateLimitScheduleResponse' :: DescribeBandwidthRateLimitScheduleResponse
-> Maybe [BandwidthRateLimitInterval]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
gatewayARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus