{-# 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.Pi.Types.DimensionKeyDetail
-- 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.Pi.Types.DimensionKeyDetail 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.DetailStatus
import qualified Amazonka.Prelude as Prelude

-- | An object that describes the details for a specified dimension.
--
-- /See:/ 'newDimensionKeyDetail' smart constructor.
data DimensionKeyDetail = DimensionKeyDetail'
  { -- | The full name of the dimension. The full name includes the group name
    -- and key name. The following values are valid:
    --
    -- -   @db.query.statement@ (Amazon DocumentDB)
    --
    -- -   @db.sql.statement@ (Amazon RDS and Aurora)
    DimensionKeyDetail -> Maybe Text
dimension :: Prelude.Maybe Prelude.Text,
    -- | The status of the dimension detail data. Possible values include the
    -- following:
    --
    -- -   @AVAILABLE@ - The dimension detail data is ready to be retrieved.
    --
    -- -   @PROCESSING@ - The dimension detail data isn\'t ready to be
    --     retrieved because more processing time is required. If the requested
    --     detail data has the status @PROCESSING@, Performance Insights
    --     returns the truncated query.
    --
    -- -   @UNAVAILABLE@ - The dimension detail data could not be collected
    --     successfully.
    DimensionKeyDetail -> Maybe DetailStatus
status :: Prelude.Maybe DetailStatus,
    -- | The value of the dimension detail data. Depending on the return status,
    -- this value is either the full or truncated SQL query for the following
    -- dimensions:
    --
    -- -   @db.query.statement@ (Amazon DocumentDB)
    --
    -- -   @db.sql.statement@ (Amazon RDS and Aurora)
    DimensionKeyDetail -> Maybe Text
value :: Prelude.Maybe Prelude.Text
  }
  deriving (DimensionKeyDetail -> DimensionKeyDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DimensionKeyDetail -> DimensionKeyDetail -> Bool
$c/= :: DimensionKeyDetail -> DimensionKeyDetail -> Bool
== :: DimensionKeyDetail -> DimensionKeyDetail -> Bool
$c== :: DimensionKeyDetail -> DimensionKeyDetail -> Bool
Prelude.Eq, ReadPrec [DimensionKeyDetail]
ReadPrec DimensionKeyDetail
Int -> ReadS DimensionKeyDetail
ReadS [DimensionKeyDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DimensionKeyDetail]
$creadListPrec :: ReadPrec [DimensionKeyDetail]
readPrec :: ReadPrec DimensionKeyDetail
$creadPrec :: ReadPrec DimensionKeyDetail
readList :: ReadS [DimensionKeyDetail]
$creadList :: ReadS [DimensionKeyDetail]
readsPrec :: Int -> ReadS DimensionKeyDetail
$creadsPrec :: Int -> ReadS DimensionKeyDetail
Prelude.Read, Int -> DimensionKeyDetail -> ShowS
[DimensionKeyDetail] -> ShowS
DimensionKeyDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DimensionKeyDetail] -> ShowS
$cshowList :: [DimensionKeyDetail] -> ShowS
show :: DimensionKeyDetail -> String
$cshow :: DimensionKeyDetail -> String
showsPrec :: Int -> DimensionKeyDetail -> ShowS
$cshowsPrec :: Int -> DimensionKeyDetail -> ShowS
Prelude.Show, forall x. Rep DimensionKeyDetail x -> DimensionKeyDetail
forall x. DimensionKeyDetail -> Rep DimensionKeyDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DimensionKeyDetail x -> DimensionKeyDetail
$cfrom :: forall x. DimensionKeyDetail -> Rep DimensionKeyDetail x
Prelude.Generic)

-- |
-- Create a value of 'DimensionKeyDetail' 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:
--
-- 'dimension', 'dimensionKeyDetail_dimension' - The full name of the dimension. The full name includes the group name
-- and key name. The following values are valid:
--
-- -   @db.query.statement@ (Amazon DocumentDB)
--
-- -   @db.sql.statement@ (Amazon RDS and Aurora)
--
-- 'status', 'dimensionKeyDetail_status' - The status of the dimension detail data. Possible values include the
-- following:
--
-- -   @AVAILABLE@ - The dimension detail data is ready to be retrieved.
--
-- -   @PROCESSING@ - The dimension detail data isn\'t ready to be
--     retrieved because more processing time is required. If the requested
--     detail data has the status @PROCESSING@, Performance Insights
--     returns the truncated query.
--
-- -   @UNAVAILABLE@ - The dimension detail data could not be collected
--     successfully.
--
-- 'value', 'dimensionKeyDetail_value' - The value of the dimension detail data. Depending on the return status,
-- this value is either the full or truncated SQL query for the following
-- dimensions:
--
-- -   @db.query.statement@ (Amazon DocumentDB)
--
-- -   @db.sql.statement@ (Amazon RDS and Aurora)
newDimensionKeyDetail ::
  DimensionKeyDetail
