{-# 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.CostExplorer.GetCostForecast
-- 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 a forecast for how much Amazon Web Services predicts that you
-- will spend over the forecast time period that you select, based on your
-- past costs.
module Amazonka.CostExplorer.GetCostForecast
  ( -- * Creating a Request
    GetCostForecast (..),
    newGetCostForecast,

    -- * Request Lenses
    getCostForecast_filter,
    getCostForecast_predictionIntervalLevel,
    getCostForecast_timePeriod,
    getCostForecast_metric,
    getCostForecast_granularity,

    -- * Destructuring the Response
    GetCostForecastResponse (..),
    newGetCostForecastResponse,

    -- * Response Lenses
    getCostForecastResponse_forecastResultsByTime,
    getCostForecastResponse_total,
    getCostForecastResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CostExplorer.Types
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:/ 'newGetCostForecast' smart constructor.
data GetCostForecast = GetCostForecast'
  { -- | The filters that you want to use to filter your forecast. The
    -- @GetCostForecast@ API supports filtering by the following dimensions:
    --
    -- -   @AZ@
    --
    -- -   @INSTANCE_TYPE@
    --
    -- -   @LINKED_ACCOUNT@
    --
    -- -   @LINKED_ACCOUNT_NAME@
    --
    -- -   @OPERATION@
    --
    -- -   @PURCHASE_TYPE@
    --
    -- -   @REGION@
    --
    -- -   @SERVICE@
    --
    -- -   @USAGE_TYPE@
    --
    -- -   @USAGE_TYPE_GROUP@
    --
    -- -   @RECORD_TYPE@
    --
    -- -   @OPERATING_SYSTEM@
    --
    -- -   @TENANCY@
    --
    -- -   @SCOPE@
    --
    -- -   @PLATFORM@
    --
    -- -   @SUBSCRIPTION_ID@
    --
    -- -   @LEGAL_ENTITY_NAME@
    --
    -- -   @DEPLOYMENT_OPTION@
    --
    -- -   @DATABASE_ENGINE@
    --
    -- -   @INSTANCE_TYPE_FAMILY@
    --
    -- -   @BILLING_ENTITY@
    --
    -- -   @RESERVATION_ID@
    --
    -- -   @SAVINGS_PLAN_ARN@
    GetCostForecast -> Maybe Expression
filter' :: Prelude.Maybe Expression,
    -- | Cost Explorer always returns the mean forecast as a single point. You
    -- can request a prediction interval around the mean by specifying a
    -- confidence level. The higher the confidence level, the more confident
    -- Cost Explorer is about the actual value falling in the prediction
    -- interval. Higher confidence levels result in wider prediction intervals.
    GetCostForecast -> Maybe Natural
predictionIntervalLevel :: Prelude.Maybe Prelude.Natural,
    -- | The period of time that you want the forecast to cover. The start date
    -- must be equal to or no later than the current date to avoid a validation
    -- error.
    GetCostForecast -> DateInterval
timePeriod :: DateInterval,
    -- | Which metric Cost Explorer uses to create your forecast. For more
    -- information about blended and unblended rates, see
    -- <http://aws.amazon.com/premiumsupport/knowledge-center/blended-rates-intro/ Why does the \"blended\" annotation appear on some line items in my bill?>.
    --
    -- Valid values for a @GetCostForecast@ call are the following:
    --
    -- -   AMORTIZED_COST
    --
    -- -   BLENDED_COST
    --
    -- -   NET_AMORTIZED_COST
    --
    -- -   NET_UNBLENDED_COST
    --
    -- -   UNBLENDED_COST
    GetCostForecast -> Metric
metric :: Metric,
    -- | How granular you want the forecast to be. You can get 3 months of
    -- @DAILY@ forecasts or 12 months of @MONTHLY@ forecasts.
    --
    -- The @GetCostForecast@ operation supports only @DAILY@ and @MONTHLY@
    -- granularities.
    GetCostForecast -> Granularity
granularity :: Granularity
  }
  deriving (GetCostForecast -> GetCostForecast -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCostForecast -> GetCostForecast -> Bool
$c/= :: GetCostForecast -> GetCostForecast -> Bool
== :: GetCostForecast -> GetCostForecast -> Bool
$c== :: GetCostForecast -> GetCostForecast -> Bool
Prelude.Eq, ReadPrec [GetCostForecast]
ReadPrec GetCostForecast
Int -> ReadS GetCostForecast
ReadS [GetCostForecast]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCostForecast]
$creadListPrec :: ReadPrec [GetCostForecast]
readPrec :: ReadPrec GetCostForecast
$creadPrec :: ReadPrec GetCostForecast
readList :: ReadS [GetCostForecast]
$creadList :: ReadS [GetCostForecast]
readsPrec :: Int -> ReadS GetCostForecast
$creadsPrec :: Int -> ReadS GetCostForecast
Prelude.Read, Int -> GetCostForecast -> ShowS
[GetCostForecast] -> ShowS
GetCostForecast -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCostForecast] -> ShowS
$cshowList :: [GetCostForecast] -> ShowS
show :: GetCostForecast -> String
$cshow :: GetCostForecast -> String
showsPrec :: Int -> GetCostForecast -> ShowS
$cshowsPrec :: Int -> GetCostForecast -> ShowS
Prelude.Show, forall x. Rep GetCostForecast x -> GetCostForecast
forall x. GetCostForecast -> Rep GetCostForecast x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCostForecast x -> GetCostForecast
$cfrom :: forall x. GetCostForecast -> Rep GetCostForecast x
Prelude.Generic)

