{-# 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.BackupGateway.GetBandwidthRateLimitSchedule
-- 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 bandwidth rate limit schedule for a specified gateway. By
-- default, gateways do not have bandwidth rate limit schedules, which
-- means no bandwidth rate limiting is in effect. Use this to get a
-- gateway\'s bandwidth rate limit schedule.
module Amazonka.BackupGateway.GetBandwidthRateLimitSchedule
  ( -- * Creating a Request
    GetBandwidthRateLimitSchedule (..),
    newGetBandwidthRateLimitSchedule,

    -- * Request Lenses
    getBandwidthRateLimitSchedule_gatewayArn,

    -- * Destructuring the Response
    GetBandwidthRateLimitScheduleResponse (..),
    newGetBandwidthRateLimitScheduleResponse,

    -- * Response Lenses
    getBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals,
    getBandwidthRateLimitScheduleResponse_gatewayArn,
    getBandwidthRateLimitScheduleResponse_httpStatus,
  )
where

import Amazonka.BackupGateway.Types
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

-- | /See:/ 'newGetBandwidthRateLimitSchedule' smart constructor.
data GetBandwidthRateLimitSchedule = GetBandwidthRateLimitSchedule'
  { -- | The Amazon Resource Name (ARN) of the gateway. Use the
    -- <https://docs.aws.amazon.com/aws-backup/latest/devguide/API_BGW_ListGateways.html ListGateways>
    -- operation to return a list of gateways for your account and Amazon Web
    -- Services Region.
    GetBandwidthRateLimitSchedule -> Text
gatewayArn :: Prelude.Text
  }
  deriving (GetBandwidthRateLimitSchedule
-> GetBandwidthRateLimitSchedule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBandwidthRateLimitSchedule
-> GetBandwidthRateLimitSchedule -> Bool
$c/= :: GetBandwidthRateLimitSchedule
-> GetBandwidthRateLimitSchedule -> Bool
== :: GetBandwidthRateLimitSchedule
-> GetBandwidthRateLimitSchedule -> Bool
$c== :: GetBandwidthRateLimitSchedule
-> GetBandwidthRateLimitSchedule -> Bool
Prelude.Eq, ReadPrec [GetBandwidthRateLimitSchedule]
ReadPrec GetBandwidthRateLimitSchedule
Int -> ReadS GetBandwidthRateLimitSchedule
ReadS [GetBandwidthRateLimitSchedule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBandwidthRateLimitSchedule]
$creadListPrec :: ReadPrec [GetBandwidthRateLimitSchedule]
readPrec :: ReadPrec GetBandwidthRateLimitSchedule
$creadPrec :: ReadPrec GetBandwidthRateLimitSchedule
readList :: ReadS [GetBandwidthRateLimitSchedule]
$creadList :: ReadS [GetBandwidthRateLimitSchedule]
readsPrec :: Int -> ReadS GetBandwidthRateLimitSchedule
$creadsPrec :: Int -> ReadS GetBandwidthRateLimitSchedule
Prelude.Read, Int -> GetBandwidthRateLimitSchedule -> ShowS
[GetBandwidthRateLimitSchedule] -> ShowS
GetBandwidthRateLimitSchedule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBandwidthRateLimitSchedule] -> ShowS
$cshowList :: [GetBandwidthRateLimitSchedule] -> ShowS
show :: GetBandwidthRateLimitSchedule -> String
$cshow :: GetBandwidthRateLimitSchedule -> String
showsPrec :: Int -> GetBandwidthRateLimitSchedule -> ShowS
$cshowsPrec :: Int -> GetBandwidthRateLimitSchedule -> ShowS
Prelude.Show, forall x.
Rep GetBandwidthRateLimitSchedule x
-> GetBandwidthRateLimitSchedule
forall x.
GetBandwidthRateLimitSchedule
-> Rep GetBandwidthRateLimitSchedule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBandwidthRateLimitSchedule x
-> GetBandwidthRateLimitSchedule
$cfrom :: forall x.
GetBandwidthRateLimitSchedule
-> Rep GetBandwidthRateLimitSchedule x
Prelude.Generic)

-- |
-- Create a value of 'GetBandwidthRateLimitSchedule' 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', 'getBandwidthRateLimitSchedule_gatewayArn' - The Amazon Resource Name (ARN) of the gateway. Use the
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/API_BGW_ListGateways.html ListGateways>
-- operation to return a list of gateways for your account and Amazon Web
-- Services Region.
newGetBandwidthRateLimitSchedule ::
  -- | 'gatewayArn'
  Prelude.Text ->
  GetBandwidthRateLimitSchedule
newGetBandwidthRateLimitSchedule :: Text -> GetBandwidthRateLimitSchedule
newGetBandwidthRateLimitSchedule Text
pGatewayArn_ =
  GetBandwidthRateLimitSchedule'
    { $sel:gatewayArn:GetBandwidthRateLimitSchedule' :: Text
gatewayArn =
        Text
pGatewayArn_
    }

