{-# 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.Pi.DescribeDimensionKeys
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- For a specific time period, retrieve the top @N@ dimension keys for a
-- metric.
--
-- Each response element returns a maximum of 500 bytes. For larger
-- elements, such as SQL statements, only the first 500 bytes are returned.
module Amazonka.Pi.DescribeDimensionKeys
  ( -- * Creating a Request
    DescribeDimensionKeys (..),
    newDescribeDimensionKeys,

    -- * Request Lenses
    describeDimensionKeys_additionalMetrics,
    describeDimensionKeys_filter,
    describeDimensionKeys_maxResults,
    describeDimensionKeys_nextToken,
    describeDimensionKeys_partitionBy,
    describeDimensionKeys_periodInSeconds,
    describeDimensionKeys_serviceType,
    describeDimensionKeys_identifier,
    describeDimensionKeys_startTime,
    describeDimensionKeys_endTime,
    describeDimensionKeys_metric,
    describeDimensionKeys_groupBy,

    -- * Destructuring the Response
    DescribeDimensionKeysResponse (..),
    newDescribeDimensionKeysResponse,

    -- * Response Lenses
    describeDimensionKeysResponse_alignedEndTime,
    describeDimensionKeysResponse_alignedStartTime,
    describeDimensionKeysResponse_keys,
    describeDimensionKeysResponse_nextToken,
    describeDimensionKeysResponse_partitionKeys,
    describeDimensionKeysResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Pi.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeDimensionKeys' smart constructor.
data DescribeDimensionKeys = DescribeDimensionKeys'
  { -- | Additional metrics for the top @N@ dimension keys. If the specified
    -- dimension group in the @GroupBy@ parameter is @db.sql_tokenized@, you
    -- can specify per-SQL metrics to get the values for the top @N@ SQL
    -- digests. The response syntax is as follows:
    -- @\"AdditionalMetrics\" : { \"@/@string@/@\" : \"@/@string@/@\" }@.
    DescribeDimensionKeys -> Maybe (NonEmpty Text)
additionalMetrics :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | One or more filters to apply in the request. Restrictions:
    --
    -- -   Any number of filters by the same dimension, as specified in the
    --     @GroupBy@ or @Partition@ parameters.
    --
    -- -   A single filter for any other dimension in this dimension group.
    DescribeDimensionKeys -> Maybe (HashMap Text Text)
filter' :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The maximum number of items to return in the response. If more items
    -- exist than the specified @MaxRecords@ value, a pagination token is
    -- included in the response so that the remaining results can be retrieved.
    DescribeDimensionKeys -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | An optional pagination token provided by a previous request. If this
    -- parameter is specified, the response includes only records beyond the
    -- token, up to the value specified by @MaxRecords@.
    DescribeDimensionKeys -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | For each dimension specified in @GroupBy@, specify a secondary dimension
    -- to further subdivide the partition keys in the response.
    DescribeDimensionKeys -> Maybe DimensionGroup
partitionBy :: Prelude.Maybe DimensionGroup,
    -- | The granularity, in seconds, of the data points returned from
    -- Performance Insights. A period can be as short as one second, or as long
    -- as one day (86400 seconds). Valid values are:
    --
    -- -   @1@ (one second)
    --
    -- -   @60@ (one minute)
    --
    -- -   @300@ (five minutes)
    --
    -- -   @3600@ (one hour)
    --
    -- -   @86400@ (twenty-four hours)
    --
    -- If you don\'t specify @PeriodInSeconds@, then Performance Insights
    -- chooses a value for you, with a goal of returning roughly 100-200 data
    -- points in the response.
    DescribeDimensionKeys -> Maybe Int
periodInSeconds :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Web Services service for which Performance Insights will
    -- return metrics. Valid values are as follows:
    --
    -- -   @RDS@
    --
    -- -   @DOCDB@
    DescribeDimensionKeys -> ServiceType
serviceType :: ServiceType,
    -- | An immutable, Amazon Web Services Region-unique identifier for a data
    -- source. Performance Insights gathers metrics from this data source.
    --
    -- To use an Amazon RDS instance as a data source, you specify its
    -- @DbiResourceId@ value. For example, specify
    -- @db-FAIHNTYBKTGAUSUZQYPDS2GW4A@.
    DescribeDimensionKeys -> Text
identifier :: Prelude.Text,
    -- | The date and time specifying the beginning of the requested time series
    -- data. You must specify a @StartTime@ within the past 7 days. The value
    -- specified is /inclusive/, which means that data points equal to or
    -- greater than @StartTime@ are returned.
    --
    -- The value for @StartTime@ must be earlier than the value for @EndTime@.
    DescribeDimensionKeys -> POSIX
startTime :: Data.POSIX,
    -- | The date and time specifying the end of the requested time series data.
    -- The value specified is /exclusive/, which means that data points less
    -- than (but not equal to) @EndTime@ are returned.
    --
    -- The value for @EndTime@ must be later than the value for @StartTime@.
    DescribeDimensionKeys -> POSIX
endTime :: Data.POSIX,
    -- | The name of a Performance Insights metric to be measured.
    --
    -- Valid values for @Metric@ are:
    --
    -- -   @db.load.avg@ - A scaled representation of the number of active
    --     sessions for the database engine.
    --
    -- -   @db.sampledload.avg@ - The raw number of active sessions for the
    --     database engine.
    --
    -- If the number of active sessions is less than an internal Performance
    -- Insights threshold, @db.load.avg@ and @db.sampledload.avg@ are the same
    -- value. If the number of active sessions is greater than the internal
    -- threshold, Performance Insights samples the active sessions, with
    -- @db.load.avg@ showing the scaled values, @db.sampledload.avg@ showing
    -- the raw values, and @db.sampledload.avg@ less than @db.load.avg@. For
    -- most use cases, you can query @db.load.avg@ only.
    DescribeDimensionKeys -> Text
metric :: Prelude.Text,
    -- | A specification for how to aggregate the data points from a query
    -- result. You must specify a valid dimension group. Performance Insights
    -- returns all dimensions within this group, unless you provide the names
    -- of specific dimensions within this group. You can also request that
    -- Performance Insights return a limited number of values for a dimension.
    DescribeDimensionKeys -> DimensionGroup
groupBy :: DimensionGroup
  }
  deriving (DescribeDimensionKeys -> DescribeDimensionKeys -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDimensionKeys -> DescribeDimensionKeys -> Bool
$c/= :: DescribeDimensionKeys -> DescribeDimensionKeys -> Bool
== :: DescribeDimensionKeys -> DescribeDimensionKeys -> Bool
$c== :: DescribeDimensionKeys -> DescribeDimensionKeys -> Bool
Prelude.Eq, ReadPrec [DescribeDimensionKeys]
ReadPrec DescribeDimensionKeys
Int -> ReadS DescribeDimensionKeys
ReadS [DescribeDimensionKeys]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDimensionKeys]
$creadListPrec :: ReadPrec [DescribeDimensionKeys]
readPrec :: ReadPrec DescribeDimensionKeys
$creadPrec :: ReadPrec DescribeDimensionKeys
readList :: ReadS [DescribeDimensionKeys]
$creadList :: ReadS [DescribeDimensionKeys]
readsPrec :: Int -> ReadS DescribeDimensionKeys
$creadsPrec :: Int -> ReadS DescribeDimensionKeys
Prelude.Read, Int -> DescribeDimensionKeys -> ShowS
[DescribeDimensionKeys] -> ShowS
DescribeDimensionKeys -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDimensionKeys] -> ShowS
$cshowList :: [DescribeDimensionKeys] -> ShowS
show :: DescribeDimensionKeys -> String
$cshow :: DescribeDimensionKeys -> String
showsPrec :: Int -> DescribeDimensionKeys -> ShowS
$cshowsPrec :: Int -> DescribeDimensionKeys -> ShowS
Prelude.Show, forall x. Rep DescribeDimensionKeys x -> DescribeDimensionKeys
forall x. DescribeDimensionKeys -> Rep DescribeDimensionKeys x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDimensionKeys x -> DescribeDimensionKeys
$cfrom :: forall x. DescribeDimensionKeys -> Rep DescribeDimensionKeys x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDimensionKeys' 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:
--
-- 'additionalMetrics', 'describeDimensionKeys_additionalMetrics' - Additional metrics for the top @N@ dimension keys. If the specified
-- dimension group in the @GroupBy@ parameter is @db.sql_tokenized@, you
-- can specify per-SQL metrics to get the values for the top @N@ SQL
-- digests. The response syntax is as follows:
-- @\"AdditionalMetrics\" : { \"@/@string@/@\" : \"@/@string@/@\" }@.
--
-- 'filter'', 'describeDimensionKeys_filter' - One or more filters to apply in the request. Restrictions:
--
-- -   Any number of filters by the same dimension, as specified in the
--     @GroupBy@ or @Partition@ parameters.
--
-- -   A single filter for any other dimension in this dimension group.
--
-- 'maxResults', 'describeDimensionKeys_maxResults' - The maximum number of items to return in the response. If more items
-- exist than the specified @MaxRecords@ value, a pagination token is
-- included in the response so that the remaining results can be retrieved.
--
-- 'nextToken', 'describeDimensionKeys_nextToken' - An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- token, up to the value specified by @MaxRecords@.
--
-- 'partitionBy', 'describeDimensionKeys_partitionBy' - For each dimension specified in @GroupBy@, specify a secondary dimension
-- to further subdivide the partition keys in the response.
--
-- 'periodInSeconds', 'describeDimensionKeys_periodInSeconds' - The granularity, in seconds, of the data points returned from
-- Performance Insights. A period can be as short as one second, or as long
-- as one day (86400 seconds). Valid values are:
--
-- -   @1@ (one second)
--
-- -   @60@ (one minute)
--
-- -   @300@ (five minutes)
--
-- -   @3600@ (one hour)
--
-- -   @86400@ (twenty-four hours)
--
-- If you don\'t specify @PeriodInSeconds@, then Performance Insights
-- chooses a value for you, with a goal of returning roughly 100-200 data
-- points in the response.
--
-- 'serviceType', 'describeDimensionKeys_serviceType' - The Amazon Web Services service for which Performance Insights will
-- return metrics. Valid values are as follows:
--
-- -   @RDS@
--
-- -   @DOCDB@
--
-- 'identifier', 'describeDimensionKeys_identifier' - An immutable, Amazon Web Services Region-unique identifier for a data
-- source. Performance Insights gathers metrics from this data source.
--
-- To use an Amazon RDS instance as a data source, you specify its
-- @DbiResourceId@ value. For example, specify
-- @db-FAIHNTYBKTGAUSUZQYPDS2GW4A@.
--
-- 'startTime', 'describeDimensionKeys_startTime' - The date and time specifying the beginning of the requested time series
-- data. You must specify a @StartTime@ within the past 7 days. The value
-- specified is /inclusive/, which means that data points equal to or
-- greater than @StartTime@ are returned.
--
-- The value for @StartTime@ must be earlier than the value for @EndTime@.
--
-- 'endTime', 'describeDimensionKeys_endTime' - The date and time specifying the end of the requested time series data.
-- The value specified is /exclusive/, which means that data points less
-- than (but not equal to) @EndTime@ are returned.
--
-- The value for @EndTime@ must be later than the value for @StartTime@.
--
-- 'metric', 'describeDimensionKeys_metric' - The name of a Performance Insights metric to be measured.
--
-- Valid values for @Metric@ are:
--
-- -   @db.load.avg@ - A scaled representation of the number of active
--     sessions for the database engine.
--
-- -   @db.sampledload.avg@ - The raw number of active sessions for the
--     database engine.
--
-- If the number of active sessions is less than an internal Performance
-- Insights threshold, @db.load.avg@ and @db.sampledload.avg@ are the same
-- value. If the number of active sessions is greater than the internal
-- threshold, Performance Insights samples the active sessions, with
-- @db.load.avg@ showing the scaled values, @db.sampledload.avg@ showing
-- the raw values, and @db.sampledload.avg@ less than @db.load.avg@. For
-- most use cases, you can query @db.load.avg@ only.
--
-- 'groupBy', 'describeDimensionKeys_groupBy' - A specification for how to aggregate the data points from a query
-- result. You must specify a valid dimension group. Performance Insights
-- returns all dimensions within this group, unless you provide the names
-- of specific dimensions within this group. You can also request that
-- Performance Insights return a limited number of values for a dimension.
newDescribeDimensionKeys ::
  -- | 'serviceType'
  ServiceType ->
  -- | 'identifier'
  Prelude.Text ->
  -- | 'startTime'
  Prelude.UTCTime ->
  -- | 'endTime'
  Prelude.UTCTime ->
  -- | 'metric'
  Prelude.Text ->
  -- | 'groupBy'
  DimensionGroup ->
  DescribeDimensionKeys
newDescribeDimensionKeys :: ServiceType
-> Text
-> UTCTime
-> UTCTime
-> Text
-> DimensionGroup
-> DescribeDimensionKeys
newDescribeDimensionKeys
  ServiceType
pServiceType_
  Text
pIdentifier_
  UTCTime
pStartTime_
  UTCTime
pEndTime_
  Text
pMetric_
  DimensionGroup
pGroupBy_ =
    DescribeDimensionKeys'
      { $sel:additionalMetrics:DescribeDimensionKeys' :: Maybe (NonEmpty Text)
additionalMetrics =
          forall a. Maybe a
Prelude.Nothing,
        $sel:filter':DescribeDimensionKeys' :: Maybe (HashMap Text Text)
filter' = forall a. Maybe a
Prelude.Nothing,
        $sel:maxResults:DescribeDimensionKeys' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeDimensionKeys' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:partitionBy:DescribeDimensionKeys' :: Maybe DimensionGroup
partitionBy = forall a. Maybe a
Prelude.Nothing,
        $sel:periodInSeconds:DescribeDimensionKeys' :: Maybe Int
periodInSeconds = forall a. Maybe a
Prelude.Nothing,
        $sel:serviceType:DescribeDimensionKeys' :: ServiceType
serviceType = ServiceType
pServiceType_,
        $sel:identifier:DescribeDimensionKeys' :: Text
identifier = Text
pIdentifier_,
        $sel:startTime:DescribeDimensionKeys' :: POSIX
startTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pStartTime_,
        $sel:endTime:DescribeDimensionKeys' :: POSIX
endTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pEndTime_,
        $sel:metric:DescribeDimensionKeys' :: Text
metric = Text
pMetric_,
        $sel:groupBy:DescribeDimensionKeys' :: DimensionGroup
groupBy = DimensionGroup
pGroupBy_
      }

-- | Additional metrics for the top @N@ dimension keys. If the specified
-- dimension group in the @GroupBy@ parameter is @db.sql_tokenized@, you
-- can specify per-SQL metrics to get the values for the top @N@ SQL
-- digests. The response syntax is as follows:
-- @\"AdditionalMetrics\" : { \"@/@string@/@\" : \"@/@string@/@\" }@.
describeDimensionKeys_additionalMetrics :: Lens.Lens' DescribeDimensionKeys (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeDimensionKeys_additionalMetrics :: Lens' DescribeDimensionKeys (Maybe (NonEmpty Text))
describeDimensionKeys_additionalMetrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Maybe (NonEmpty Text)
additionalMetrics :: Maybe (NonEmpty Text)
$sel:additionalMetrics:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (NonEmpty Text)
additionalMetrics} -> Maybe (NonEmpty Text)
additionalMetrics) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Maybe (NonEmpty Text)
a -> DescribeDimensionKeys
s {$sel:additionalMetrics:DescribeDimensionKeys' :: Maybe (NonEmpty Text)
additionalMetrics = Maybe (NonEmpty Text)
a} :: DescribeDimensionKeys) 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

-- | One or more filters to apply in the request. Restrictions:
--
-- -   Any number of filters by the same dimension, as specified in the
--     @GroupBy@ or @Partition@ parameters.
--
-- -   A single filter for any other dimension in this dimension group.
describeDimensionKeys_filter :: Lens.Lens' DescribeDimensionKeys (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeDimensionKeys_filter :: Lens' DescribeDimensionKeys (Maybe (HashMap Text Text))
describeDimensionKeys_filter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Maybe (HashMap Text Text)
filter' :: Maybe (HashMap Text Text)
$sel:filter':DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (HashMap Text Text)
filter'} -> Maybe (HashMap Text Text)
filter') (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Maybe (HashMap Text Text)
a -> DescribeDimensionKeys
s {$sel:filter':DescribeDimensionKeys' :: Maybe (HashMap Text Text)
filter' = Maybe (HashMap Text Text)
a} :: DescribeDimensionKeys) 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 maximum number of items to return in the response. If more items
-- exist than the specified @MaxRecords@ value, a pagination token is
-- included in the response so that the remaining results can be retrieved.
describeDimensionKeys_maxResults :: Lens.Lens' DescribeDimensionKeys (Prelude.Maybe Prelude.Natural)
describeDimensionKeys_maxResults :: Lens' DescribeDimensionKeys (Maybe Natural)
describeDimensionKeys_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Maybe Natural
a -> DescribeDimensionKeys
s {$sel:maxResults:DescribeDimensionKeys' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeDimensionKeys)

-- | An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- token, up to the value specified by @MaxRecords@.
describeDimensionKeys_nextToken :: Lens.Lens' DescribeDimensionKeys (Prelude.Maybe Prelude.Text)
describeDimensionKeys_nextToken :: Lens' DescribeDimensionKeys (Maybe Text)
describeDimensionKeys_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Maybe Text
a -> DescribeDimensionKeys
s {$sel:nextToken:DescribeDimensionKeys' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeDimensionKeys)

-- | For each dimension specified in @GroupBy@, specify a secondary dimension
-- to further subdivide the partition keys in the response.
describeDimensionKeys_partitionBy :: Lens.Lens' DescribeDimensionKeys (Prelude.Maybe DimensionGroup)
describeDimensionKeys_partitionBy :: Lens' DescribeDimensionKeys (Maybe DimensionGroup)
describeDimensionKeys_partitionBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Maybe DimensionGroup
partitionBy :: Maybe DimensionGroup
$sel:partitionBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe DimensionGroup
partitionBy} -> Maybe DimensionGroup
partitionBy) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Maybe DimensionGroup
a -> DescribeDimensionKeys
s {$sel:partitionBy:DescribeDimensionKeys' :: Maybe DimensionGroup
partitionBy = Maybe DimensionGroup
a} :: DescribeDimensionKeys)