-- |
-- Create a value of 'GetCostForecast' 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:
--
-- 'filter'', 'getCostForecast_filter' - The filters that you want to use to filter your forecast. The
-- @GetCostForecast@ API supports filtering by the following dimensions:
--
-- -   @AZ@
--
-- -   @INSTANCE_TYPE@
--
-- -   @LINKED_ACCOUNT@
--
-- -   @LINKED_ACCOUNT_NAME@
--
-- -   @OPERATION@
--
-- -   @PURCHASE_TYPE@
--
-- -   @REGION@
--
-- -   @SERVICE@
--
-- -   @USAGE_TYPE@
--
-- -   @USAGE_TYPE_GROUP@
--
-- -   @RECORD_TYPE@
--
-- -   @OPERATING_SYSTEM@
--
-- -   @TENANCY@
--
-- -   @SCOPE@
--
-- -   @PLATFORM@
--
-- -   @SUBSCRIPTION_ID@
--
-- -   @LEGAL_ENTITY_NAME@
--
-- -   @DEPLOYMENT_OPTION@
--
-- -   @DATABASE_ENGINE@
--
-- -   @INSTANCE_TYPE_FAMILY@
--
-- -   @BILLING_ENTITY@
--
-- -   @RESERVATION_ID@
--
-- -   @SAVINGS_PLAN_ARN@
--
-- 'predictionIntervalLevel', 'getCostForecast_predictionIntervalLevel' - Cost Explorer always returns the mean forecast as a single point. You
-- can request a prediction interval around the mean by specifying a
-- confidence level. The higher the confidence level, the more confident
-- Cost Explorer is about the actual value falling in the prediction
-- interval. Higher confidence levels result in wider prediction intervals.
--
-- 'timePeriod', 'getCostForecast_timePeriod' - The period of time that you want the forecast to cover. The start date
-- must be equal to or no later than the current date to avoid a validation
-- error.
--
-- 'metric', 'getCostForecast_metric' - Which metric Cost Explorer uses to create your forecast. For more
-- information about blended and unblended rates, see
-- <http://aws.amazon.com/premiumsupport/knowledge-center/blended-rates-intro/ Why does the \"blended\" annotation appear on some line items in my bill?>.
--
-- Valid values for a @GetCostForecast@ call are the following:
--
-- -   AMORTIZED_COST
--
-- -   BLENDED_COST
--
-- -   NET_AMORTIZED_COST
--
-- -   NET_UNBLENDED_COST
--
-- -   UNBLENDED_COST
--
-- 'granularity', 'getCostForecast_granularity' - How granular you want the forecast to be. You can get 3 months of
-- @DAILY@ forecasts or 12 months of @MONTHLY@ forecasts.
--
-- The @GetCostForecast@ operation supports only @DAILY@ and @MONTHLY@
-- granularities.
newGetCostForecast ::
  -- | 'timePeriod'
  DateInterval ->
  -- | 'metric'
  Metric ->
  -- | 'granularity'
  Granularity ->
  GetCostForecast
