{-# 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.DescribeSpotPriceHistory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the Spot price history. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/using-spot-instances-history.html Spot Instance pricing history>
-- in the /Amazon EC2 User Guide for Linux Instances/.
--
-- When you specify a start and end time, the operation returns the prices
-- of the instance types within that time range. It also returns the last
-- price change before the start time, which is the effective price as of
-- the start time.
--
-- This operation returns paginated results.
module Amazonka.EC2.DescribeSpotPriceHistory
  ( -- * Creating a Request
    DescribeSpotPriceHistory (..),
    newDescribeSpotPriceHistory,

    -- * Request Lenses
    describeSpotPriceHistory_availabilityZone,
    describeSpotPriceHistory_dryRun,
    describeSpotPriceHistory_endTime,
    describeSpotPriceHistory_filters,
    describeSpotPriceHistory_instanceTypes,
    describeSpotPriceHistory_maxResults,
    describeSpotPriceHistory_nextToken,
    describeSpotPriceHistory_productDescriptions,
    describeSpotPriceHistory_startTime,

    -- * Destructuring the Response
    DescribeSpotPriceHistoryResponse (..),
    newDescribeSpotPriceHistoryResponse,

    -- * Response Lenses
    describeSpotPriceHistoryResponse_nextToken,
    describeSpotPriceHistoryResponse_spotPriceHistory,
    describeSpotPriceHistoryResponse_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 DescribeSpotPriceHistory.
--
-- /See:/ 'newDescribeSpotPriceHistory' smart constructor.
data DescribeSpotPriceHistory = DescribeSpotPriceHistory'
  { -- | Filters the results by the specified Availability Zone.
    DescribeSpotPriceHistory -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | 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@.
    DescribeSpotPriceHistory -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The date and time, up to the current date, from which to stop retrieving
    -- the price history data, in UTC format (for example,
    -- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z).
    DescribeSpotPriceHistory -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | One or more filters.
    --
    -- -   @availability-zone@ - The Availability Zone for which prices should
    --     be returned.
    --
    -- -   @instance-type@ - The type of instance (for example, @m3.medium@).
    --
    -- -   @product-description@ - The product description for the Spot price
    --     (@Linux\/UNIX@ | @Red Hat Enterprise Linux@ | @SUSE Linux@ |
    --     @Windows@ | @Linux\/UNIX (Amazon VPC)@ |
    --     @Red Hat Enterprise Linux (Amazon VPC)@ | @SUSE Linux (Amazon VPC)@
    --     | @Windows (Amazon VPC)@).
    --
    -- -   @spot-price@ - The Spot price. The value must match exactly (or use
    --     wildcards; greater than or less than comparison is not supported).
    --
    -- -   @timestamp@ - The time stamp of the Spot price history, in UTC
    --     format (for example, /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z). You can use
    --     wildcards (* and ?). Greater than or less than comparison is not
    --     supported.
    DescribeSpotPriceHistory -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | Filters the results by the specified instance types.
    DescribeSpotPriceHistory -> Maybe [InstanceType]
instanceTypes :: Prelude.Maybe [InstanceType],
    -- | The maximum number of results to return in a single call. Specify a
    -- value between 1 and 1000. The default value is 1000. To retrieve the
    -- remaining results, make another call with the returned @NextToken@
    -- value.
    DescribeSpotPriceHistory -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | The token for the next set of results.
    DescribeSpotPriceHistory -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Filters the results by the specified basic product descriptions.
    DescribeSpotPriceHistory -> Maybe [Text]
productDescriptions :: Prelude.Maybe [Prelude.Text],
    -- | The date and time, up to the past 90 days, from which to start
    -- retrieving the price history data, in UTC format (for example,
    -- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z).
    DescribeSpotPriceHistory -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601
  }
  deriving (DescribeSpotPriceHistory -> DescribeSpotPriceHistory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSpotPriceHistory -> DescribeSpotPriceHistory -> Bool
$c/= :: DescribeSpotPriceHistory -> DescribeSpotPriceHistory -> Bool
== :: DescribeSpotPriceHistory -> DescribeSpotPriceHistory -> Bool
$c== :: DescribeSpotPriceHistory -> DescribeSpotPriceHistory -> Bool
Prelude.Eq, ReadPrec [DescribeSpotPriceHistory]
ReadPrec DescribeSpotPriceHistory
Int -> ReadS DescribeSpotPriceHistory
ReadS [DescribeSpotPriceHistory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSpotPriceHistory]
$creadListPrec :: ReadPrec [DescribeSpotPriceHistory]
readPrec :: ReadPrec DescribeSpotPriceHistory
$creadPrec :: ReadPrec DescribeSpotPriceHistory
readList :: ReadS [DescribeSpotPriceHistory]
$creadList :: ReadS [DescribeSpotPriceHistory]
readsPrec :: Int -> ReadS DescribeSpotPriceHistory
$creadsPrec :: Int -> ReadS DescribeSpotPriceHistory
Prelude.Read, Int -> DescribeSpotPriceHistory -> ShowS
[DescribeSpotPriceHistory] -> ShowS
DescribeSpotPriceHistory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSpotPriceHistory] -> ShowS
$cshowList :: [DescribeSpotPriceHistory] -> ShowS
show :: DescribeSpotPriceHistory -> String
$cshow :: DescribeSpotPriceHistory -> String
showsPrec :: Int -> DescribeSpotPriceHistory -> ShowS
$cshowsPrec :: Int -> DescribeSpotPriceHistory -> ShowS
Prelude.Show, forall x.
Rep DescribeSpotPriceHistory x -> DescribeSpotPriceHistory
forall x.
DescribeSpotPriceHistory -> Rep DescribeSpotPriceHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSpotPriceHistory x -> DescribeSpotPriceHistory
$cfrom :: forall x.
DescribeSpotPriceHistory -> Rep DescribeSpotPriceHistory x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSpotPriceHistory' 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:
--
-- 'availabilityZone', 'describeSpotPriceHistory_availabilityZone' - Filters the results by the specified Availability Zone.
--
-- 'dryRun', 'describeSpotPriceHistory_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@.
--
-- 'endTime', 'describeSpotPriceHistory_endTime' - The date and time, up to the current date, from which to stop retrieving
-- the price history data, in UTC format (for example,
-- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z).
--
-- 'filters', 'describeSpotPriceHistory_filters' - One or more filters.
--
-- -   @availability-zone@ - The Availability Zone for which prices should
--     be returned.
--
-- -   @instance-type@ - The type of instance (for example, @m3.medium@).
--
-- -   @product-description@ - The product description for the Spot price
--     (@Linux\/UNIX@ | @Red Hat Enterprise Linux@ | @SUSE Linux@ |
--     @Windows@ | @Linux\/UNIX (Amazon VPC)@ |
--     @Red Hat Enterprise Linux (Amazon VPC)@ | @SUSE Linux (Amazon VPC)@
--     | @Windows (Amazon VPC)@).
--
-- -   @spot-price@ - The Spot price. The value must match exactly (or use
--     wildcards; greater than or less than comparison is not supported).
--
-- -   @timestamp@ - The time stamp of the Spot price history, in UTC
--     format (for example, /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z). You can use
--     wildcards (* and ?). Greater than or less than comparison is not
--     supported.
--
-- 'instanceTypes', 'describeSpotPriceHistory_instanceTypes' - Filters the results by the specified instance types.
--
-- 'maxResults', 'describeSpotPriceHistory_maxResults' - The maximum number of results to return in a single call. Specify a
-- value between 1 and 1000. The default value is 1000. To retrieve the
-- remaining results, make another call with the returned @NextToken@
-- value.
--
-- 'nextToken', 'describeSpotPriceHistory_nextToken' - The token for the next set of results.
--
-- 'productDescriptions', 'describeSpotPriceHistory_productDescriptions' - Filters the results by the specified basic product descriptions.
--
-- 'startTime', 'describeSpotPriceHistory_startTime' - The date and time, up to the past 90 days, from which to start
-- retrieving the price history data, in UTC format (for example,
-- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z).
newDescribeSpotPriceHistory ::
  DescribeSpotPriceHistory
newDescribeSpotPriceHistory :: DescribeSpotPriceHistory
newDescribeSpotPriceHistory =
  DescribeSpotPriceHistory'
    { $sel:availabilityZone:DescribeSpotPriceHistory' :: Maybe Text
availabilityZone =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:DescribeSpotPriceHistory' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:DescribeSpotPriceHistory' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:DescribeSpotPriceHistory' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceTypes:DescribeSpotPriceHistory' :: Maybe [InstanceType]
instanceTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeSpotPriceHistory' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeSpotPriceHistory' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:productDescriptions:DescribeSpotPriceHistory' :: Maybe [Text]
productDescriptions = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:DescribeSpotPriceHistory' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing
    }

-- | Filters the results by the specified Availability Zone.
describeSpotPriceHistory_availabilityZone :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe Prelude.Text)
describeSpotPriceHistory_availabilityZone :: Lens' DescribeSpotPriceHistory (Maybe Text)
describeSpotPriceHistory_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe Text
availabilityZone :: Maybe Text
$sel:availabilityZone:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
availabilityZone} -> Maybe Text
availabilityZone) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe Text
a -> DescribeSpotPriceHistory
s {$sel:availabilityZone:DescribeSpotPriceHistory' :: Maybe Text
availabilityZone = Maybe Text
a} :: DescribeSpotPriceHistory)

