{-# 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.DataResponse
-- 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.DataResponse 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.MetricPoint
import Amazonka.EC2.Types.MetricType
import Amazonka.EC2.Types.PeriodType
import Amazonka.EC2.Types.StatisticType
import qualified Amazonka.Prelude as Prelude

-- | The response to a @DataQuery@.
--
-- /See:/ 'newDataResponse' smart constructor.
data DataResponse = DataResponse'
  { -- | The Region or Availability Zone that\'s the destination for the data
    -- query. For example, @eu-west-1@.
    DataResponse -> Maybe Text
destination :: Prelude.Maybe Prelude.Text,
    -- | The ID passed in the @DataQuery@.
    DataResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The metric used for the network performance request. Currently only
    -- @aggregate-latency@ is supported, showing network latency during a
    -- specified period.
    DataResponse -> Maybe MetricType
metric :: Prelude.Maybe MetricType,
    -- | A list of @MetricPoint@ objects.
    DataResponse -> Maybe [MetricPoint]
metricPoints :: Prelude.Maybe [MetricPoint],
    -- | The period used for the network performance request.
    DataResponse -> Maybe PeriodType
period :: Prelude.Maybe PeriodType,
    -- | The Region or Availability Zone that\'s the source for the data query.
    -- For example, @us-east-1@.
    DataResponse -> Maybe Text
source :: Prelude.Maybe Prelude.Text,
    -- | The statistic used for the network performance request.
    DataResponse -> Maybe StatisticType
statistic :: Prelude.Maybe StatisticType
  }
  deriving (DataResponse -> DataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataResponse -> DataResponse -> Bool
$c/= :: DataResponse -> DataResponse -> Bool
== :: DataResponse -> DataResponse -> Bool
$c== :: DataResponse -> DataResponse -> Bool
Prelude.Eq, ReadPrec [DataResponse]
ReadPrec DataResponse
Int -> ReadS DataResponse
ReadS [DataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataResponse]
$creadListPrec :: ReadPrec [DataResponse]
readPrec :: ReadPrec DataResponse
$creadPrec :: ReadPrec DataResponse
readList :: ReadS [DataResponse]
$creadList :: ReadS [DataResponse]
readsPrec :: Int -> ReadS DataResponse
$creadsPrec :: Int -> ReadS DataResponse
Prelude.Read, Int -> DataResponse -> ShowS
[DataResponse] -> ShowS
DataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataResponse] -> ShowS
$cshowList :: [DataResponse] -> ShowS
show :: DataResponse -> String
$cshow :: DataResponse -> String
showsPrec :: Int -> DataResponse -> ShowS
$cshowsPrec :: Int -> DataResponse -> ShowS
Prelude.Show, forall x. Rep DataResponse x -> DataResponse
forall x. DataResponse -> Rep DataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataResponse x -> DataResponse
$cfrom :: forall x. DataResponse -> Rep DataResponse x
Prelude.Generic)

-- |
-- Create a value of 'DataResponse' 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', 'dataResponse_destination' - The Region or Availability Zone that\'s the destination for the data
-- query. For example, @eu-west-1@.
--
-- 'id', 'dataResponse_id' - The ID passed in the @DataQuery@.
--
-- 'metric', 'dataResponse_metric' - The metric used for the network performance request. Currently only
-- @aggregate-latency@ is supported, showing network latency during a
-- specified period.
--
-- 'metricPoints', 'dataResponse_metricPoints' - A list of @MetricPoint@ objects.
--
-- 'period', 'dataResponse_period' - The period used for the network performance request.
--
-- 'source', 'dataResponse_source' - The Region or Availability Zone that\'s the source for the data query.
-- For example, @us-east-1@.
--
-- 'statistic', 'dataResponse_statistic' - The statistic used for the network performance request.
newDataResponse ::
  DataResponse
newDataResponse :: DataResponse
newDataResponse =
  DataResponse'
    { $sel:destination:DataResponse' :: Maybe Text
destination = forall a. Maybe a
Prelude.Nothing,
      $sel:id:DataResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:metric:DataResponse' :: Maybe MetricType
metric = forall a. Maybe a
Prelude.Nothing,
      $sel:metricPoints:DataResponse' :: Maybe [MetricPoint]
metricPoints = forall a. Maybe a
Prelude.Nothing,
      $sel:period:DataResponse' :: Maybe PeriodType
period = forall a. Maybe a
Prelude.Nothing,
      $sel:source:DataResponse' :: Maybe Text
source = forall a. Maybe a
Prelude.Nothing,
      $sel:statistic:DataResponse' :: Maybe StatisticType
statistic = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The ID passed in the @DataQuery@.
dataResponse_id :: Lens.Lens' DataResponse (Prelude.Maybe Prelude.Text)
dataResponse_id :: Lens' DataResponse (Maybe Text)
dataResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataResponse' {Maybe Text
id :: Maybe Text
$sel:id:DataResponse' :: DataResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: DataResponse
s@DataResponse' {} Maybe Text
a -> DataResponse
s {$sel:id:DataResponse' :: Maybe Text
id = Maybe Text
a} :: DataResponse)

-- | The metric used for the network performance request. Currently only
-- @aggregate-latency@ is supported, showing network latency during a
-- specified period.
dataResponse_metric :: Lens.Lens' DataResponse (Prelude.Maybe MetricType)
dataResponse_metric :: Lens' DataResponse (Maybe MetricType)
dataResponse_metric = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataResponse' {Maybe MetricType
metric :: Maybe MetricType
$sel:metric:DataResponse' :: DataResponse -> Maybe MetricType
metric} -> Maybe MetricType
metric) (\s :: DataResponse
s@DataResponse' {} Maybe MetricType
a -> DataResponse
s {$sel:metric:DataResponse' :: Maybe MetricType
metric = Maybe MetricType
a} :: DataResponse)

-- | A list of @MetricPoint@ objects.
dataResponse_metricPoints :: Lens.Lens' DataResponse (Prelude.Maybe [MetricPoint])
dataResponse_metricPoints :: Lens' DataResponse (Maybe [MetricPoint])
dataResponse_metricPoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataResponse' {Maybe [MetricPoint]
metricPoints :: Maybe [MetricPoint]
$sel:metricPoints:DataResponse' :: DataResponse -> Maybe [MetricPoint]
metricPoints} -> Maybe [MetricPoint]
metricPoints) (\s :: DataResponse
s@DataResponse' {} Maybe [MetricPoint]
a -> DataResponse
s {$sel:metricPoints:DataResponse' :: Maybe [MetricPoint]
metricPoints = Maybe [MetricPoint]
a} :: DataResponse) 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 period used for the network performance request.
dataResponse_period :: Lens.Lens' DataResponse (Prelude.Maybe PeriodType)
dataResponse_period :: Lens' DataResponse (Maybe PeriodType)
dataResponse_period = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataResponse' {Maybe PeriodType
period :: Maybe PeriodType
$sel:period:DataResponse' :: DataResponse -> Maybe PeriodType
period} -> Maybe PeriodType
period) (\s :: DataResponse
s@DataResponse' {} Maybe PeriodType
a -> DataResponse
s {$sel:period:DataResponse' :: Maybe PeriodType
period = Maybe PeriodType
a} :: DataResponse)

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

-- | The statistic used for the network performance request.
dataResponse_statistic :: Lens.Lens' DataResponse (Prelude.Maybe StatisticType)
dataResponse_statistic :: Lens' DataResponse (Maybe StatisticType)
dataResponse_statistic = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataResponse' {Maybe StatisticType
statistic :: Maybe StatisticType
$sel:statistic:DataResponse' :: DataResponse -> Maybe StatisticType
statistic} -> Maybe StatisticType
statistic) (\s :: DataResponse
s@DataResponse' {} Maybe StatisticType
a -> DataResponse
s {$sel:statistic:DataResponse' :: Maybe StatisticType
statistic = Maybe StatisticType
a} :: DataResponse)

instance Data.FromXML DataResponse where
  parseXML :: [Node] -> Either String DataResponse
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe MetricType
-> Maybe [MetricPoint]
-> Maybe PeriodType
-> Maybe Text
-> Maybe StatisticType
-> DataResponse
DataResponse'
      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
"id")
      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
"metricPointSet"
                      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.<*> ([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 DataResponse where
  hashWithSalt :: Int -> DataResponse -> Int
hashWithSalt Int
_salt DataResponse' {Maybe [MetricPoint]
Maybe Text
Maybe MetricType
Maybe PeriodType
Maybe StatisticType
statistic :: Maybe StatisticType
source :: Maybe Text
period :: Maybe PeriodType
metricPoints :: Maybe [MetricPoint]
metric :: Maybe MetricType
id :: Maybe Text
destination :: Maybe Text
$sel:statistic:DataResponse' :: DataResponse -> Maybe StatisticType
$sel:source:DataResponse' :: DataResponse -> Maybe Text
$sel:period:DataResponse' :: DataResponse -> Maybe PeriodType
$sel:metricPoints:DataResponse' :: DataResponse -> Maybe [MetricPoint]
$sel:metric:DataResponse' :: DataResponse -> Maybe MetricType
$sel:id:DataResponse' :: DataResponse -> Maybe Text
$sel:destination:DataResponse' :: DataResponse -> 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 Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MetricType
metric
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MetricPoint]
metricPoints
      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 DataResponse where
  rnf :: DataResponse -> ()
rnf DataResponse' {Maybe [MetricPoint]
Maybe Text
Maybe MetricType
Maybe PeriodType
Maybe StatisticType
statistic :: Maybe StatisticType
source :: Maybe Text
period :: Maybe PeriodType
metricPoints :: Maybe [MetricPoint]
metric :: Maybe MetricType
id :: Maybe Text
destination :: Maybe Text
$sel:statistic:DataResponse' :: DataResponse -> Maybe StatisticType
$sel:source:DataResponse' :: DataResponse -> Maybe Text
$sel:period:DataResponse' :: DataResponse -> Maybe PeriodType
$sel:metricPoints:DataResponse' :: DataResponse -> Maybe [MetricPoint]
$sel:metric:DataResponse' :: DataResponse -> Maybe MetricType
$sel:id:DataResponse' :: DataResponse -> Maybe Text
$sel:destination:DataResponse' :: DataResponse -> 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 Text
id
      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 [MetricPoint]
metricPoints
      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