newGetCostForecast :: DateInterval -> Metric -> Granularity -> GetCostForecast
newGetCostForecast
  DateInterval
pTimePeriod_
  Metric
pMetric_
  Granularity
pGranularity_ =
    GetCostForecast'
      { $sel:filter':GetCostForecast' :: Maybe Expression
filter' = forall a. Maybe a
Prelude.Nothing,
        $sel:predictionIntervalLevel:GetCostForecast' :: Maybe Natural
predictionIntervalLevel = forall a. Maybe a
Prelude.Nothing,
        $sel:timePeriod:GetCostForecast' :: DateInterval
timePeriod = DateInterval
pTimePeriod_,
        $sel:metric:GetCostForecast' :: Metric
metric = Metric
pMetric_,
        $sel:granularity:GetCostForecast' :: Granularity
granularity = Granularity
pGranularity_
      }

-- | The filters that you want to use to filter your forecast. The
-- @GetCostForecast@ API supports filtering by the following dimensions:
--
-- -   @AZ@
--
-- -   @INSTANCE_TYPE@
--
-- -   @LINKED_ACCOUNT@
--
-- -   @LINKED_ACCOUNT_NAME@
--
-- -   @OPERATION@
--
-- -   @PURCHASE_TYPE@
--
-- -   @REGION@
--
-- -   @SERVICE@
--
-- -   @USAGE_TYPE@
--
-- -   @USAGE_TYPE_GROUP@
--
-- -   @RECORD_TYPE@
--
-- -   @OPERATING_SYSTEM@
--
-- -   @TENANCY@
--
-- -   @SCOPE@
--
-- -   @PLATFORM@
--
-- -   @SUBSCRIPTION_ID@
--
-- -   @LEGAL_ENTITY_NAME@
--
-- -   @DEPLOYMENT_OPTION@
--
-- -   @DATABASE_ENGINE@
--
-- -   @INSTANCE_TYPE_FAMILY@
--
-- -   @BILLING_ENTITY@
--
-- -   @RESERVATION_ID@
--
-- -   @SAVINGS_PLAN_ARN@
getCostForecast_filter :: Lens.Lens' GetCostForecast (Prelude.Maybe Expression)
getCostForecast_filter :: Lens' GetCostForecast (Maybe Expression)
getCostForecast_filter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecast' {Maybe Expression
filter' :: Maybe Expression
$sel:filter':GetCostForecast' :: GetCostForecast -> Maybe Expression
filter'} -> Maybe Expression
filter') (\s :: GetCostForecast
s@GetCostForecast' {} Maybe Expression
a -> GetCostForecast
s {$sel:filter':GetCostForecast' :: Maybe Expression
filter' = Maybe Expression
a} :: GetCostForecast)

-- | Cost Explorer always returns the mean forecast as a single point. You
-- can request a prediction interval around the mean by specifying a
-- confidence level. The higher the confidence level, the more confident
-- Cost Explorer is about the actual value falling in the prediction
-- interval. Higher confidence levels result in wider prediction intervals.
getCostForecast_predictionIntervalLevel :: Lens.Lens' GetCostForecast (Prelude.Maybe Prelude.Natural)
getCostForecast_predictionIntervalLevel :: Lens' GetCostForecast (Maybe Natural)
getCostForecast_predictionIntervalLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecast' {Maybe Natural
predictionIntervalLevel :: Maybe Natural
$sel:predictionIntervalLevel:GetCostForecast' :: GetCostForecast -> Maybe Natural
predictionIntervalLevel} -> Maybe Natural
predictionIntervalLevel) (\s :: GetCostForecast
s@GetCostForecast' {} Maybe Natural
a -> GetCostForecast
s {$sel:predictionIntervalLevel:GetCostForecast' :: Maybe Natural
predictionIntervalLevel = Maybe Natural
a} :: GetCostForecast)