-- | 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@.
describeSpotPriceHistory_dryRun :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe Prelude.Bool)
describeSpotPriceHistory_dryRun :: Lens' DescribeSpotPriceHistory (Maybe Bool)
describeSpotPriceHistory_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe Bool
a -> DescribeSpotPriceHistory
s {$sel:dryRun:DescribeSpotPriceHistory' :: Maybe Bool
dryRun = Maybe Bool
a} :: DescribeSpotPriceHistory)

-- | The date and time, up to the current date, from which to stop retrieving
-- the price history data, in UTC format (for example,
-- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z).
describeSpotPriceHistory_endTime :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe Prelude.UTCTime)
describeSpotPriceHistory_endTime :: Lens' DescribeSpotPriceHistory (Maybe UTCTime)
describeSpotPriceHistory_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe ISO8601
a -> DescribeSpotPriceHistory
s {$sel:endTime:DescribeSpotPriceHistory' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: DescribeSpotPriceHistory) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | One or more filters.
--
-- -   @availability-zone@ - The Availability Zone for which prices should
--     be returned.
--
-- -   @instance-type@ - The type of instance (for example, @m3.medium@).
--
-- -   @product-description@ - The product description for the Spot price
--     (@Linux\/UNIX@ | @Red Hat Enterprise Linux@ | @SUSE Linux@ |
--     @Windows@ | @Linux\/UNIX (Amazon VPC)@ |
--     @Red Hat Enterprise Linux (Amazon VPC)@ | @SUSE Linux (Amazon VPC)@
--     | @Windows (Amazon VPC)@).
--
-- -   @spot-price@ - The Spot price. The value must match exactly (or use
--     wildcards; greater than or less than comparison is not supported).
--
-- -   @timestamp@ - The time stamp of the Spot price history, in UTC
--     format (for example, /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z). You can use
--     wildcards (* and ?). Greater than or less than comparison is not
--     supported.
describeSpotPriceHistory_filters :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe [Filter])
describeSpotPriceHistory_filters :: Lens' DescribeSpotPriceHistory (Maybe [Filter])
describeSpotPriceHistory_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe [Filter]
a -> DescribeSpotPriceHistory
s {$sel:filters:DescribeSpotPriceHistory' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: DescribeSpotPriceHistory) 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

-- | Filters the results by the specified instance types.
describeSpotPriceHistory_instanceTypes :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe [InstanceType])
describeSpotPriceHistory_instanceTypes :: Lens' DescribeSpotPriceHistory (Maybe [InstanceType])
describeSpotPriceHistory_instanceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe [InstanceType]
instanceTypes :: Maybe [InstanceType]
$sel:instanceTypes:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [InstanceType]
instanceTypes} -> Maybe [InstanceType]
instanceTypes) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe [InstanceType]
a -> DescribeSpotPriceHistory
s {$sel:instanceTypes:DescribeSpotPriceHistory' :: Maybe [InstanceType]
instanceTypes = Maybe [InstanceType]
a} :: DescribeSpotPriceHistory) 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 maximum number of results to return in a single call. Specify a
-- value between 1 and 1000. The default value is 1000. To retrieve the
-- remaining results, make another call with the returned @NextToken@
-- value.
describeSpotPriceHistory_maxResults :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe Prelude.Int)
describeSpotPriceHistory_maxResults :: Lens' DescribeSpotPriceHistory (Maybe Int)
describeSpotPriceHistory_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe Int
a -> DescribeSpotPriceHistory
s {$sel:maxResults:DescribeSpotPriceHistory' :: Maybe Int
maxResults = Maybe Int
a} :: DescribeSpotPriceHistory)