newDimensionKeyDetail :: DimensionKeyDetail
newDimensionKeyDetail =
  DimensionKeyDetail'
    { $sel:dimension:DimensionKeyDetail' :: Maybe Text
dimension = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DimensionKeyDetail' :: Maybe DetailStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:value:DimensionKeyDetail' :: Maybe Text
value = forall a. Maybe a
Prelude.Nothing
    }

-- | The full name of the dimension. The full name includes the group name
-- and key name. The following values are valid:
--
-- -   @db.query.statement@ (Amazon DocumentDB)
--
-- -   @db.sql.statement@ (Amazon RDS and Aurora)
dimensionKeyDetail_dimension :: Lens.Lens' DimensionKeyDetail (Prelude.Maybe Prelude.Text)
dimensionKeyDetail_dimension :: Lens' DimensionKeyDetail (Maybe Text)
dimensionKeyDetail_dimension = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DimensionKeyDetail' {Maybe Text
dimension :: Maybe Text
$sel:dimension:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe Text
dimension} -> Maybe Text
dimension) (\s :: DimensionKeyDetail
s@DimensionKeyDetail' {} Maybe Text
a -> DimensionKeyDetail
s {$sel:dimension:DimensionKeyDetail' :: Maybe Text
dimension = Maybe Text
a} :: DimensionKeyDetail)

-- | The status of the dimension detail data. Possible values include the
-- following:
--
-- -   @AVAILABLE@ - The dimension detail data is ready to be retrieved.
--
-- -   @PROCESSING@ - The dimension detail data isn\'t ready to be
--     retrieved because more processing time is required. If the requested
--     detail data has the status @PROCESSING@, Performance Insights
--     returns the truncated query.
--
-- -   @UNAVAILABLE@ - The dimension detail data could not be collected
--     successfully.
dimensionKeyDetail_status :: Lens.Lens' DimensionKeyDetail (Prelude.Maybe DetailStatus)
dimensionKeyDetail_status :: Lens' DimensionKeyDetail (Maybe DetailStatus)
dimensionKeyDetail_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DimensionKeyDetail' {Maybe DetailStatus
status :: Maybe DetailStatus
$sel:status:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe DetailStatus
status} -> Maybe DetailStatus
status) (\s :: DimensionKeyDetail
s@DimensionKeyDetail' {} Maybe DetailStatus
a -> DimensionKeyDetail
s {$sel:status:DimensionKeyDetail' :: Maybe DetailStatus
status = Maybe DetailStatus
a} :: DimensionKeyDetail)

-- | The value of the dimension detail data. Depending on the return status,
-- this value is either the full or truncated SQL query for the following
-- dimensions:
--
-- -   @db.query.statement@ (Amazon DocumentDB)
--
-- -   @db.sql.statement@ (Amazon RDS and Aurora)
dimensionKeyDetail_value :: Lens.Lens' DimensionKeyDetail (Prelude.Maybe Prelude.Text)
dimensionKeyDetail_value :: Lens' DimensionKeyDetail (Maybe Text)
dimensionKeyDetail_value = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DimensionKeyDetail' {Maybe Text
value :: Maybe Text
$sel:value:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe Text
value} -> Maybe Text
value) (\s :: DimensionKeyDetail
s@DimensionKeyDetail' {} Maybe Text
a -> DimensionKeyDetail
s {$sel:value:DimensionKeyDetail' :: Maybe Text
value = Maybe Text
a} :: DimensionKeyDetail)

instance Data.FromJSON DimensionKeyDetail where
  parseJSON :: Value -> Parser DimensionKeyDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DimensionKeyDetail"
      ( \Object
x ->
          Maybe Text
-> Maybe DetailStatus -> Maybe Text -> DimensionKeyDetail
DimensionKeyDetail'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Dimension")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Value")
      )

instance Prelude.Hashable DimensionKeyDetail where
  hashWithSalt :: Int -> DimensionKeyDetail -> Int
hashWithSalt Int
_salt DimensionKeyDetail' {Maybe Text
Maybe DetailStatus
value :: Maybe Text
status :: Maybe DetailStatus
dimension :: Maybe Text
$sel:value:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe Text
$sel:status:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe DetailStatus
$sel:dimension:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dimension
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DetailStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
value

instance Prelude.NFData DimensionKeyDetail where
  rnf :: DimensionKeyDetail -> ()
rnf DimensionKeyDetail' {Maybe Text
Maybe DetailStatus
value :: Maybe Text
status :: Maybe DetailStatus
dimension :: Maybe Text
$sel:value:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe Text
$sel:status:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe DetailStatus
$sel:dimension:DimensionKeyDetail' :: DimensionKeyDetail -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dimension
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DetailStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
value