-- | The period of time that you want the forecast to cover. The start date
-- must be equal to or no later than the current date to avoid a validation
-- error.
getCostForecast_timePeriod :: Lens.Lens' GetCostForecast DateInterval
getCostForecast_timePeriod :: Lens' GetCostForecast DateInterval
getCostForecast_timePeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecast' {DateInterval
timePeriod :: DateInterval
$sel:timePeriod:GetCostForecast' :: GetCostForecast -> DateInterval
timePeriod} -> DateInterval
timePeriod) (\s :: GetCostForecast
s@GetCostForecast' {} DateInterval
a -> GetCostForecast
s {$sel:timePeriod:GetCostForecast' :: DateInterval
timePeriod = DateInterval
a} :: GetCostForecast)

-- | Which metric Cost Explorer uses to create your forecast. For more
-- information about blended and unblended rates, see
-- <http://aws.amazon.com/premiumsupport/knowledge-center/blended-rates-intro/ Why does the \"blended\" annotation appear on some line items in my bill?>.
--
-- Valid values for a @GetCostForecast@ call are the following:
--
-- -   AMORTIZED_COST
--
-- -   BLENDED_COST
--
-- -   NET_AMORTIZED_COST
--
-- -   NET_UNBLENDED_COST
--
-- -   UNBLENDED_COST
getCostForecast_metric :: Lens.Lens' GetCostForecast Metric
getCostForecast_metric :: Lens' GetCostForecast Metric
getCostForecast_metric = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecast' {Metric
metric :: Metric
$sel:metric:GetCostForecast' :: GetCostForecast -> Metric
metric} -> Metric
metric) (\s :: GetCostForecast
s@GetCostForecast' {} Metric
a -> GetCostForecast
s {$sel:metric:GetCostForecast' :: Metric
metric = Metric
a} :: GetCostForecast)

-- | How granular you want the forecast to be. You can get 3 months of
-- @DAILY@ forecasts or 12 months of @MONTHLY@ forecasts.
--
-- The @GetCostForecast@ operation supports only @DAILY@ and @MONTHLY@
-- granularities.
getCostForecast_granularity :: Lens.Lens' GetCostForecast Granularity
getCostForecast_granularity :: Lens' GetCostForecast Granularity
getCostForecast_granularity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecast' {Granularity
granularity :: Granularity
$sel:granularity:GetCostForecast' :: GetCostForecast -> Granularity
granularity} -> Granularity
granularity) (\s :: GetCostForecast
s@GetCostForecast' {} Granularity
a -> GetCostForecast
s {$sel:granularity:GetCostForecast' :: Granularity
granularity = Granularity
a} :: GetCostForecast)

instance Core.AWSRequest GetCostForecast where
  type
    AWSResponse GetCostForecast =
      GetCostForecastResponse
  request :: (Service -> Service) -> GetCostForecast -> Request GetCostForecast
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 GetCostForecast
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCostForecast)))
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 [ForecastResult]
-> Maybe MetricValue -> Int -> GetCostForecastResponse
GetCostForecastResponse'
            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
"ForecastResultsByTime"
                            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
"Total")
            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 GetCostForecast where
  hashWithSalt :: Int -> GetCostForecast -> Int
hashWithSalt Int
_salt GetCostForecast' {Maybe Natural
Maybe Expression
DateInterval
Granularity
Metric
granularity :: Granularity
metric :: Metric
timePeriod :: DateInterval
predictionIntervalLevel :: Maybe Natural
filter' :: Maybe Expression
$sel:granularity:GetCostForecast' :: GetCostForecast -> Granularity
$sel:metric:GetCostForecast' :: GetCostForecast -> Metric
$sel:timePeriod:GetCostForecast' :: GetCostForecast -> DateInterval
$sel:predictionIntervalLevel:GetCostForecast' :: GetCostForecast -> Maybe Natural
$sel:filter':GetCostForecast' :: GetCostForecast -> Maybe Expression
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Expression
filter'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
predictionIntervalLevel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DateInterval
timePeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Metric
metric
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Granularity
granularity

instance Prelude.NFData GetCostForecast where
  rnf :: GetCostForecast -> ()