-- | The token for the next set of results.
describeSpotPriceHistory_nextToken :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe Prelude.Text)
describeSpotPriceHistory_nextToken :: Lens' DescribeSpotPriceHistory (Maybe Text)
describeSpotPriceHistory_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe Text
a -> DescribeSpotPriceHistory
s {$sel:nextToken:DescribeSpotPriceHistory' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeSpotPriceHistory)

-- | Filters the results by the specified basic product descriptions.
describeSpotPriceHistory_productDescriptions :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe [Prelude.Text])
describeSpotPriceHistory_productDescriptions :: Lens' DescribeSpotPriceHistory (Maybe [Text])
describeSpotPriceHistory_productDescriptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe [Text]
productDescriptions :: Maybe [Text]
$sel:productDescriptions:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Text]
productDescriptions} -> Maybe [Text]
productDescriptions) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe [Text]
a -> DescribeSpotPriceHistory
s {$sel:productDescriptions:DescribeSpotPriceHistory' :: Maybe [Text]
productDescriptions = Maybe [Text]
a} :: DescribeSpotPriceHistory) 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 date and time, up to the past 90 days, from which to start
-- retrieving the price history data, in UTC format (for example,
-- /YYYY/-/MM/-/DD/T/HH/:/MM/:/SS/Z).
describeSpotPriceHistory_startTime :: Lens.Lens' DescribeSpotPriceHistory (Prelude.Maybe Prelude.UTCTime)
describeSpotPriceHistory_startTime :: Lens' DescribeSpotPriceHistory (Maybe UTCTime)
describeSpotPriceHistory_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistory' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: DescribeSpotPriceHistory
s@DescribeSpotPriceHistory' {} Maybe ISO8601
a -> DescribeSpotPriceHistory
s {$sel:startTime:DescribeSpotPriceHistory' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: DescribeSpotPriceHistory) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Core.AWSPager DescribeSpotPriceHistory where
  page :: DescribeSpotPriceHistory
-> AWSResponse DescribeSpotPriceHistory
-> Maybe DescribeSpotPriceHistory
page DescribeSpotPriceHistory
rq AWSResponse DescribeSpotPriceHistory
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeSpotPriceHistory
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSpotPriceHistoryResponse (Maybe Text)
describeSpotPriceHistoryResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeSpotPriceHistory
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSpotPriceHistoryResponse (Maybe [SpotPrice])
describeSpotPriceHistoryResponse_spotPriceHistory
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeSpotPriceHistory
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeSpotPriceHistory (Maybe Text)
describeSpotPriceHistory_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeSpotPriceHistory
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSpotPriceHistoryResponse (Maybe Text)
describeSpotPriceHistoryResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest DescribeSpotPriceHistory where
  type
    AWSResponse DescribeSpotPriceHistory =
      DescribeSpotPriceHistoryResponse
  request :: (Service -> Service)
-> DescribeSpotPriceHistory -> Request DescribeSpotPriceHistory
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 DescribeSpotPriceHistory
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSpotPriceHistory)))
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
-> Maybe [SpotPrice] -> Int -> DescribeSpotPriceHistoryResponse
DescribeSpotPriceHistoryResponse'
            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
"nextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"spotPriceHistorySet"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                        )
            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 DescribeSpotPriceHistory where
  hashWithSalt :: Int -> DescribeSpotPriceHistory -> Int
hashWithSalt Int
_salt DescribeSpotPriceHistory' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [Filter]
Maybe [InstanceType]
Maybe Text
Maybe ISO8601
startTime :: Maybe ISO8601
productDescriptions :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Int
instanceTypes :: Maybe [InstanceType]
filters :: Maybe [Filter]
endTime :: Maybe ISO8601
dryRun :: Maybe Bool
availabilityZone :: Maybe Text
$sel:startTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
$sel:productDescriptions:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Text]
$sel:nextToken:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
$sel:maxResults:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Int
$sel:instanceTypes:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [InstanceType]
$sel:filters:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Filter]
$sel:endTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
$sel:dryRun:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Bool
$sel:availabilityZone:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InstanceType]
instanceTypes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
productDescriptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
startTime

instance Prelude.NFData DescribeSpotPriceHistory where
  rnf :: DescribeSpotPriceHistory -> ()
rnf DescribeSpotPriceHistory' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [Filter]
Maybe [InstanceType]
Maybe Text
Maybe ISO8601
startTime :: Maybe ISO8601
productDescriptions :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Int
instanceTypes :: Maybe [InstanceType]
filters :: Maybe [Filter]
endTime :: Maybe ISO8601
dryRun :: Maybe Bool
availabilityZone :: Maybe Text
$sel:startTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
$sel:productDescriptions:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Text]
$sel:nextToken:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
$sel:maxResults:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Int
$sel:instanceTypes:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [InstanceType]
$sel:filters:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Filter]
$sel:endTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
$sel:dryRun:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Bool
$sel:availabilityZone:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 ISO8601
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InstanceType]
instanceTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
productDescriptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
startTime

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

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

instance Data.ToQuery DescribeSpotPriceHistory where
  toQuery :: DescribeSpotPriceHistory -> QueryString
toQuery DescribeSpotPriceHistory' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [Filter]
Maybe [InstanceType]
Maybe Text
Maybe ISO8601
startTime :: Maybe ISO8601
productDescriptions :: Maybe [Text]
nextToken :: Maybe Text
maxResults :: Maybe Int
instanceTypes :: Maybe [InstanceType]
filters :: Maybe [Filter]
endTime :: Maybe ISO8601
dryRun :: Maybe Bool
availabilityZone :: Maybe Text
$sel:startTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
$sel:productDescriptions:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Text]
$sel:nextToken:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
$sel:maxResults:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Int
$sel:instanceTypes:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [InstanceType]
$sel:filters:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe [Filter]
$sel:endTime:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe ISO8601
$sel:dryRun:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Bool
$sel:availabilityZone:DescribeSpotPriceHistory' :: DescribeSpotPriceHistory -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeSpotPriceHistory" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"AvailabilityZone" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
availabilityZone,
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"EndTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
endTime,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Filter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"InstanceType"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [InstanceType]
instanceTypes
          ),
        ByteString
"MaxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxResults,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"ProductDescription"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
productDescriptions
          ),
        ByteString
"StartTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
startTime
      ]

-- | Contains the output of DescribeSpotPriceHistory.
--
-- /See:/ 'newDescribeSpotPriceHistoryResponse' smart constructor.
data DescribeSpotPriceHistoryResponse = DescribeSpotPriceHistoryResponse'
  { -- | The token required to retrieve the next set of results. This value is
    -- null or an empty string when there are no more results to return.
    DescribeSpotPriceHistoryResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The historical Spot prices.
    DescribeSpotPriceHistoryResponse -> Maybe [SpotPrice]
spotPriceHistory :: Prelude.Maybe [SpotPrice],
    -- | The response's http status code.
    DescribeSpotPriceHistoryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSpotPriceHistoryResponse
-> DescribeSpotPriceHistoryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSpotPriceHistoryResponse
-> DescribeSpotPriceHistoryResponse -> Bool
$c/= :: DescribeSpotPriceHistoryResponse
-> DescribeSpotPriceHistoryResponse -> Bool
== :: DescribeSpotPriceHistoryResponse
-> DescribeSpotPriceHistoryResponse -> Bool
$c== :: DescribeSpotPriceHistoryResponse
-> DescribeSpotPriceHistoryResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSpotPriceHistoryResponse]
ReadPrec DescribeSpotPriceHistoryResponse
Int -> ReadS DescribeSpotPriceHistoryResponse
ReadS [DescribeSpotPriceHistoryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSpotPriceHistoryResponse]
$creadListPrec :: ReadPrec [DescribeSpotPriceHistoryResponse]
readPrec :: ReadPrec DescribeSpotPriceHistoryResponse
$creadPrec :: ReadPrec DescribeSpotPriceHistoryResponse
readList :: ReadS [DescribeSpotPriceHistoryResponse]
$creadList :: ReadS [DescribeSpotPriceHistoryResponse]
readsPrec :: Int -> ReadS DescribeSpotPriceHistoryResponse
$creadsPrec :: Int -> ReadS DescribeSpotPriceHistoryResponse
Prelude.Read, Int -> DescribeSpotPriceHistoryResponse -> ShowS
[DescribeSpotPriceHistoryResponse] -> ShowS
DescribeSpotPriceHistoryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSpotPriceHistoryResponse] -> ShowS
$cshowList :: [DescribeSpotPriceHistoryResponse] -> ShowS
show :: DescribeSpotPriceHistoryResponse -> String
$cshow :: DescribeSpotPriceHistoryResponse -> String
showsPrec :: Int -> DescribeSpotPriceHistoryResponse -> ShowS
$cshowsPrec :: Int -> DescribeSpotPriceHistoryResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSpotPriceHistoryResponse x
-> DescribeSpotPriceHistoryResponse
forall x.
DescribeSpotPriceHistoryResponse
-> Rep DescribeSpotPriceHistoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSpotPriceHistoryResponse x
-> DescribeSpotPriceHistoryResponse
$cfrom :: forall x.
DescribeSpotPriceHistoryResponse
-> Rep DescribeSpotPriceHistoryResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSpotPriceHistoryResponse' 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:
--
-- 'nextToken', 'describeSpotPriceHistoryResponse_nextToken' - The token required to retrieve the next set of results. This value is
-- null or an empty string when there are no more results to return.
--
-- 'spotPriceHistory', 'describeSpotPriceHistoryResponse_spotPriceHistory' - The historical Spot prices.
--
-- 'httpStatus', 'describeSpotPriceHistoryResponse_httpStatus' - The response's http status code.
newDescribeSpotPriceHistoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSpotPriceHistoryResponse
newDescribeSpotPriceHistoryResponse :: Int -> DescribeSpotPriceHistoryResponse
newDescribeSpotPriceHistoryResponse Int
pHttpStatus_ =
  DescribeSpotPriceHistoryResponse'
    { $sel:nextToken:DescribeSpotPriceHistoryResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:spotPriceHistory:DescribeSpotPriceHistoryResponse' :: Maybe [SpotPrice]
spotPriceHistory = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSpotPriceHistoryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token required to retrieve the next set of results. This value is
-- null or an empty string when there are no more results to return.
describeSpotPriceHistoryResponse_nextToken :: Lens.Lens' DescribeSpotPriceHistoryResponse (Prelude.Maybe Prelude.Text)
describeSpotPriceHistoryResponse_nextToken :: Lens' DescribeSpotPriceHistoryResponse (Maybe Text)
describeSpotPriceHistoryResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistoryResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeSpotPriceHistoryResponse' :: DescribeSpotPriceHistoryResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeSpotPriceHistoryResponse
s@DescribeSpotPriceHistoryResponse' {} Maybe Text
a -> DescribeSpotPriceHistoryResponse
s {$sel:nextToken:DescribeSpotPriceHistoryResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeSpotPriceHistoryResponse)

-- | The historical Spot prices.
describeSpotPriceHistoryResponse_spotPriceHistory :: Lens.Lens' DescribeSpotPriceHistoryResponse (Prelude.Maybe [SpotPrice])
describeSpotPriceHistoryResponse_spotPriceHistory :: Lens' DescribeSpotPriceHistoryResponse (Maybe [SpotPrice])
describeSpotPriceHistoryResponse_spotPriceHistory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistoryResponse' {Maybe [SpotPrice]
spotPriceHistory :: Maybe [SpotPrice]
$sel:spotPriceHistory:DescribeSpotPriceHistoryResponse' :: DescribeSpotPriceHistoryResponse -> Maybe [SpotPrice]
spotPriceHistory} -> Maybe [SpotPrice]
spotPriceHistory) (\s :: DescribeSpotPriceHistoryResponse
s@DescribeSpotPriceHistoryResponse' {} Maybe [SpotPrice]
a -> DescribeSpotPriceHistoryResponse
s {$sel:spotPriceHistory:DescribeSpotPriceHistoryResponse' :: Maybe [SpotPrice]
spotPriceHistory = Maybe [SpotPrice]
a} :: DescribeSpotPriceHistoryResponse) 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 response's http status code.
describeSpotPriceHistoryResponse_httpStatus :: Lens.Lens' DescribeSpotPriceHistoryResponse Prelude.Int
describeSpotPriceHistoryResponse_httpStatus :: Lens' DescribeSpotPriceHistoryResponse Int
describeSpotPriceHistoryResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSpotPriceHistoryResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeSpotPriceHistoryResponse' :: DescribeSpotPriceHistoryResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeSpotPriceHistoryResponse
s@DescribeSpotPriceHistoryResponse' {} Int
a -> DescribeSpotPriceHistoryResponse
s {$sel:httpStatus:DescribeSpotPriceHistoryResponse' :: Int
httpStatus = Int
a} :: DescribeSpotPriceHistoryResponse)

instance
  Prelude.NFData
    DescribeSpotPriceHistoryResponse
  where
  rnf :: DescribeSpotPriceHistoryResponse -> ()
rnf DescribeSpotPriceHistoryResponse' {Int
Maybe [SpotPrice]
Maybe Text
httpStatus :: Int
spotPriceHistory :: Maybe [SpotPrice]
nextToken :: Maybe Text
$sel:httpStatus:DescribeSpotPriceHistoryResponse' :: DescribeSpotPriceHistoryResponse -> Int
$sel:spotPriceHistory:DescribeSpotPriceHistoryResponse' :: DescribeSpotPriceHistoryResponse -> Maybe [SpotPrice]
$sel:nextToken:DescribeSpotPriceHistoryResponse' :: DescribeSpotPriceHistoryResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SpotPrice]
spotPriceHistory
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus