{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.SavingsPlansUtilizationAggregates
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CostExplorer.Types.SavingsPlansUtilizationAggregates where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import Amazonka.CostExplorer.Types.SavingsPlansAmortizedCommitment
import Amazonka.CostExplorer.Types.SavingsPlansSavings
import Amazonka.CostExplorer.Types.SavingsPlansUtilization
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The aggregated utilization metrics for your Savings Plans usage.
--
-- /See:/ 'newSavingsPlansUtilizationAggregates' smart constructor.
data SavingsPlansUtilizationAggregates = SavingsPlansUtilizationAggregates'
  { -- | The total amortized commitment for a Savings Plans. This includes the
    -- sum of the upfront and recurring Savings Plans fees.
    SavingsPlansUtilizationAggregates
-> Maybe SavingsPlansAmortizedCommitment
amortizedCommitment :: Prelude.Maybe SavingsPlansAmortizedCommitment,
    -- | The amount that\'s saved by using existing Savings Plans. Savings
    -- returns both net savings from Savings Plans and also the
    -- @onDemandCostEquivalent@ of the Savings Plans when considering the
    -- utilization rate.
    SavingsPlansUtilizationAggregates -> Maybe SavingsPlansSavings
savings :: Prelude.Maybe SavingsPlansSavings,
    -- | A ratio of your effectiveness of using existing Savings Plans to apply
    -- to workloads that are Savings Plans eligible.
    SavingsPlansUtilizationAggregates -> SavingsPlansUtilization
utilization :: SavingsPlansUtilization
  }
  deriving (SavingsPlansUtilizationAggregates
-> SavingsPlansUtilizationAggregates -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SavingsPlansUtilizationAggregates
-> SavingsPlansUtilizationAggregates -> Bool
$c/= :: SavingsPlansUtilizationAggregates
-> SavingsPlansUtilizationAggregates -> Bool
== :: SavingsPlansUtilizationAggregates
-> SavingsPlansUtilizationAggregates -> Bool
$c== :: SavingsPlansUtilizationAggregates
-> SavingsPlansUtilizationAggregates -> Bool
Prelude.Eq, ReadPrec [SavingsPlansUtilizationAggregates]
ReadPrec SavingsPlansUtilizationAggregates
Int -> ReadS SavingsPlansUtilizationAggregates
ReadS [SavingsPlansUtilizationAggregates]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SavingsPlansUtilizationAggregates]
$creadListPrec :: ReadPrec [SavingsPlansUtilizationAggregates]
readPrec :: ReadPrec SavingsPlansUtilizationAggregates
$creadPrec :: ReadPrec SavingsPlansUtilizationAggregates
readList :: ReadS [SavingsPlansUtilizationAggregates]
$creadList :: ReadS [SavingsPlansUtilizationAggregates]
readsPrec :: Int -> ReadS SavingsPlansUtilizationAggregates
$creadsPrec :: Int -> ReadS SavingsPlansUtilizationAggregates
Prelude.Read, Int -> SavingsPlansUtilizationAggregates -> ShowS
[SavingsPlansUtilizationAggregates] -> ShowS
SavingsPlansUtilizationAggregates -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SavingsPlansUtilizationAggregates] -> ShowS
$cshowList :: [SavingsPlansUtilizationAggregates] -> ShowS
show :: SavingsPlansUtilizationAggregates -> String
$cshow :: SavingsPlansUtilizationAggregates -> String
showsPrec :: Int -> SavingsPlansUtilizationAggregates -> ShowS
$cshowsPrec :: Int -> SavingsPlansUtilizationAggregates -> ShowS
Prelude.Show, forall x.
Rep SavingsPlansUtilizationAggregates x
-> SavingsPlansUtilizationAggregates
forall x.
SavingsPlansUtilizationAggregates
-> Rep SavingsPlansUtilizationAggregates x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SavingsPlansUtilizationAggregates x
-> SavingsPlansUtilizationAggregates
$cfrom :: forall x.
SavingsPlansUtilizationAggregates
-> Rep SavingsPlansUtilizationAggregates x
Prelude.Generic)

-- |
-- Create a value of 'SavingsPlansUtilizationAggregates' 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:
--
-- 'amortizedCommitment', 'savingsPlansUtilizationAggregates_amortizedCommitment' - The total amortized commitment for a Savings Plans. This includes the
-- sum of the upfront and recurring Savings Plans fees.
--
-- 'savings', 'savingsPlansUtilizationAggregates_savings' - The amount that\'s saved by using existing Savings Plans. Savings
-- returns both net savings from Savings Plans and also the
-- @onDemandCostEquivalent@ of the Savings Plans when considering the
-- utilization rate.
--
-- 'utilization', 'savingsPlansUtilizationAggregates_utilization' - A ratio of your effectiveness of using existing Savings Plans to apply
-- to workloads that are Savings Plans eligible.
newSavingsPlansUtilizationAggregates ::
  -- | 'utilization'
  SavingsPlansUtilization ->
  SavingsPlansUtilizationAggregates
newSavingsPlansUtilizationAggregates :: SavingsPlansUtilization -> SavingsPlansUtilizationAggregates
newSavingsPlansUtilizationAggregates SavingsPlansUtilization
pUtilization_ =
  SavingsPlansUtilizationAggregates'
    { $sel:amortizedCommitment:SavingsPlansUtilizationAggregates' :: Maybe SavingsPlansAmortizedCommitment
amortizedCommitment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:savings:SavingsPlansUtilizationAggregates' :: Maybe SavingsPlansSavings
savings = forall a. Maybe a
Prelude.Nothing,
      $sel:utilization:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilization
utilization = SavingsPlansUtilization
pUtilization_
    }

-- | The total amortized commitment for a Savings Plans. This includes the
-- sum of the upfront and recurring Savings Plans fees.
savingsPlansUtilizationAggregates_amortizedCommitment :: Lens.Lens' SavingsPlansUtilizationAggregates (Prelude.Maybe SavingsPlansAmortizedCommitment)
savingsPlansUtilizationAggregates_amortizedCommitment :: Lens'
  SavingsPlansUtilizationAggregates
  (Maybe SavingsPlansAmortizedCommitment)
savingsPlansUtilizationAggregates_amortizedCommitment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SavingsPlansUtilizationAggregates' {Maybe SavingsPlansAmortizedCommitment
amortizedCommitment :: Maybe SavingsPlansAmortizedCommitment
$sel:amortizedCommitment:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates
-> Maybe SavingsPlansAmortizedCommitment
amortizedCommitment} -> Maybe SavingsPlansAmortizedCommitment
amortizedCommitment) (\s :: SavingsPlansUtilizationAggregates
s@SavingsPlansUtilizationAggregates' {} Maybe SavingsPlansAmortizedCommitment
a -> SavingsPlansUtilizationAggregates
s {$sel:amortizedCommitment:SavingsPlansUtilizationAggregates' :: Maybe SavingsPlansAmortizedCommitment
amortizedCommitment = Maybe SavingsPlansAmortizedCommitment
a} :: SavingsPlansUtilizationAggregates)

-- | The amount that\'s saved by using existing Savings Plans. Savings
-- returns both net savings from Savings Plans and also the
-- @onDemandCostEquivalent@ of the Savings Plans when considering the
-- utilization rate.
savingsPlansUtilizationAggregates_savings :: Lens.Lens' SavingsPlansUtilizationAggregates (Prelude.Maybe SavingsPlansSavings)
savingsPlansUtilizationAggregates_savings :: Lens' SavingsPlansUtilizationAggregates (Maybe SavingsPlansSavings)
savingsPlansUtilizationAggregates_savings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SavingsPlansUtilizationAggregates' {Maybe SavingsPlansSavings
savings :: Maybe SavingsPlansSavings
$sel:savings:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates -> Maybe SavingsPlansSavings
savings} -> Maybe SavingsPlansSavings
savings) (\s :: SavingsPlansUtilizationAggregates
s@SavingsPlansUtilizationAggregates' {} Maybe SavingsPlansSavings
a -> SavingsPlansUtilizationAggregates
s {$sel:savings:SavingsPlansUtilizationAggregates' :: Maybe SavingsPlansSavings
savings = Maybe SavingsPlansSavings
a} :: SavingsPlansUtilizationAggregates)

-- | A ratio of your effectiveness of using existing Savings Plans to apply
-- to workloads that are Savings Plans eligible.
savingsPlansUtilizationAggregates_utilization :: Lens.Lens' SavingsPlansUtilizationAggregates SavingsPlansUtilization
savingsPlansUtilizationAggregates_utilization :: Lens' SavingsPlansUtilizationAggregates SavingsPlansUtilization
savingsPlansUtilizationAggregates_utilization = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SavingsPlansUtilizationAggregates' {SavingsPlansUtilization
utilization :: SavingsPlansUtilization
$sel:utilization:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates -> SavingsPlansUtilization
utilization} -> SavingsPlansUtilization
utilization) (\s :: SavingsPlansUtilizationAggregates
s@SavingsPlansUtilizationAggregates' {} SavingsPlansUtilization
a -> SavingsPlansUtilizationAggregates
s {$sel:utilization:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilization
utilization = SavingsPlansUtilization
a} :: SavingsPlansUtilizationAggregates)

instance
  Data.FromJSON
    SavingsPlansUtilizationAggregates
  where
  parseJSON :: Value -> Parser SavingsPlansUtilizationAggregates
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SavingsPlansUtilizationAggregates"
      ( \Object
x ->
          Maybe SavingsPlansAmortizedCommitment
-> Maybe SavingsPlansSavings
-> SavingsPlansUtilization
-> SavingsPlansUtilizationAggregates
SavingsPlansUtilizationAggregates'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AmortizedCommitment")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Savings")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Utilization")
      )

instance
  Prelude.Hashable
    SavingsPlansUtilizationAggregates
  where
  hashWithSalt :: Int -> SavingsPlansUtilizationAggregates -> Int
hashWithSalt
    Int
_salt
    SavingsPlansUtilizationAggregates' {Maybe SavingsPlansAmortizedCommitment
Maybe SavingsPlansSavings
SavingsPlansUtilization
utilization :: SavingsPlansUtilization
savings :: Maybe SavingsPlansSavings
amortizedCommitment :: Maybe SavingsPlansAmortizedCommitment
$sel:utilization:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates -> SavingsPlansUtilization
$sel:savings:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates -> Maybe SavingsPlansSavings
$sel:amortizedCommitment:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates
-> Maybe SavingsPlansAmortizedCommitment
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SavingsPlansAmortizedCommitment
amortizedCommitment
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SavingsPlansSavings
savings
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` SavingsPlansUtilization
utilization

instance
  Prelude.NFData
    SavingsPlansUtilizationAggregates
  where
  rnf :: SavingsPlansUtilizationAggregates -> ()
rnf SavingsPlansUtilizationAggregates' {Maybe SavingsPlansAmortizedCommitment
Maybe SavingsPlansSavings
SavingsPlansUtilization
utilization :: SavingsPlansUtilization
savings :: Maybe SavingsPlansSavings
amortizedCommitment :: Maybe SavingsPlansAmortizedCommitment
$sel:utilization:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates -> SavingsPlansUtilization
$sel:savings:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates -> Maybe SavingsPlansSavings
$sel:amortizedCommitment:SavingsPlansUtilizationAggregates' :: SavingsPlansUtilizationAggregates
-> Maybe SavingsPlansAmortizedCommitment
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe SavingsPlansAmortizedCommitment
amortizedCommitment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SavingsPlansSavings
savings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SavingsPlansUtilization
utilization