rnf GetCostForecast' {Maybe Natural
Maybe Expression
DateInterval
Granularity
Metric
granularity :: Granularity
metric :: Metric
timePeriod :: DateInterval
predictionIntervalLevel :: Maybe Natural
filter' :: Maybe Expression
$sel:granularity:GetCostForecast' :: GetCostForecast -> Granularity
$sel:metric:GetCostForecast' :: GetCostForecast -> Metric
$sel:timePeriod:GetCostForecast' :: GetCostForecast -> DateInterval
$sel:predictionIntervalLevel:GetCostForecast' :: GetCostForecast -> Maybe Natural
$sel:filter':GetCostForecast' :: GetCostForecast -> Maybe Expression
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Expression
filter'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
predictionIntervalLevel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DateInterval
timePeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Metric
metric
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Granularity
granularity

instance Data.ToHeaders GetCostForecast where
  toHeaders :: GetCostForecast -> 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
"AWSInsightsIndexService.GetCostForecast" ::
                          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 GetCostForecast where
  toJSON :: GetCostForecast -> Value
toJSON GetCostForecast' {Maybe Natural
Maybe Expression
DateInterval
Granularity
Metric
granularity :: Granularity
metric :: Metric
timePeriod :: DateInterval
predictionIntervalLevel :: Maybe Natural
filter' :: Maybe Expression
$sel:granularity:GetCostForecast' :: GetCostForecast -> Granularity
$sel:metric:GetCostForecast' :: GetCostForecast -> Metric
$sel:timePeriod:GetCostForecast' :: GetCostForecast -> DateInterval
$sel:predictionIntervalLevel:GetCostForecast' :: GetCostForecast -> Maybe Natural
$sel:filter':GetCostForecast' :: GetCostForecast -> Maybe Expression
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filter" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Expression
filter',
            (Key
"PredictionIntervalLevel" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
predictionIntervalLevel,
            forall a. a -> Maybe a
Prelude.Just (Key
"TimePeriod" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= DateInterval
timePeriod),
            forall a. a -> Maybe a
Prelude.Just (Key
"Metric" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Metric
metric),
            forall a. a -> Maybe a
Prelude.Just (Key
"Granularity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Granularity
granularity)
          ]
      )

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

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

