{-# 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.EC2.Types.Subscription
-- 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.EC2.Types.Subscription where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.MetricType
import Amazonka.EC2.Types.PeriodType
import Amazonka.EC2.Types.StatisticType
import qualified Amazonka.Prelude as Prelude

-- | Describes an Infrastructure Performance subscription.
--
-- /See:/ 'newSubscription' smart constructor.
data Subscription = Subscription'
  { -- | The Region or Availability Zone that\'s the target for the subscription.
    -- For example, @eu-west-1@.
    Subscription -> Maybe Text
destination :: Prelude.Maybe Prelude.Text,
    -- | The metric used for the subscription.
    Subscription -> Maybe MetricType
metric :: Prelude.Maybe MetricType,
    -- | The data aggregation time for the subscription.
    Subscription -> Maybe PeriodType
period :: Prelude.Maybe PeriodType,
    -- | The Region or Availability Zone that\'s the source for the subscription.
    -- For example, @us-east-1@.
    Subscription -> Maybe Text
source :: Prelude.Maybe Prelude.Text,
    -- | The statistic used for the subscription.
    Subscription -> Maybe StatisticType
statistic :: Prelude.Maybe StatisticType
  }
  deriving (Subscription -> Subscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subscription -> Subscription -> Bool
$c/= :: Subscription -> Subscription -> Bool
== :: Subscription -> Subscription -> Bool
$c== :: Subscription -> Subscription -> Bool
Prelude.Eq, ReadPrec [Subscription]
ReadPrec Subscription
Int -> ReadS Subscription
ReadS [Subscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Subscription]
$creadListPrec :: ReadPrec [Subscription]
readPrec :: ReadPrec Subscription
$creadPrec :: ReadPrec Subscription
readList :: ReadS [Subscription]
$creadList :: ReadS [Subscription]
readsPrec :: Int -> ReadS Subscription
$creadsPrec :: Int -> ReadS Subscription
Prelude.Read, Int -> Subscription -> ShowS
[Subscription] -> ShowS
Subscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subscription] -> ShowS
$cshowList :: [Subscription] -> ShowS
show :: Subscription -> String
$cshow :: Subscription -> String
showsPrec :: Int -> Subscription -> ShowS
$cshowsPrec :: Int -> Subscription -> ShowS
Prelude.Show, forall x. Rep Subscription x -> Subscription
forall x. Subscription -> Rep Subscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subscription x -> Subscription
$cfrom :: forall x. Subscription -> Rep Subscription x
Prelude.Generic)

-- |
-- Create a value of 'Subscription' 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:
--
-- 'destination', 'subscription_destination' - The Region or Availability Zone that\'s the target for the subscription.
-- For example, @eu-west-1@.
--
-- 'metric', 'subscription_metric' - The metric used for the subscription.
--
-- 'period', 'subscription_period' - The data aggregation time for the subscription.
--
-- 'source', 'subscription_source' - The Region or Availability Zone that\'s the source for the subscription.
-- For example, @us-east-1@.
--
-- 'statistic', 'subscription_statistic' - The statistic used for the subscription.
newSubscription ::
  Subscription
newSubscription :: Subscription
newSubscription =
  Subscription'
    { $sel:destination:Subscription' :: Maybe Text
destination = forall a. Maybe a
Prelude.Nothing,
      $sel:metric:Subscription' :: Maybe MetricType
metric = forall a. Maybe a
Prelude.Nothing,
      $sel:period:Subscription' :: Maybe PeriodType
period = forall a. Maybe a
Prelude.Nothing,
      $sel:source:Subscription' :: Maybe Text
source = forall a. Maybe a
Prelude.Nothing,
      $sel:statistic:Subscription' :: Maybe StatisticType
statistic = forall a. Maybe a
Prelude.Nothing
    }

-- | The Region or Availability Zone that\'s the target for the subscription.
-- For example, @eu-west-1@.
subscription_destination :: Lens.Lens' Subscription (Prelude.Maybe Prelude.Text)
subscription_destination :: Lens' Subscription (Maybe Text)
subscription_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscription' {Maybe Text
destination :: Maybe Text
$sel:destination:Subscription' :: Subscription -> Maybe Text
destination} -> Maybe Text
destination) (\s :: Subscription
s@Subscription' {} Maybe Text
a -> Subscription
s {$sel:destination:Subscription' :: Maybe Text
destination = Maybe Text
a} :: Subscription)

-- | The metric used for the subscription.
subscription_metric :: Lens.Lens' Subscription (Prelude.Maybe MetricType)
subscription_metric :: Lens' Subscription (Maybe MetricType)
subscription_metric = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscription' {Maybe MetricType
metric :: Maybe MetricType
$sel:metric:Subscription' :: Subscription -> Maybe MetricType
metric} -> Maybe MetricType
metric) (\s :: Subscription
s@Subscription' {} Maybe MetricType
a -> Subscription
s {$sel:metric:Subscription' :: Maybe MetricType
metric = Maybe MetricType
a} :: Subscription)

-- | The data aggregation time for the subscription.
subscription_period :: Lens.Lens' Subscription (Prelude.Maybe PeriodType)
subscription_period :: Lens' Subscription (Maybe PeriodType)
subscription_period = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscription' {Maybe PeriodType
period :: Maybe PeriodType
$sel:period:Subscription' :: Subscription -> Maybe PeriodType
period} -> Maybe PeriodType
period) (\s :: Subscription
s@Subscription' {} Maybe PeriodType
a -> Subscription
s {$sel:period:Subscription' :: Maybe PeriodType
period = Maybe PeriodType
a} :: Subscription)

-- | The Region or Availability Zone that\'s the source for the subscription.
-- For example, @us-east-1@.
subscription_source :: Lens.Lens' Subscription (Prelude.Maybe Prelude.Text)
subscription_source :: Lens' Subscription (Maybe Text)
subscription_source = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscription' {Maybe Text
source :: Maybe Text
$sel:source:Subscription' :: Subscription -> Maybe Text
source} -> Maybe Text
source) (\s :: Subscription
s@Subscription' {} Maybe Text
a -> Subscription
s {$sel:source:Subscription' :: Maybe Text
source = Maybe Text
a} :: Subscription)

-- | The statistic used for the subscription.
subscription_statistic :: Lens.Lens' Subscription (Prelude.Maybe StatisticType)
subscription_statistic :: Lens' Subscription (Maybe StatisticType)
subscription_statistic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscription' {Maybe StatisticType
statistic :: Maybe StatisticType
$sel:statistic:Subscription' :: Subscription -> Maybe StatisticType
statistic} -> Maybe StatisticType
statistic) (\s :: Subscription
s@Subscription' {} Maybe StatisticType
a -> Subscription
s {$sel:statistic:Subscription' :: Maybe StatisticType
statistic = Maybe StatisticType
a} :: Subscription)

instance Data.FromXML Subscription where
  parseXML :: [Node] -> Either String Subscription
parseXML [Node]
x =
    Maybe Text
-> Maybe MetricType
-> Maybe PeriodType
-> Maybe Text
-> Maybe StatisticType
-> Subscription
Subscription'
      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
"destination")
      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
"metric")
      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
"period")
      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
"source")
      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
"statistic")

instance Prelude.Hashable Subscription where
  hashWithSalt :: Int -> Subscription -> Int
hashWithSalt Int
_salt Subscription' {Maybe Text
Maybe MetricType
Maybe PeriodType
Maybe StatisticType
statistic :: Maybe StatisticType
source :: Maybe Text
period :: Maybe PeriodType
metric :: Maybe MetricType
destination :: Maybe Text
$sel:statistic:Subscription' :: Subscription -> Maybe StatisticType
$sel:source:Subscription' :: Subscription -> Maybe Text
$sel:period:Subscription' :: Subscription -> Maybe PeriodType
$sel:metric:Subscription' :: Subscription -> Maybe MetricType
$sel:destination:Subscription' :: Subscription -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MetricType
metric
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PeriodType
period
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
source
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StatisticType
statistic

instance Prelude.NFData Subscription where
  rnf :: Subscription -> ()
rnf Subscription' {Maybe Text
Maybe MetricType
Maybe PeriodType
Maybe StatisticType
statistic :: Maybe StatisticType
source :: Maybe Text
period :: Maybe PeriodType
metric :: Maybe MetricType
destination :: Maybe Text
$sel:statistic:Subscription' :: Subscription -> Maybe StatisticType
$sel:source:Subscription' :: Subscription -> Maybe Text
$sel:period:Subscription' :: Subscription -> Maybe PeriodType
$sel:metric:Subscription' :: Subscription -> Maybe MetricType
$sel:destination:Subscription' :: Subscription -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MetricType
metric
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PeriodType
period
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
source
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StatisticType
statistic