-- | The granularity, in seconds, of the data points returned from
-- Performance Insights. A period can be as short as one second, or as long
-- as one day (86400 seconds). Valid values are:
--
-- -   @1@ (one second)
--
-- -   @60@ (one minute)
--
-- -   @300@ (five minutes)
--
-- -   @3600@ (one hour)
--
-- -   @86400@ (twenty-four hours)
--
-- If you don\'t specify @PeriodInSeconds@, then Performance Insights
-- chooses a value for you, with a goal of returning roughly 100-200 data
-- points in the response.
describeDimensionKeys_periodInSeconds :: Lens.Lens' DescribeDimensionKeys (Prelude.Maybe Prelude.Int)
describeDimensionKeys_periodInSeconds :: Lens' DescribeDimensionKeys (Maybe Int)
describeDimensionKeys_periodInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Maybe Int
periodInSeconds :: Maybe Int
$sel:periodInSeconds:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Int
periodInSeconds} -> Maybe Int
periodInSeconds) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Maybe Int
a -> DescribeDimensionKeys
s {$sel:periodInSeconds:DescribeDimensionKeys' :: Maybe Int
periodInSeconds = Maybe Int
a} :: DescribeDimensionKeys)

-- | The Amazon Web Services service for which Performance Insights will
-- return metrics. Valid values are as follows:
--
-- -   @RDS@
--
-- -   @DOCDB@
describeDimensionKeys_serviceType :: Lens.Lens' DescribeDimensionKeys ServiceType
describeDimensionKeys_serviceType :: Lens' DescribeDimensionKeys ServiceType
describeDimensionKeys_serviceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {ServiceType
serviceType :: ServiceType
$sel:serviceType:DescribeDimensionKeys' :: DescribeDimensionKeys -> ServiceType
serviceType} -> ServiceType
serviceType) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} ServiceType
a -> DescribeDimensionKeys
s {$sel:serviceType:DescribeDimensionKeys' :: ServiceType
serviceType = ServiceType
a} :: DescribeDimensionKeys)

-- | An immutable, Amazon Web Services Region-unique identifier for a data
-- source. Performance Insights gathers metrics from this data source.
--
-- To use an Amazon RDS instance as a data source, you specify its
-- @DbiResourceId@ value. For example, specify
-- @db-FAIHNTYBKTGAUSUZQYPDS2GW4A@.
describeDimensionKeys_identifier :: Lens.Lens' DescribeDimensionKeys Prelude.Text
describeDimensionKeys_identifier :: Lens' DescribeDimensionKeys Text
describeDimensionKeys_identifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Text
identifier :: Text
$sel:identifier:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
identifier} -> Text
identifier) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Text
a -> DescribeDimensionKeys
s {$sel:identifier:DescribeDimensionKeys' :: Text
identifier = Text
a} :: DescribeDimensionKeys)

-- | The date and time specifying the beginning of the requested time series
-- data. You must specify a @StartTime@ within the past 7 days. The value
-- specified is /inclusive/, which means that data points equal to or
-- greater than @StartTime@ are returned.
--
-- The value for @StartTime@ must be earlier than the value for @EndTime@.
describeDimensionKeys_startTime :: Lens.Lens' DescribeDimensionKeys Prelude.UTCTime
describeDimensionKeys_startTime :: Lens' DescribeDimensionKeys UTCTime
describeDimensionKeys_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {POSIX
startTime :: POSIX
$sel:startTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
startTime} -> POSIX
startTime) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} POSIX
a -> DescribeDimensionKeys
s {$sel:startTime:DescribeDimensionKeys' :: POSIX
startTime = POSIX
a} :: DescribeDimensionKeys) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The date and time specifying the end of the requested time series data.
-- The value specified is /exclusive/, which means that data points less
-- than (but not equal to) @EndTime@ are returned.
--
-- The value for @EndTime@ must be later than the value for @StartTime@.
describeDimensionKeys_endTime :: Lens.Lens' DescribeDimensionKeys Prelude.UTCTime
describeDimensionKeys_endTime :: Lens' DescribeDimensionKeys UTCTime
describeDimensionKeys_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {POSIX
endTime :: POSIX
$sel:endTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
endTime} -> POSIX
endTime) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} POSIX
a -> DescribeDimensionKeys
s {$sel:endTime:DescribeDimensionKeys' :: POSIX
endTime = POSIX
a} :: DescribeDimensionKeys) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The name of a Performance Insights metric to be measured.
--
-- Valid values for @Metric@ are:
--
-- -   @db.load.avg@ - A scaled representation of the number of active
--     sessions for the database engine.
--
-- -   @db.sampledload.avg@ - The raw number of active sessions for the
--     database engine.
--
-- If the number of active sessions is less than an internal Performance
-- Insights threshold, @db.load.avg@ and @db.sampledload.avg@ are the same
-- value. If the number of active sessions is greater than the internal
-- threshold, Performance Insights samples the active sessions, with
-- @db.load.avg@ showing the scaled values, @db.sampledload.avg@ showing
-- the raw values, and @db.sampledload.avg@ less than @db.load.avg@. For
-- most use cases, you can query @db.load.avg@ only.
describeDimensionKeys_metric :: Lens.Lens' DescribeDimensionKeys Prelude.Text
describeDimensionKeys_metric :: Lens' DescribeDimensionKeys Text
describeDimensionKeys_metric = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {Text
metric :: Text
$sel:metric:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
metric} -> Text
metric) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} Text
a -> DescribeDimensionKeys
s {$sel:metric:DescribeDimensionKeys' :: Text
metric = Text
a} :: DescribeDimensionKeys)

-- | A specification for how to aggregate the data points from a query
-- result. You must specify a valid dimension group. Performance Insights
-- returns all dimensions within this group, unless you provide the names
-- of specific dimensions within this group. You can also request that
-- Performance Insights return a limited number of values for a dimension.
describeDimensionKeys_groupBy :: Lens.Lens' DescribeDimensionKeys DimensionGroup
describeDimensionKeys_groupBy :: Lens' DescribeDimensionKeys DimensionGroup
describeDimensionKeys_groupBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeys' {DimensionGroup
groupBy :: DimensionGroup
$sel:groupBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> DimensionGroup
groupBy} -> DimensionGroup
groupBy) (\s :: DescribeDimensionKeys
s@DescribeDimensionKeys' {} DimensionGroup
a -> DescribeDimensionKeys
s {$sel:groupBy:DescribeDimensionKeys' :: DimensionGroup
groupBy = DimensionGroup
a} :: DescribeDimensionKeys)

instance Core.AWSRequest DescribeDimensionKeys where
  type
    AWSResponse DescribeDimensionKeys =
      DescribeDimensionKeysResponse
  request :: (Service -> Service)
-> DescribeDimensionKeys -> Request DescribeDimensionKeys
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 DescribeDimensionKeys
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeDimensionKeys)))
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 POSIX
-> Maybe POSIX
-> Maybe [DimensionKeyDescription]
-> Maybe Text
-> Maybe [ResponsePartitionKey]
-> Int
-> DescribeDimensionKeysResponse
DescribeDimensionKeysResponse'
            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
"AlignedEndTime")
            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
"AlignedStartTime")
            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
"Keys" 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
"NextToken")
            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
"PartitionKeys" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeDimensionKeys where
  hashWithSalt :: Int -> DescribeDimensionKeys -> Int
hashWithSalt Int
_salt DescribeDimensionKeys' {Maybe Int
Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe (HashMap Text Text)
Maybe DimensionGroup
Text
POSIX
DimensionGroup
ServiceType
groupBy :: DimensionGroup
metric :: Text
endTime :: POSIX
startTime :: POSIX
identifier :: Text
serviceType :: ServiceType
periodInSeconds :: Maybe Int
partitionBy :: Maybe DimensionGroup
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe (HashMap Text Text)
additionalMetrics :: Maybe (NonEmpty Text)
$sel:groupBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> DimensionGroup
$sel:metric:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
$sel:endTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
$sel:startTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
$sel:identifier:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
$sel:serviceType:DescribeDimensionKeys' :: DescribeDimensionKeys -> ServiceType
$sel:periodInSeconds:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Int
$sel:partitionBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe DimensionGroup
$sel:nextToken:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Text
$sel:maxResults:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Natural
$sel:filter':DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (HashMap Text Text)
$sel:additionalMetrics:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (NonEmpty Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
additionalMetrics
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
filter'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DimensionGroup
partitionBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
periodInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ServiceType
serviceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
metric
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` DimensionGroup
groupBy

instance Prelude.NFData DescribeDimensionKeys where
  rnf :: DescribeDimensionKeys -> ()
rnf DescribeDimensionKeys' {Maybe Int
Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe (HashMap Text Text)
Maybe DimensionGroup
Text
POSIX
DimensionGroup
ServiceType
groupBy :: DimensionGroup
metric :: Text
endTime :: POSIX
startTime :: POSIX
identifier :: Text
serviceType :: ServiceType
periodInSeconds :: Maybe Int
partitionBy :: Maybe DimensionGroup
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe (HashMap Text Text)
additionalMetrics :: Maybe (NonEmpty Text)
$sel:groupBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> DimensionGroup
$sel:metric:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
$sel:endTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
$sel:startTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
$sel:identifier:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
$sel:serviceType:DescribeDimensionKeys' :: DescribeDimensionKeys -> ServiceType
$sel:periodInSeconds:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Int
$sel:partitionBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe DimensionGroup
$sel:nextToken:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Text
$sel:maxResults:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Natural
$sel:filter':DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (HashMap Text Text)
$sel:additionalMetrics:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
additionalMetrics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
filter'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DimensionGroup
partitionBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
periodInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ServiceType
serviceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
identifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
metric
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf DimensionGroup
groupBy

instance Data.ToHeaders DescribeDimensionKeys where
  toHeaders :: DescribeDimensionKeys -> 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
"PerformanceInsightsv20180227.DescribeDimensionKeys" ::
                          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 DescribeDimensionKeys where
  toJSON :: DescribeDimensionKeys -> Value
toJSON DescribeDimensionKeys' {Maybe Int
Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
Maybe (HashMap Text Text)
Maybe DimensionGroup
Text
POSIX
DimensionGroup
ServiceType
groupBy :: DimensionGroup
metric :: Text
endTime :: POSIX
startTime :: POSIX
identifier :: Text
serviceType :: ServiceType
periodInSeconds :: Maybe Int
partitionBy :: Maybe DimensionGroup
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe (HashMap Text Text)
additionalMetrics :: Maybe (NonEmpty Text)
$sel:groupBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> DimensionGroup
$sel:metric:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
$sel:endTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
$sel:startTime:DescribeDimensionKeys' :: DescribeDimensionKeys -> POSIX
$sel:identifier:DescribeDimensionKeys' :: DescribeDimensionKeys -> Text
$sel:serviceType:DescribeDimensionKeys' :: DescribeDimensionKeys -> ServiceType
$sel:periodInSeconds:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Int
$sel:partitionBy:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe DimensionGroup
$sel:nextToken:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Text
$sel:maxResults:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe Natural
$sel:filter':DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (HashMap Text Text)
$sel:additionalMetrics:DescribeDimensionKeys' :: DescribeDimensionKeys -> Maybe (NonEmpty Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AdditionalMetrics" 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 (NonEmpty Text)
additionalMetrics,
            (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 (HashMap Text Text)
filter',
            (Key
"MaxResults" 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
maxResults,
            (Key
"NextToken" 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 Text
nextToken,
            (Key
"PartitionBy" 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 DimensionGroup
partitionBy,
            (Key
"PeriodInSeconds" 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 Int
periodInSeconds,
            forall a. a -> Maybe a
Prelude.Just (Key
"ServiceType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ServiceType
serviceType),
            forall a. a -> Maybe a
Prelude.Just (Key
"Identifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
identifier),
            forall a. a -> Maybe a
Prelude.Just (Key
"StartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
startTime),
            forall a. a -> Maybe a
Prelude.Just (Key
"EndTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
endTime),
            forall a. a -> Maybe a
Prelude.Just (Key
"Metric" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
metric),
            forall a. a -> Maybe a
Prelude.Just (Key
"GroupBy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= DimensionGroup
groupBy)
          ]
      )

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

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

-- | /See:/ 'newDescribeDimensionKeysResponse' smart constructor.
data DescribeDimensionKeysResponse = DescribeDimensionKeysResponse'
  { -- | The end time for the returned dimension keys, after alignment to a
    -- granular boundary (as specified by @PeriodInSeconds@). @AlignedEndTime@
    -- will be greater than or equal to the value of the user-specified
    -- @Endtime@.
    DescribeDimensionKeysResponse -> Maybe POSIX
alignedEndTime :: Prelude.Maybe Data.POSIX,
    -- | The start time for the returned dimension keys, after alignment to a
    -- granular boundary (as specified by @PeriodInSeconds@).
    -- @AlignedStartTime@ will be less than or equal to the value of the
    -- user-specified @StartTime@.
    DescribeDimensionKeysResponse -> Maybe POSIX
alignedStartTime :: Prelude.Maybe Data.POSIX,
    -- | The dimension keys that were requested.
    DescribeDimensionKeysResponse -> Maybe [DimensionKeyDescription]
keys :: Prelude.Maybe [DimensionKeyDescription],
    -- | A pagination token that indicates the response didn’t return all
    -- available records because @MaxRecords@ was specified in the previous
    -- request. To get the remaining records, specify @NextToken@ in a separate
    -- request with this value.
    DescribeDimensionKeysResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | If @PartitionBy@ was present in the request, @PartitionKeys@ contains
    -- the breakdown of dimension keys by the specified partitions.
    DescribeDimensionKeysResponse -> Maybe [ResponsePartitionKey]
partitionKeys :: Prelude.Maybe [ResponsePartitionKey],
    -- | The response's http status code.
    DescribeDimensionKeysResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeDimensionKeysResponse
-> DescribeDimensionKeysResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDimensionKeysResponse
-> DescribeDimensionKeysResponse -> Bool
$c/= :: DescribeDimensionKeysResponse
-> DescribeDimensionKeysResponse -> Bool
== :: DescribeDimensionKeysResponse
-> DescribeDimensionKeysResponse -> Bool
$c== :: DescribeDimensionKeysResponse
-> DescribeDimensionKeysResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDimensionKeysResponse]
ReadPrec DescribeDimensionKeysResponse
Int -> ReadS DescribeDimensionKeysResponse
ReadS [DescribeDimensionKeysResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDimensionKeysResponse]
$creadListPrec :: ReadPrec [DescribeDimensionKeysResponse]
readPrec :: ReadPrec DescribeDimensionKeysResponse
$creadPrec :: ReadPrec DescribeDimensionKeysResponse
readList :: ReadS [DescribeDimensionKeysResponse]
$creadList :: ReadS [DescribeDimensionKeysResponse]
readsPrec :: Int -> ReadS DescribeDimensionKeysResponse
$creadsPrec :: Int -> ReadS DescribeDimensionKeysResponse
Prelude.Read, Int -> DescribeDimensionKeysResponse -> ShowS
[DescribeDimensionKeysResponse] -> ShowS
DescribeDimensionKeysResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDimensionKeysResponse] -> ShowS
$cshowList :: [DescribeDimensionKeysResponse] -> ShowS
show :: DescribeDimensionKeysResponse -> String
$cshow :: DescribeDimensionKeysResponse -> String
showsPrec :: Int -> DescribeDimensionKeysResponse -> ShowS
$cshowsPrec :: Int -> DescribeDimensionKeysResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeDimensionKeysResponse x
-> DescribeDimensionKeysResponse
forall x.
DescribeDimensionKeysResponse
-> Rep DescribeDimensionKeysResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDimensionKeysResponse x
-> DescribeDimensionKeysResponse
$cfrom :: forall x.
DescribeDimensionKeysResponse
-> Rep DescribeDimensionKeysResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDimensionKeysResponse' 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:
--
-- 'alignedEndTime', 'describeDimensionKeysResponse_alignedEndTime' - The end time for the returned dimension keys, after alignment to a
-- granular boundary (as specified by @PeriodInSeconds@). @AlignedEndTime@
-- will be greater than or equal to the value of the user-specified
-- @Endtime@.
--
-- 'alignedStartTime', 'describeDimensionKeysResponse_alignedStartTime' - The start time for the returned dimension keys, after alignment to a
-- granular boundary (as specified by @PeriodInSeconds@).
-- @AlignedStartTime@ will be less than or equal to the value of the
-- user-specified @StartTime@.
--
-- 'keys', 'describeDimensionKeysResponse_keys' - The dimension keys that were requested.
--
-- 'nextToken', 'describeDimensionKeysResponse_nextToken' - A pagination token that indicates the response didn’t return all
-- available records because @MaxRecords@ was specified in the previous
-- request. To get the remaining records, specify @NextToken@ in a separate
-- request with this value.
--
-- 'partitionKeys', 'describeDimensionKeysResponse_partitionKeys' - If @PartitionBy@ was present in the request, @PartitionKeys@ contains
-- the breakdown of dimension keys by the specified partitions.
--
-- 'httpStatus', 'describeDimensionKeysResponse_httpStatus' - The response's http status code.
newDescribeDimensionKeysResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDimensionKeysResponse
newDescribeDimensionKeysResponse :: Int -> DescribeDimensionKeysResponse
newDescribeDimensionKeysResponse Int
pHttpStatus_ =
  DescribeDimensionKeysResponse'
    { $sel:alignedEndTime:DescribeDimensionKeysResponse' :: Maybe POSIX
alignedEndTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:alignedStartTime:DescribeDimensionKeysResponse' :: Maybe POSIX
alignedStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:keys:DescribeDimensionKeysResponse' :: Maybe [DimensionKeyDescription]
keys = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeDimensionKeysResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:partitionKeys:DescribeDimensionKeysResponse' :: Maybe [ResponsePartitionKey]
partitionKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeDimensionKeysResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The end time for the returned dimension keys, after alignment to a
-- granular boundary (as specified by @PeriodInSeconds@). @AlignedEndTime@
-- will be greater than or equal to the value of the user-specified
-- @Endtime@.
describeDimensionKeysResponse_alignedEndTime :: Lens.Lens' DescribeDimensionKeysResponse (Prelude.Maybe Prelude.UTCTime)
describeDimensionKeysResponse_alignedEndTime :: Lens' DescribeDimensionKeysResponse (Maybe UTCTime)
describeDimensionKeysResponse_alignedEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeysResponse' {Maybe POSIX
alignedEndTime :: Maybe POSIX
$sel:alignedEndTime:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe POSIX
alignedEndTime} -> Maybe POSIX
alignedEndTime) (\s :: DescribeDimensionKeysResponse
s@DescribeDimensionKeysResponse' {} Maybe POSIX
a -> DescribeDimensionKeysResponse
s {$sel:alignedEndTime:DescribeDimensionKeysResponse' :: Maybe POSIX
alignedEndTime = Maybe POSIX
a} :: DescribeDimensionKeysResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The start time for the returned dimension keys, after alignment to a
-- granular boundary (as specified by @PeriodInSeconds@).
-- @AlignedStartTime@ will be less than or equal to the value of the
-- user-specified @StartTime@.
describeDimensionKeysResponse_alignedStartTime :: Lens.Lens' DescribeDimensionKeysResponse (Prelude.Maybe Prelude.UTCTime)
describeDimensionKeysResponse_alignedStartTime :: Lens' DescribeDimensionKeysResponse (Maybe UTCTime)
describeDimensionKeysResponse_alignedStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeysResponse' {Maybe POSIX
alignedStartTime :: Maybe POSIX
$sel:alignedStartTime:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe POSIX
alignedStartTime} -> Maybe POSIX
alignedStartTime) (\s :: DescribeDimensionKeysResponse
s@DescribeDimensionKeysResponse' {} Maybe POSIX
a -> DescribeDimensionKeysResponse
s {$sel:alignedStartTime:DescribeDimensionKeysResponse' :: Maybe POSIX
alignedStartTime = Maybe POSIX
a} :: DescribeDimensionKeysResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The dimension keys that were requested.
describeDimensionKeysResponse_keys :: Lens.Lens' DescribeDimensionKeysResponse (Prelude.Maybe [DimensionKeyDescription])
describeDimensionKeysResponse_keys :: Lens'
  DescribeDimensionKeysResponse (Maybe [DimensionKeyDescription])
describeDimensionKeysResponse_keys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeysResponse' {Maybe [DimensionKeyDescription]
keys :: Maybe [DimensionKeyDescription]
$sel:keys:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe [DimensionKeyDescription]
keys} -> Maybe [DimensionKeyDescription]
keys) (\s :: DescribeDimensionKeysResponse
s@DescribeDimensionKeysResponse' {} Maybe [DimensionKeyDescription]
a -> DescribeDimensionKeysResponse
s {$sel:keys:DescribeDimensionKeysResponse' :: Maybe [DimensionKeyDescription]
keys = Maybe [DimensionKeyDescription]
a} :: DescribeDimensionKeysResponse) 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

-- | A pagination token that indicates the response didn’t return all
-- available records because @MaxRecords@ was specified in the previous
-- request. To get the remaining records, specify @NextToken@ in a separate
-- request with this value.
describeDimensionKeysResponse_nextToken :: Lens.Lens' DescribeDimensionKeysResponse (Prelude.Maybe Prelude.Text)
describeDimensionKeysResponse_nextToken :: Lens' DescribeDimensionKeysResponse (Maybe Text)
describeDimensionKeysResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeysResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeDimensionKeysResponse
s@DescribeDimensionKeysResponse' {} Maybe Text
a -> DescribeDimensionKeysResponse
s {$sel:nextToken:DescribeDimensionKeysResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeDimensionKeysResponse)

-- | If @PartitionBy@ was present in the request, @PartitionKeys@ contains
-- the breakdown of dimension keys by the specified partitions.
describeDimensionKeysResponse_partitionKeys :: Lens.Lens' DescribeDimensionKeysResponse (Prelude.Maybe [ResponsePartitionKey])
describeDimensionKeysResponse_partitionKeys :: Lens' DescribeDimensionKeysResponse (Maybe [ResponsePartitionKey])
describeDimensionKeysResponse_partitionKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeysResponse' {Maybe [ResponsePartitionKey]
partitionKeys :: Maybe [ResponsePartitionKey]
$sel:partitionKeys:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe [ResponsePartitionKey]
partitionKeys} -> Maybe [ResponsePartitionKey]
partitionKeys) (\s :: DescribeDimensionKeysResponse
s@DescribeDimensionKeysResponse' {} Maybe [ResponsePartitionKey]
a -> DescribeDimensionKeysResponse
s {$sel:partitionKeys:DescribeDimensionKeysResponse' :: Maybe [ResponsePartitionKey]
partitionKeys = Maybe [ResponsePartitionKey]
a} :: DescribeDimensionKeysResponse) 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 response's http status code.
describeDimensionKeysResponse_httpStatus :: Lens.Lens' DescribeDimensionKeysResponse Prelude.Int
describeDimensionKeysResponse_httpStatus :: Lens' DescribeDimensionKeysResponse Int
describeDimensionKeysResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDimensionKeysResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeDimensionKeysResponse
s@DescribeDimensionKeysResponse' {} Int
a -> DescribeDimensionKeysResponse
s {$sel:httpStatus:DescribeDimensionKeysResponse' :: Int
httpStatus = Int
a} :: DescribeDimensionKeysResponse)

instance Prelude.NFData DescribeDimensionKeysResponse where
  rnf :: DescribeDimensionKeysResponse -> ()
rnf DescribeDimensionKeysResponse' {Int
Maybe [DimensionKeyDescription]
Maybe [ResponsePartitionKey]
Maybe Text
Maybe POSIX
httpStatus :: Int
partitionKeys :: Maybe [ResponsePartitionKey]
nextToken :: Maybe Text
keys :: Maybe [DimensionKeyDescription]
alignedStartTime :: Maybe POSIX
alignedEndTime :: Maybe POSIX
$sel:httpStatus:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Int
$sel:partitionKeys:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe [ResponsePartitionKey]
$sel:nextToken:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe Text
$sel:keys:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe [DimensionKeyDescription]
$sel:alignedStartTime:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe POSIX
$sel:alignedEndTime:DescribeDimensionKeysResponse' :: DescribeDimensionKeysResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
alignedEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
alignedStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DimensionKeyDescription]
keys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResponsePartitionKey]
partitionKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus