{-# 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.Support.Types.TrustedAdvisorCostOptimizingSummary
-- 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.Support.Types.TrustedAdvisorCostOptimizingSummary where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The estimated cost savings that might be realized if the recommended
-- operations are taken.
--
-- /See:/ 'newTrustedAdvisorCostOptimizingSummary' smart constructor.
data TrustedAdvisorCostOptimizingSummary = TrustedAdvisorCostOptimizingSummary'
  { -- | The estimated monthly savings that might be realized if the recommended
    -- operations are taken.
    TrustedAdvisorCostOptimizingSummary -> Double
estimatedMonthlySavings :: Prelude.Double,
    -- | The estimated percentage of savings that might be realized if the
    -- recommended operations are taken.
    TrustedAdvisorCostOptimizingSummary -> Double
estimatedPercentMonthlySavings :: Prelude.Double
  }
  deriving (TrustedAdvisorCostOptimizingSummary
-> TrustedAdvisorCostOptimizingSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrustedAdvisorCostOptimizingSummary
-> TrustedAdvisorCostOptimizingSummary -> Bool
$c/= :: TrustedAdvisorCostOptimizingSummary
-> TrustedAdvisorCostOptimizingSummary -> Bool
== :: TrustedAdvisorCostOptimizingSummary
-> TrustedAdvisorCostOptimizingSummary -> Bool
$c== :: TrustedAdvisorCostOptimizingSummary
-> TrustedAdvisorCostOptimizingSummary -> Bool
Prelude.Eq, ReadPrec [TrustedAdvisorCostOptimizingSummary]
ReadPrec TrustedAdvisorCostOptimizingSummary
Int -> ReadS TrustedAdvisorCostOptimizingSummary
ReadS [TrustedAdvisorCostOptimizingSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TrustedAdvisorCostOptimizingSummary]
$creadListPrec :: ReadPrec [TrustedAdvisorCostOptimizingSummary]
readPrec :: ReadPrec TrustedAdvisorCostOptimizingSummary
$creadPrec :: ReadPrec TrustedAdvisorCostOptimizingSummary
readList :: ReadS [TrustedAdvisorCostOptimizingSummary]
$creadList :: ReadS [TrustedAdvisorCostOptimizingSummary]
readsPrec :: Int -> ReadS TrustedAdvisorCostOptimizingSummary
$creadsPrec :: Int -> ReadS TrustedAdvisorCostOptimizingSummary
Prelude.Read, Int -> TrustedAdvisorCostOptimizingSummary -> ShowS
[TrustedAdvisorCostOptimizingSummary] -> ShowS
TrustedAdvisorCostOptimizingSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrustedAdvisorCostOptimizingSummary] -> ShowS
$cshowList :: [TrustedAdvisorCostOptimizingSummary] -> ShowS
show :: TrustedAdvisorCostOptimizingSummary -> String
$cshow :: TrustedAdvisorCostOptimizingSummary -> String
showsPrec :: Int -> TrustedAdvisorCostOptimizingSummary -> ShowS
$cshowsPrec :: Int -> TrustedAdvisorCostOptimizingSummary -> ShowS
Prelude.Show, forall x.
Rep TrustedAdvisorCostOptimizingSummary x
-> TrustedAdvisorCostOptimizingSummary
forall x.
TrustedAdvisorCostOptimizingSummary
-> Rep TrustedAdvisorCostOptimizingSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TrustedAdvisorCostOptimizingSummary x
-> TrustedAdvisorCostOptimizingSummary
$cfrom :: forall x.
TrustedAdvisorCostOptimizingSummary
-> Rep TrustedAdvisorCostOptimizingSummary x
Prelude.Generic)

-- |
-- Create a value of 'TrustedAdvisorCostOptimizingSummary' 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:
--
-- 'estimatedMonthlySavings', 'trustedAdvisorCostOptimizingSummary_estimatedMonthlySavings' - The estimated monthly savings that might be realized if the recommended
-- operations are taken.
--
-- 'estimatedPercentMonthlySavings', 'trustedAdvisorCostOptimizingSummary_estimatedPercentMonthlySavings' - The estimated percentage of savings that might be realized if the
-- recommended operations are taken.
newTrustedAdvisorCostOptimizingSummary ::
  -- | 'estimatedMonthlySavings'
  Prelude.Double ->
  -- | 'estimatedPercentMonthlySavings'
  Prelude.Double ->
  TrustedAdvisorCostOptimizingSummary
newTrustedAdvisorCostOptimizingSummary :: Double -> Double -> TrustedAdvisorCostOptimizingSummary
newTrustedAdvisorCostOptimizingSummary
  Double
pEstimatedMonthlySavings_
  Double
pEstimatedPercentMonthlySavings_ =
    TrustedAdvisorCostOptimizingSummary'
      { $sel:estimatedMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: Double
estimatedMonthlySavings =
          Double
pEstimatedMonthlySavings_,
        $sel:estimatedPercentMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: Double
estimatedPercentMonthlySavings =
          Double
pEstimatedPercentMonthlySavings_
      }

-- | The estimated monthly savings that might be realized if the recommended
-- operations are taken.
trustedAdvisorCostOptimizingSummary_estimatedMonthlySavings :: Lens.Lens' TrustedAdvisorCostOptimizingSummary Prelude.Double
trustedAdvisorCostOptimizingSummary_estimatedMonthlySavings :: Lens' TrustedAdvisorCostOptimizingSummary Double
trustedAdvisorCostOptimizingSummary_estimatedMonthlySavings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrustedAdvisorCostOptimizingSummary' {Double
estimatedMonthlySavings :: Double
$sel:estimatedMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: TrustedAdvisorCostOptimizingSummary -> Double
estimatedMonthlySavings} -> Double
estimatedMonthlySavings) (\s :: TrustedAdvisorCostOptimizingSummary
s@TrustedAdvisorCostOptimizingSummary' {} Double
a -> TrustedAdvisorCostOptimizingSummary
s {$sel:estimatedMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: Double
estimatedMonthlySavings = Double
a} :: TrustedAdvisorCostOptimizingSummary)

-- | The estimated percentage of savings that might be realized if the
-- recommended operations are taken.
trustedAdvisorCostOptimizingSummary_estimatedPercentMonthlySavings :: Lens.Lens' TrustedAdvisorCostOptimizingSummary Prelude.Double
trustedAdvisorCostOptimizingSummary_estimatedPercentMonthlySavings :: Lens' TrustedAdvisorCostOptimizingSummary Double
trustedAdvisorCostOptimizingSummary_estimatedPercentMonthlySavings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrustedAdvisorCostOptimizingSummary' {Double
estimatedPercentMonthlySavings :: Double
$sel:estimatedPercentMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: TrustedAdvisorCostOptimizingSummary -> Double
estimatedPercentMonthlySavings} -> Double
estimatedPercentMonthlySavings) (\s :: TrustedAdvisorCostOptimizingSummary
s@TrustedAdvisorCostOptimizingSummary' {} Double
a -> TrustedAdvisorCostOptimizingSummary
s {$sel:estimatedPercentMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: Double
estimatedPercentMonthlySavings = Double
a} :: TrustedAdvisorCostOptimizingSummary)

instance
  Data.FromJSON
    TrustedAdvisorCostOptimizingSummary
  where
  parseJSON :: Value -> Parser TrustedAdvisorCostOptimizingSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TrustedAdvisorCostOptimizingSummary"
      ( \Object
x ->
          Double -> Double -> TrustedAdvisorCostOptimizingSummary
TrustedAdvisorCostOptimizingSummary'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"estimatedMonthlySavings")
            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
"estimatedPercentMonthlySavings")
      )

instance
  Prelude.Hashable
    TrustedAdvisorCostOptimizingSummary
  where
  hashWithSalt :: Int -> TrustedAdvisorCostOptimizingSummary -> Int
hashWithSalt
    Int
_salt
    TrustedAdvisorCostOptimizingSummary' {Double
estimatedPercentMonthlySavings :: Double
estimatedMonthlySavings :: Double
$sel:estimatedPercentMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: TrustedAdvisorCostOptimizingSummary -> Double
$sel:estimatedMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: TrustedAdvisorCostOptimizingSummary -> Double
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Double
estimatedMonthlySavings
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Double
estimatedPercentMonthlySavings

instance
  Prelude.NFData
    TrustedAdvisorCostOptimizingSummary
  where
  rnf :: TrustedAdvisorCostOptimizingSummary -> ()
rnf TrustedAdvisorCostOptimizingSummary' {Double
estimatedPercentMonthlySavings :: Double
estimatedMonthlySavings :: Double
$sel:estimatedPercentMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: TrustedAdvisorCostOptimizingSummary -> Double
$sel:estimatedMonthlySavings:TrustedAdvisorCostOptimizingSummary' :: TrustedAdvisorCostOptimizingSummary -> Double
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Double
estimatedMonthlySavings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Double
estimatedPercentMonthlySavings