-- | /See:/ 'newGetCostForecastResponse' smart constructor.
data GetCostForecastResponse = GetCostForecastResponse'
  { -- | The forecasts for your query, in order. For @DAILY@ forecasts, this is a
    -- list of days. For @MONTHLY@ forecasts, this is a list of months.
    GetCostForecastResponse -> Maybe [ForecastResult]
forecastResultsByTime :: Prelude.Maybe [ForecastResult],
    -- | How much you are forecasted to spend over the forecast period, in @USD@.
    GetCostForecastResponse -> Maybe MetricValue
total :: Prelude.Maybe MetricValue,
    -- | The response's http status code.
    GetCostForecastResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCostForecastResponse -> GetCostForecastResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCostForecastResponse -> GetCostForecastResponse -> Bool
$c/= :: GetCostForecastResponse -> GetCostForecastResponse -> Bool
== :: GetCostForecastResponse -> GetCostForecastResponse -> Bool
$c== :: GetCostForecastResponse -> GetCostForecastResponse -> Bool
Prelude.Eq, ReadPrec [GetCostForecastResponse]
ReadPrec GetCostForecastResponse
Int -> ReadS GetCostForecastResponse
ReadS [GetCostForecastResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCostForecastResponse]
$creadListPrec :: ReadPrec [GetCostForecastResponse]
readPrec :: ReadPrec GetCostForecastResponse
$creadPrec :: ReadPrec GetCostForecastResponse
readList :: ReadS [GetCostForecastResponse]
$creadList :: ReadS [GetCostForecastResponse]
readsPrec :: Int -> ReadS GetCostForecastResponse
$creadsPrec :: Int -> ReadS GetCostForecastResponse
Prelude.Read, Int -> GetCostForecastResponse -> ShowS
[GetCostForecastResponse] -> ShowS
GetCostForecastResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCostForecastResponse] -> ShowS
$cshowList :: [GetCostForecastResponse] -> ShowS
show :: GetCostForecastResponse -> String
$cshow :: GetCostForecastResponse -> String
showsPrec :: Int -> GetCostForecastResponse -> ShowS
$cshowsPrec :: Int -> GetCostForecastResponse -> ShowS
Prelude.Show, forall x. Rep GetCostForecastResponse x -> GetCostForecastResponse
forall x. GetCostForecastResponse -> Rep GetCostForecastResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCostForecastResponse x -> GetCostForecastResponse
$cfrom :: forall x. GetCostForecastResponse -> Rep GetCostForecastResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCostForecastResponse' 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:
--
-- 'forecastResultsByTime', 'getCostForecastResponse_forecastResultsByTime' - The forecasts for your query, in order. For @DAILY@ forecasts, this is a
-- list of days. For @MONTHLY@ forecasts, this is a list of months.
--
-- 'total', 'getCostForecastResponse_total' - How much you are forecasted to spend over the forecast period, in @USD@.
--
-- 'httpStatus', 'getCostForecastResponse_httpStatus' - The response's http status code.
newGetCostForecastResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCostForecastResponse
newGetCostForecastResponse :: Int -> GetCostForecastResponse
newGetCostForecastResponse Int
pHttpStatus_ =
  GetCostForecastResponse'
    { $sel:forecastResultsByTime:GetCostForecastResponse' :: Maybe [ForecastResult]
forecastResultsByTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:total:GetCostForecastResponse' :: Maybe MetricValue
total = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCostForecastResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The forecasts for your query, in order. For @DAILY@ forecasts, this is a
-- list of days. For @MONTHLY@ forecasts, this is a list of months.
getCostForecastResponse_forecastResultsByTime :: Lens.Lens' GetCostForecastResponse (Prelude.Maybe [ForecastResult])
getCostForecastResponse_forecastResultsByTime :: Lens' GetCostForecastResponse (Maybe [ForecastResult])
getCostForecastResponse_forecastResultsByTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecastResponse' {Maybe [ForecastResult]
forecastResultsByTime :: Maybe [ForecastResult]
$sel:forecastResultsByTime:GetCostForecastResponse' :: GetCostForecastResponse -> Maybe [ForecastResult]
forecastResultsByTime} -> Maybe [ForecastResult]
forecastResultsByTime) (\s :: GetCostForecastResponse
s@GetCostForecastResponse' {} Maybe [ForecastResult]
a -> GetCostForecastResponse
s {$sel:forecastResultsByTime:GetCostForecastResponse' :: Maybe [ForecastResult]
forecastResultsByTime = Maybe [ForecastResult]
a} :: GetCostForecastResponse) 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

-- | How much you are forecasted to spend over the forecast period, in @USD@.
getCostForecastResponse_total :: Lens.Lens' GetCostForecastResponse (Prelude.Maybe MetricValue)
getCostForecastResponse_total :: Lens' GetCostForecastResponse (Maybe MetricValue)
getCostForecastResponse_total = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCostForecastResponse' {Maybe MetricValue
total :: Maybe MetricValue
$sel:total:GetCostForecastResponse' :: GetCostForecastResponse -> Maybe MetricValue
total} -> Maybe MetricValue
total) (\s :: GetCostForecastResponse
s@GetCostForecastResponse' {} Maybe MetricValue
a -> GetCostForecastResponse
s {$sel:total:GetCostForecastResponse' :: Maybe MetricValue
total = Maybe MetricValue
a} :: GetCostForecastResponse)

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

instance Prelude.NFData GetCostForecastResponse where
  rnf :: GetCostForecastResponse -> ()
rnf GetCostForecastResponse' {Int
Maybe [ForecastResult]
Maybe MetricValue
httpStatus :: Int
total :: Maybe MetricValue
forecastResultsByTime :: Maybe [ForecastResult]
$sel:httpStatus:GetCostForecastResponse' :: GetCostForecastResponse -> Int
$sel:total:GetCostForecastResponse' :: GetCostForecastResponse -> Maybe MetricValue
$sel:forecastResultsByTime:GetCostForecastResponse' :: GetCostForecastResponse -> Maybe [ForecastResult]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ForecastResult]
forecastResultsByTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MetricValue
total
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus