{-# 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.EC2.AcceptReservedInstancesExchangeQuote
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Accepts the Convertible Reserved Instance exchange quote described in
-- the GetReservedInstancesExchangeQuote call.
module Amazonka.EC2.AcceptReservedInstancesExchangeQuote
  ( -- * Creating a Request
    AcceptReservedInstancesExchangeQuote (..),
    newAcceptReservedInstancesExchangeQuote,

    -- * Request Lenses
    acceptReservedInstancesExchangeQuote_dryRun,
    acceptReservedInstancesExchangeQuote_targetConfigurations,
    acceptReservedInstancesExchangeQuote_reservedInstanceIds,

    -- * Destructuring the Response
    AcceptReservedInstancesExchangeQuoteResponse (..),
    newAcceptReservedInstancesExchangeQuoteResponse,

    -- * Response Lenses
    acceptReservedInstancesExchangeQuoteResponse_exchangeId,
    acceptReservedInstancesExchangeQuoteResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Contains the parameters for accepting the quote.
--
-- /See:/ 'newAcceptReservedInstancesExchangeQuote' smart constructor.
data AcceptReservedInstancesExchangeQuote = AcceptReservedInstancesExchangeQuote'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    AcceptReservedInstancesExchangeQuote -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The configuration of the target Convertible Reserved Instance to
    -- exchange for your current Convertible Reserved Instances.
    AcceptReservedInstancesExchangeQuote
-> Maybe [TargetConfigurationRequest]
targetConfigurations :: Prelude.Maybe [TargetConfigurationRequest],
    -- | The IDs of the Convertible Reserved Instances to exchange for another
    -- Convertible Reserved Instance of the same or higher value.
    AcceptReservedInstancesExchangeQuote -> [Text]
reservedInstanceIds :: [Prelude.Text]
  }
  deriving (AcceptReservedInstancesExchangeQuote
-> AcceptReservedInstancesExchangeQuote -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptReservedInstancesExchangeQuote
-> AcceptReservedInstancesExchangeQuote -> Bool
$c/= :: AcceptReservedInstancesExchangeQuote
-> AcceptReservedInstancesExchangeQuote -> Bool
== :: AcceptReservedInstancesExchangeQuote
-> AcceptReservedInstancesExchangeQuote -> Bool
$c== :: AcceptReservedInstancesExchangeQuote
-> AcceptReservedInstancesExchangeQuote -> Bool
Prelude.Eq, ReadPrec [AcceptReservedInstancesExchangeQuote]
ReadPrec AcceptReservedInstancesExchangeQuote
Int -> ReadS AcceptReservedInstancesExchangeQuote
ReadS [AcceptReservedInstancesExchangeQuote]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AcceptReservedInstancesExchangeQuote]
$creadListPrec :: ReadPrec [AcceptReservedInstancesExchangeQuote]
readPrec :: ReadPrec AcceptReservedInstancesExchangeQuote
$creadPrec :: ReadPrec AcceptReservedInstancesExchangeQuote
readList :: ReadS [AcceptReservedInstancesExchangeQuote]
$creadList :: ReadS [AcceptReservedInstancesExchangeQuote]
readsPrec :: Int -> ReadS AcceptReservedInstancesExchangeQuote
$creadsPrec :: Int -> ReadS AcceptReservedInstancesExchangeQuote
Prelude.Read, Int -> AcceptReservedInstancesExchangeQuote -> ShowS
[AcceptReservedInstancesExchangeQuote] -> ShowS
AcceptReservedInstancesExchangeQuote -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptReservedInstancesExchangeQuote] -> ShowS
$cshowList :: [AcceptReservedInstancesExchangeQuote] -> ShowS
show :: AcceptReservedInstancesExchangeQuote -> String
$cshow :: AcceptReservedInstancesExchangeQuote -> String
showsPrec :: Int -> AcceptReservedInstancesExchangeQuote -> ShowS
$cshowsPrec :: Int -> AcceptReservedInstancesExchangeQuote -> ShowS
Prelude.Show, forall x.
Rep AcceptReservedInstancesExchangeQuote x
-> AcceptReservedInstancesExchangeQuote
forall x.
AcceptReservedInstancesExchangeQuote
-> Rep AcceptReservedInstancesExchangeQuote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AcceptReservedInstancesExchangeQuote x
-> AcceptReservedInstancesExchangeQuote
$cfrom :: forall x.
AcceptReservedInstancesExchangeQuote
-> Rep AcceptReservedInstancesExchangeQuote x
Prelude.Generic)