-- | The Amazon Resource Name (ARN) of the gateway. Use the
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/API_BGW_ListGateways.html ListGateways>
-- operation to return a list of gateways for your account and Amazon Web
-- Services Region.
getBandwidthRateLimitSchedule_gatewayArn :: Lens.Lens' GetBandwidthRateLimitSchedule Prelude.Text
getBandwidthRateLimitSchedule_gatewayArn :: Lens' GetBandwidthRateLimitSchedule Text
getBandwidthRateLimitSchedule_gatewayArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBandwidthRateLimitSchedule' {Text
gatewayArn :: Text
$sel:gatewayArn:GetBandwidthRateLimitSchedule' :: GetBandwidthRateLimitSchedule -> Text
gatewayArn} -> Text
gatewayArn) (\s :: GetBandwidthRateLimitSchedule
s@GetBandwidthRateLimitSchedule' {} Text
a -> GetBandwidthRateLimitSchedule
s {$sel:gatewayArn:GetBandwidthRateLimitSchedule' :: Text
gatewayArn = Text
a} :: GetBandwidthRateLimitSchedule)

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

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

instance Data.ToHeaders GetBandwidthRateLimitSchedule where
  toHeaders :: GetBandwidthRateLimitSchedule -> 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
"BackupOnPremises_v20210101.GetBandwidthRateLimitSchedule" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetBandwidthRateLimitSchedule where
  toJSON :: GetBandwidthRateLimitSchedule -> Value
toJSON GetBandwidthRateLimitSchedule' {Text
gatewayArn :: Text
$sel:gatewayArn:GetBandwidthRateLimitSchedule' :: GetBandwidthRateLimitSchedule -> 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 GetBandwidthRateLimitSchedule where
  toPath :: GetBandwidthRateLimitSchedule -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetBandwidthRateLimitScheduleResponse' smart constructor.
data GetBandwidthRateLimitScheduleResponse = GetBandwidthRateLimitScheduleResponse'
  { -- | An array containing bandwidth rate limit schedule intervals for a
    -- gateway. When no bandwidth rate limit intervals have been scheduled, the
    -- array is empty.
    GetBandwidthRateLimitScheduleResponse
-> Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals :: Prelude.Maybe [BandwidthRateLimitInterval],
    -- | The Amazon Resource Name (ARN) of the gateway. Use the
    -- <https://docs.aws.amazon.com/aws-backup/latest/devguide/API_BGW_ListGateways.html ListGateways>
    -- operation to return a list of gateways for your account and Amazon Web
    -- Services Region.
    GetBandwidthRateLimitScheduleResponse -> Maybe Text
gatewayArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBandwidthRateLimitScheduleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBandwidthRateLimitScheduleResponse
-> GetBandwidthRateLimitScheduleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBandwidthRateLimitScheduleResponse
-> GetBandwidthRateLimitScheduleResponse -> Bool
$c/= :: GetBandwidthRateLimitScheduleResponse
-> GetBandwidthRateLimitScheduleResponse -> Bool
== :: GetBandwidthRateLimitScheduleResponse
-> GetBandwidthRateLimitScheduleResponse -> Bool
$c== :: GetBandwidthRateLimitScheduleResponse
-> GetBandwidthRateLimitScheduleResponse -> Bool
Prelude.Eq, ReadPrec [GetBandwidthRateLimitScheduleResponse]
ReadPrec GetBandwidthRateLimitScheduleResponse
Int -> ReadS GetBandwidthRateLimitScheduleResponse
ReadS [GetBandwidthRateLimitScheduleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBandwidthRateLimitScheduleResponse]
$creadListPrec :: ReadPrec [GetBandwidthRateLimitScheduleResponse]
readPrec :: ReadPrec GetBandwidthRateLimitScheduleResponse
$creadPrec :: ReadPrec GetBandwidthRateLimitScheduleResponse
readList :: ReadS [GetBandwidthRateLimitScheduleResponse]
$creadList :: ReadS [GetBandwidthRateLimitScheduleResponse]
readsPrec :: Int -> ReadS GetBandwidthRateLimitScheduleResponse
$creadsPrec :: Int -> ReadS GetBandwidthRateLimitScheduleResponse
Prelude.Read, Int -> GetBandwidthRateLimitScheduleResponse -> ShowS
[GetBandwidthRateLimitScheduleResponse] -> ShowS
GetBandwidthRateLimitScheduleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBandwidthRateLimitScheduleResponse] -> ShowS
$cshowList :: [GetBandwidthRateLimitScheduleResponse] -> ShowS
show :: GetBandwidthRateLimitScheduleResponse -> String
$cshow :: GetBandwidthRateLimitScheduleResponse -> String
showsPrec :: Int -> GetBandwidthRateLimitScheduleResponse -> ShowS
$cshowsPrec :: Int -> GetBandwidthRateLimitScheduleResponse -> ShowS
Prelude.Show, forall x.
Rep GetBandwidthRateLimitScheduleResponse x
-> GetBandwidthRateLimitScheduleResponse
forall x.
GetBandwidthRateLimitScheduleResponse
-> Rep GetBandwidthRateLimitScheduleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBandwidthRateLimitScheduleResponse x
-> GetBandwidthRateLimitScheduleResponse
$cfrom :: forall x.
GetBandwidthRateLimitScheduleResponse
-> Rep GetBandwidthRateLimitScheduleResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBandwidthRateLimitScheduleResponse' 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', 'getBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals' - An array containing bandwidth rate limit schedule intervals for a
-- gateway. When no bandwidth rate limit intervals have been scheduled, the
-- array is empty.
--
-- 'gatewayArn', 'getBandwidthRateLimitScheduleResponse_gatewayArn' - The Amazon Resource Name (ARN) of the gateway. Use the
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/API_BGW_ListGateways.html ListGateways>
-- operation to return a list of gateways for your account and Amazon Web
-- Services Region.
--
-- 'httpStatus', 'getBandwidthRateLimitScheduleResponse_httpStatus' - The response's http status code.
newGetBandwidthRateLimitScheduleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBandwidthRateLimitScheduleResponse
newGetBandwidthRateLimitScheduleResponse :: Int -> GetBandwidthRateLimitScheduleResponse
newGetBandwidthRateLimitScheduleResponse Int
pHttpStatus_ =
  GetBandwidthRateLimitScheduleResponse'
    { $sel:bandwidthRateLimitIntervals:GetBandwidthRateLimitScheduleResponse' :: Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals =
        forall a. Maybe a
Prelude.Nothing,
      $sel:gatewayArn:GetBandwidthRateLimitScheduleResponse' :: Maybe Text
gatewayArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBandwidthRateLimitScheduleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array containing bandwidth rate limit schedule intervals for a
-- gateway. When no bandwidth rate limit intervals have been scheduled, the
-- array is empty.
getBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals :: Lens.Lens' GetBandwidthRateLimitScheduleResponse (Prelude.Maybe [BandwidthRateLimitInterval])
getBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals :: Lens'
  GetBandwidthRateLimitScheduleResponse
  (Maybe [BandwidthRateLimitInterval])
getBandwidthRateLimitScheduleResponse_bandwidthRateLimitIntervals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBandwidthRateLimitScheduleResponse' {Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals :: Maybe [BandwidthRateLimitInterval]
$sel:bandwidthRateLimitIntervals:GetBandwidthRateLimitScheduleResponse' :: GetBandwidthRateLimitScheduleResponse
-> Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals} -> Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals) (\s :: GetBandwidthRateLimitScheduleResponse
s@GetBandwidthRateLimitScheduleResponse' {} Maybe [BandwidthRateLimitInterval]
a -> GetBandwidthRateLimitScheduleResponse
s {$sel:bandwidthRateLimitIntervals:GetBandwidthRateLimitScheduleResponse' :: Maybe [BandwidthRateLimitInterval]
bandwidthRateLimitIntervals = Maybe [BandwidthRateLimitInterval]
a} :: GetBandwidthRateLimitScheduleResponse) 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 Amazon Resource Name (ARN) of the gateway. Use the
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/API_BGW_ListGateways.html ListGateways>
-- operation to return a list of gateways for your account and Amazon Web
-- Services Region.
getBandwidthRateLimitScheduleResponse_gatewayArn :: Lens.Lens' GetBandwidthRateLimitScheduleResponse (Prelude.Maybe Prelude.Text)
getBandwidthRateLimitScheduleResponse_gatewayArn :: Lens' GetBandwidthRateLimitScheduleResponse (Maybe Text)
getBandwidthRateLimitScheduleResponse_gatewayArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBandwidthRateLimitScheduleResponse' {Maybe Text
gatewayArn :: Maybe Text
$sel:gatewayArn:GetBandwidthRateLimitScheduleResponse' :: GetBandwidthRateLimitScheduleResponse -> Maybe Text
gatewayArn} -> Maybe Text
gatewayArn) (\s :: GetBandwidthRateLimitScheduleResponse
s@GetBandwidthRateLimitScheduleResponse' {} Maybe Text
a -> GetBandwidthRateLimitScheduleResponse
s {$sel:gatewayArn:GetBandwidthRateLimitScheduleResponse' :: Maybe Text
gatewayArn = Maybe Text
a} :: GetBandwidthRateLimitScheduleResponse)

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

instance
  Prelude.NFData
    GetBandwidthRateLimitScheduleResponse
  where
  rnf :: GetBandwidthRateLimitScheduleResponse -> ()
rnf GetBandwidthRateLimitScheduleResponse' {Int
Maybe [BandwidthRateLimitInterval]
Maybe Text
httpStatus :: Int
gatewayArn :: Maybe Text
bandwidthRateLimitIntervals :: Maybe [BandwidthRateLimitInterval]
$sel:httpStatus:GetBandwidthRateLimitScheduleResponse' :: GetBandwidthRateLimitScheduleResponse -> Int
$sel:gatewayArn:GetBandwidthRateLimitScheduleResponse' :: GetBandwidthRateLimitScheduleResponse -> Maybe Text
$sel:bandwidthRateLimitIntervals:GetBandwidthRateLimitScheduleResponse' :: GetBandwidthRateLimitScheduleResponse
-> 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