-- |
-- Create a value of 'AcceptReservedInstancesExchangeQuote' 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:
--
-- 'dryRun', 'acceptReservedInstancesExchangeQuote_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'targetConfigurations', 'acceptReservedInstancesExchangeQuote_targetConfigurations' - The configuration of the target Convertible Reserved Instance to
-- exchange for your current Convertible Reserved Instances.
--
-- 'reservedInstanceIds', 'acceptReservedInstancesExchangeQuote_reservedInstanceIds' - The IDs of the Convertible Reserved Instances to exchange for another
-- Convertible Reserved Instance of the same or higher value.
newAcceptReservedInstancesExchangeQuote ::
  AcceptReservedInstancesExchangeQuote
newAcceptReservedInstancesExchangeQuote :: AcceptReservedInstancesExchangeQuote
newAcceptReservedInstancesExchangeQuote =
  AcceptReservedInstancesExchangeQuote'
    { $sel:dryRun:AcceptReservedInstancesExchangeQuote' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:targetConfigurations:AcceptReservedInstancesExchangeQuote' :: Maybe [TargetConfigurationRequest]
targetConfigurations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:reservedInstanceIds:AcceptReservedInstancesExchangeQuote' :: [Text]
reservedInstanceIds = forall a. Monoid a => a
Prelude.mempty
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
acceptReservedInstancesExchangeQuote_dryRun :: Lens.Lens' AcceptReservedInstancesExchangeQuote (Prelude.Maybe Prelude.Bool)
acceptReservedInstancesExchangeQuote_dryRun :: Lens' AcceptReservedInstancesExchangeQuote (Maybe Bool)
acceptReservedInstancesExchangeQuote_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptReservedInstancesExchangeQuote' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: AcceptReservedInstancesExchangeQuote
s@AcceptReservedInstancesExchangeQuote' {} Maybe Bool
a -> AcceptReservedInstancesExchangeQuote
s {$sel:dryRun:AcceptReservedInstancesExchangeQuote' :: Maybe Bool
dryRun = Maybe Bool
a} :: AcceptReservedInstancesExchangeQuote)

-- | The configuration of the target Convertible Reserved Instance to
-- exchange for your current Convertible Reserved Instances.
acceptReservedInstancesExchangeQuote_targetConfigurations :: Lens.Lens' AcceptReservedInstancesExchangeQuote (Prelude.Maybe [TargetConfigurationRequest])
acceptReservedInstancesExchangeQuote_targetConfigurations :: Lens'
  AcceptReservedInstancesExchangeQuote
  (Maybe [TargetConfigurationRequest])
acceptReservedInstancesExchangeQuote_targetConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptReservedInstancesExchangeQuote' {Maybe [TargetConfigurationRequest]
targetConfigurations :: Maybe [TargetConfigurationRequest]
$sel:targetConfigurations:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote
-> Maybe [TargetConfigurationRequest]
targetConfigurations} -> Maybe [TargetConfigurationRequest]
targetConfigurations) (\s :: AcceptReservedInstancesExchangeQuote
s@AcceptReservedInstancesExchangeQuote' {} Maybe [TargetConfigurationRequest]
a -> AcceptReservedInstancesExchangeQuote
s {$sel:targetConfigurations:AcceptReservedInstancesExchangeQuote' :: Maybe [TargetConfigurationRequest]
targetConfigurations = Maybe [TargetConfigurationRequest]
a} :: AcceptReservedInstancesExchangeQuote) 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 IDs of the Convertible Reserved Instances to exchange for another
-- Convertible Reserved Instance of the same or higher value.
acceptReservedInstancesExchangeQuote_reservedInstanceIds :: Lens.Lens' AcceptReservedInstancesExchangeQuote [Prelude.Text]
acceptReservedInstancesExchangeQuote_reservedInstanceIds :: Lens' AcceptReservedInstancesExchangeQuote [Text]
acceptReservedInstancesExchangeQuote_reservedInstanceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptReservedInstancesExchangeQuote' {[Text]
reservedInstanceIds :: [Text]
$sel:reservedInstanceIds:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> [Text]
reservedInstanceIds} -> [Text]
reservedInstanceIds) (\s :: AcceptReservedInstancesExchangeQuote
s@AcceptReservedInstancesExchangeQuote' {} [Text]
a -> AcceptReservedInstancesExchangeQuote
s {$sel:reservedInstanceIds:AcceptReservedInstancesExchangeQuote' :: [Text]
reservedInstanceIds = [Text]
a} :: AcceptReservedInstancesExchangeQuote) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Core.AWSRequest
    AcceptReservedInstancesExchangeQuote
  where
  type
    AWSResponse AcceptReservedInstancesExchangeQuote =
      AcceptReservedInstancesExchangeQuoteResponse
  request :: (Service -> Service)
-> AcceptReservedInstancesExchangeQuote
-> Request AcceptReservedInstancesExchangeQuote
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AcceptReservedInstancesExchangeQuote
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse AcceptReservedInstancesExchangeQuote)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Int -> AcceptReservedInstancesExchangeQuoteResponse
AcceptReservedInstancesExchangeQuoteResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"exchangeId")
            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
    AcceptReservedInstancesExchangeQuote
  where
  hashWithSalt :: Int -> AcceptReservedInstancesExchangeQuote -> Int
hashWithSalt
    Int
_salt
    AcceptReservedInstancesExchangeQuote' {[Text]
Maybe Bool
Maybe [TargetConfigurationRequest]
reservedInstanceIds :: [Text]
targetConfigurations :: Maybe [TargetConfigurationRequest]
dryRun :: Maybe Bool
$sel:reservedInstanceIds:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> [Text]
$sel:targetConfigurations:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote
-> Maybe [TargetConfigurationRequest]
$sel:dryRun:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> Maybe Bool
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [TargetConfigurationRequest]
targetConfigurations
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
reservedInstanceIds

instance
  Prelude.NFData
    AcceptReservedInstancesExchangeQuote
  where
  rnf :: AcceptReservedInstancesExchangeQuote -> ()
rnf AcceptReservedInstancesExchangeQuote' {[Text]
Maybe Bool
Maybe [TargetConfigurationRequest]
reservedInstanceIds :: [Text]
targetConfigurations :: Maybe [TargetConfigurationRequest]
dryRun :: Maybe Bool
$sel:reservedInstanceIds:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> [Text]
$sel:targetConfigurations:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote
-> Maybe [TargetConfigurationRequest]
$sel:dryRun:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [TargetConfigurationRequest]
targetConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
reservedInstanceIds

instance
  Data.ToHeaders
    AcceptReservedInstancesExchangeQuote
  where
  toHeaders :: AcceptReservedInstancesExchangeQuote -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance
  Data.ToQuery
    AcceptReservedInstancesExchangeQuote
  where
  toQuery :: AcceptReservedInstancesExchangeQuote -> QueryString
toQuery AcceptReservedInstancesExchangeQuote' {[Text]
Maybe Bool
Maybe [TargetConfigurationRequest]
reservedInstanceIds :: [Text]
targetConfigurations :: Maybe [TargetConfigurationRequest]
dryRun :: Maybe Bool
$sel:reservedInstanceIds:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> [Text]
$sel:targetConfigurations:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote
-> Maybe [TargetConfigurationRequest]
$sel:dryRun:AcceptReservedInstancesExchangeQuote' :: AcceptReservedInstancesExchangeQuote -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"AcceptReservedInstancesExchangeQuote" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"TargetConfiguration"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TargetConfigurationRequest]
targetConfigurations
          ),
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList
          ByteString
"ReservedInstanceId"
          [Text]
reservedInstanceIds
      ]

-- | The result of the exchange and whether it was @successful@.
--
-- /See:/ 'newAcceptReservedInstancesExchangeQuoteResponse' smart constructor.
data AcceptReservedInstancesExchangeQuoteResponse = AcceptReservedInstancesExchangeQuoteResponse'
  { -- | The ID of the successful exchange.
    AcceptReservedInstancesExchangeQuoteResponse -> Maybe Text
exchangeId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    AcceptReservedInstancesExchangeQuoteResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AcceptReservedInstancesExchangeQuoteResponse
-> AcceptReservedInstancesExchangeQuoteResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptReservedInstancesExchangeQuoteResponse
-> AcceptReservedInstancesExchangeQuoteResponse -> Bool
$c/= :: AcceptReservedInstancesExchangeQuoteResponse
-> AcceptReservedInstancesExchangeQuoteResponse -> Bool
== :: AcceptReservedInstancesExchangeQuoteResponse
-> AcceptReservedInstancesExchangeQuoteResponse -> Bool
$c== :: AcceptReservedInstancesExchangeQuoteResponse
-> AcceptReservedInstancesExchangeQuoteResponse -> Bool
Prelude.Eq, ReadPrec [AcceptReservedInstancesExchangeQuoteResponse]
ReadPrec AcceptReservedInstancesExchangeQuoteResponse
Int -> ReadS AcceptReservedInstancesExchangeQuoteResponse
ReadS [AcceptReservedInstancesExchangeQuoteResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AcceptReservedInstancesExchangeQuoteResponse]
$creadListPrec :: ReadPrec [AcceptReservedInstancesExchangeQuoteResponse]
readPrec :: ReadPrec AcceptReservedInstancesExchangeQuoteResponse
$creadPrec :: ReadPrec AcceptReservedInstancesExchangeQuoteResponse
readList :: ReadS [AcceptReservedInstancesExchangeQuoteResponse]
$creadList :: ReadS [AcceptReservedInstancesExchangeQuoteResponse]
readsPrec :: Int -> ReadS AcceptReservedInstancesExchangeQuoteResponse
$creadsPrec :: Int -> ReadS AcceptReservedInstancesExchangeQuoteResponse
Prelude.Read, Int -> AcceptReservedInstancesExchangeQuoteResponse -> ShowS
[AcceptReservedInstancesExchangeQuoteResponse] -> ShowS
AcceptReservedInstancesExchangeQuoteResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptReservedInstancesExchangeQuoteResponse] -> ShowS
$cshowList :: [AcceptReservedInstancesExchangeQuoteResponse] -> ShowS
show :: AcceptReservedInstancesExchangeQuoteResponse -> String
$cshow :: AcceptReservedInstancesExchangeQuoteResponse -> String
showsPrec :: Int -> AcceptReservedInstancesExchangeQuoteResponse -> ShowS
$cshowsPrec :: Int -> AcceptReservedInstancesExchangeQuoteResponse -> ShowS
Prelude.Show, forall x.
Rep AcceptReservedInstancesExchangeQuoteResponse x
-> AcceptReservedInstancesExchangeQuoteResponse
forall x.
AcceptReservedInstancesExchangeQuoteResponse
-> Rep AcceptReservedInstancesExchangeQuoteResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AcceptReservedInstancesExchangeQuoteResponse x
-> AcceptReservedInstancesExchangeQuoteResponse
$cfrom :: forall x.
AcceptReservedInstancesExchangeQuoteResponse
-> Rep AcceptReservedInstancesExchangeQuoteResponse x
Prelude.Generic)

-- |
-- Create a value of 'AcceptReservedInstancesExchangeQuoteResponse' 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:
--
-- 'exchangeId', 'acceptReservedInstancesExchangeQuoteResponse_exchangeId' - The ID of the successful exchange.
--
-- 'httpStatus', 'acceptReservedInstancesExchangeQuoteResponse_httpStatus' - The response's http status code.
newAcceptReservedInstancesExchangeQuoteResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AcceptReservedInstancesExchangeQuoteResponse
newAcceptReservedInstancesExchangeQuoteResponse :: Int -> AcceptReservedInstancesExchangeQuoteResponse
newAcceptReservedInstancesExchangeQuoteResponse
  Int
pHttpStatus_ =
    AcceptReservedInstancesExchangeQuoteResponse'
      { $sel:exchangeId:AcceptReservedInstancesExchangeQuoteResponse' :: Maybe Text
exchangeId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:AcceptReservedInstancesExchangeQuoteResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The ID of the successful exchange.
acceptReservedInstancesExchangeQuoteResponse_exchangeId :: Lens.Lens' AcceptReservedInstancesExchangeQuoteResponse (Prelude.Maybe Prelude.Text)
acceptReservedInstancesExchangeQuoteResponse_exchangeId :: Lens' AcceptReservedInstancesExchangeQuoteResponse (Maybe Text)
acceptReservedInstancesExchangeQuoteResponse_exchangeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptReservedInstancesExchangeQuoteResponse' {Maybe Text
exchangeId :: Maybe Text
$sel:exchangeId:AcceptReservedInstancesExchangeQuoteResponse' :: AcceptReservedInstancesExchangeQuoteResponse -> Maybe Text
exchangeId} -> Maybe Text
exchangeId) (\s :: AcceptReservedInstancesExchangeQuoteResponse
s@AcceptReservedInstancesExchangeQuoteResponse' {} Maybe Text
a -> AcceptReservedInstancesExchangeQuoteResponse
s {$sel:exchangeId:AcceptReservedInstancesExchangeQuoteResponse' :: Maybe Text
exchangeId = Maybe Text
a} :: AcceptReservedInstancesExchangeQuoteResponse)

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

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