{-# 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.DimensionGroup
-- 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.DimensionGroup where

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

-- | A logical grouping of Performance Insights metrics for a related subject
-- area. For example, the @db.sql@ dimension group consists of the
-- following dimensions:
--
-- -   @db.sql.id@ - The hash of a running SQL statement, generated by
--     Performance Insights.
--
-- -   @db.sql.db_id@ - Either the SQL ID generated by the database engine,
--     or a value generated by Performance Insights that begins with @pi-@.
--
-- -   @db.sql.statement@ - The full text of the SQL statement that is
--     running, for example, @SELECT * FROM employees@.
--
-- -   @db.sql_tokenized.id@ - The hash of the SQL digest generated by
--     Performance Insights.
--
-- Each response element returns a maximum of 500 bytes. For larger
-- elements, such as SQL statements, only the first 500 bytes are returned.
--
-- /See:/ 'newDimensionGroup' smart constructor.
data DimensionGroup = DimensionGroup'
  { -- | A list of specific dimensions from a dimension group. If this parameter
    -- is not present, then it signifies that all of the dimensions in the
    -- group were requested, or are present in the response.
    --
    -- Valid values for elements in the @Dimensions@ array are:
    --
    -- -   @db.application.name@ - The name of the application that is
    --     connected to the database. Valid values are as follows:
    --
    --     -   Aurora PostgreSQL
    --
    --     -   Amazon RDS PostgreSQL
    --
    --     -   Amazon DocumentDB
    --
    -- -   @db.host.id@ - The host ID of the connected client (all engines).
    --
    -- -   @db.host.name@ - The host name of the connected client (all
    --     engines).
    --
    -- -   @db.name@ - The name of the database to which the client is
    --     connected. Valid values are as follows:
    --
    --     -   Aurora PostgreSQL
    --
    --     -   Amazon RDS PostgreSQL
    --
    --     -   Aurora MySQL
    --
    --     -   Amazon RDS MySQL
    --
    --     -   Amazon RDS MariaDB
    --
    --     -   Amazon DocumentDB
    --
    -- -   @db.query.id@ - The query ID generated by Performance Insights (only
    --     Amazon DocumentDB).
    --
    -- -   @db.query.db_id@ - The query ID generated by the database (only
    --     Amazon DocumentDB).
    --
    -- -   @db.query.statement@ - The text of the query that is being run (only
    --     Amazon DocumentDB).
    --
    -- -   @db.query.tokenized_id@
    --
    -- -   @db.query.tokenized.id@ - The query digest ID generated by
    --     Performance Insights (only Amazon DocumentDB).
    --
    -- -   @db.query.tokenized.db_id@ - The query digest ID generated by
    --     Performance Insights (only Amazon DocumentDB).
    --
    -- -   @db.query.tokenized.statement@ - The text of the query digest (only
    --     Amazon DocumentDB).
    --
    -- -   @db.session_type.name@ - The type of the current session (only
    --     Amazon DocumentDB).
    --
    -- -   @db.sql.id@ - The hash of the full, non-tokenized SQL statement
    --     generated by Performance Insights (all engines except Amazon
    --     DocumentDB).
    --
    -- -   @db.sql.db_id@ - Either the SQL ID generated by the database engine,
    --     or a value generated by Performance Insights that begins with @pi-@
    --     (all engines except Amazon DocumentDB).
    --
    -- -   @db.sql.statement@ - The full text of the SQL statement that is
    --     running, as in @SELECT * FROM employees@ (all engines except Amazon
    --     DocumentDB)
    --
    -- -   @db.sql.tokenized_id@
    --
    -- -   @db.sql_tokenized.id@ - The hash of the SQL digest generated by
    --     Performance Insights (all engines except Amazon DocumentDB). In the
    --     console, @db.sql_tokenized.id@ is called the Support ID because
    --     Amazon Web Services Support can look at this data to help you
    --     troubleshoot database issues.
    --
    -- -   @db.sql_tokenized.db_id@ - Either the native database ID used to
    --     refer to the SQL statement, or a synthetic ID such as
    --     @pi-2372568224@ that Performance Insights generates if the native
    --     database ID isn\'t available (all engines except Amazon DocumentDB).
    --
    -- -   @db.sql_tokenized.statement@ - The text of the SQL digest, as in
    --     @SELECT * FROM employees WHERE employee_id = ?@ (all engines except
    --     Amazon DocumentDB)
    --
    -- -   @db.user.id@ - The ID of the user logged in to the database (all
    --     engines except Amazon DocumentDB).
    --
    -- -   @db.user.name@ - The name of the user logged in to the database (all
    --     engines except Amazon DocumentDB).
    --
    -- -   @db.wait_event.name@ - The event for which the backend is waiting
    --     (all engines except Amazon DocumentDB).
    --
    -- -   @db.wait_event.type@ - The type of event for which the backend is
    --     waiting (all engines except Amazon DocumentDB).
    --
    -- -   @db.wait_event_type.name@ - The name of the event type for which the
    --     backend is waiting (all engines except Amazon DocumentDB).
    --
    -- -   @db.wait_state.name@ - The event for which the backend is waiting
    --     (only Amazon DocumentDB).
    DimensionGroup -> Maybe (NonEmpty Text)
dimensions :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The maximum number of items to fetch for this dimension group.
    DimensionGroup -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The name of the dimension group. Valid values are as follows:
    --
    -- -   @db@ - The name of the database to which the client is connected.
    --     The following values are permitted:
    --
    --     -   Aurora PostgreSQL
    --
    --     -   Amazon RDS PostgreSQL
    --
    --     -   Aurora MySQL
    --
    --     -   Amazon RDS MySQL
    --
    --     -   Amazon RDS MariaDB
    --
    --     -   Amazon DocumentDB
    --
    -- -   @db.application@ - The name of the application that is connected to
    --     the database. The following values are permitted:
    --
    --     -   Aurora PostgreSQL
    --
    --     -   Amazon RDS PostgreSQL
    --
    --     -   Amazon DocumentDB
    --
    -- -   @db.host@ - The host name of the connected client (all engines).
    --
    -- -   @db.query@ - The query that is currently running (only Amazon
    --     DocumentDB).
    --
    -- -   @db.query_tokenized@ - The digest query (only Amazon DocumentDB).
    --
    -- -   @db.session_type@ - The type of the current session (only Aurora
    --     PostgreSQL and RDS PostgreSQL).
    --
    -- -   @db.sql@ - The text of the SQL statement that is currently running
    --     (all engines except Amazon DocumentDB).
    --
    -- -   @db.sql_tokenized@ - The SQL digest (all engines except Amazon
    --     DocumentDB).
    --
    -- -   @db.user@ - The user logged in to the database (all engines except
    --     Amazon DocumentDB).
    --
    -- -   @db.wait_event@ - The event for which the database backend is
    --     waiting (all engines except Amazon DocumentDB).
    --
    -- -   @db.wait_event_type@ - The type of event for which the database
    --     backend is waiting (all engines except Amazon DocumentDB).
    --
    -- -   @db.wait_state@ - The event for which the database backend is
    --     waiting (only Amazon DocumentDB).
    DimensionGroup -> Text
group' :: Prelude.Text
  }
  deriving (DimensionGroup -> DimensionGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DimensionGroup -> DimensionGroup -> Bool
$c/= :: DimensionGroup -> DimensionGroup -> Bool
== :: DimensionGroup -> DimensionGroup -> Bool
$c== :: DimensionGroup -> DimensionGroup -> Bool
Prelude.Eq, ReadPrec [DimensionGroup]
ReadPrec DimensionGroup
Int -> ReadS DimensionGroup
ReadS [DimensionGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DimensionGroup]
$creadListPrec :: ReadPrec [DimensionGroup]
readPrec :: ReadPrec DimensionGroup
$creadPrec :: ReadPrec DimensionGroup
readList :: ReadS [DimensionGroup]
$creadList :: ReadS [DimensionGroup]
readsPrec :: Int -> ReadS DimensionGroup
$creadsPrec :: Int -> ReadS DimensionGroup
Prelude.Read, Int -> DimensionGroup -> ShowS
[DimensionGroup] -> ShowS
DimensionGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DimensionGroup] -> ShowS
$cshowList :: [DimensionGroup] -> ShowS
show :: DimensionGroup -> String
$cshow :: DimensionGroup -> String
showsPrec :: Int -> DimensionGroup -> ShowS
$cshowsPrec :: Int -> DimensionGroup -> ShowS
Prelude.Show, forall x. Rep DimensionGroup x -> DimensionGroup
forall x. DimensionGroup -> Rep DimensionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DimensionGroup x -> DimensionGroup
$cfrom :: forall x. DimensionGroup -> Rep DimensionGroup x
Prelude.Generic)

-- |
-- Create a value of 'DimensionGroup' 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:
--
-- 'dimensions', 'dimensionGroup_dimensions' - A list of specific dimensions from a dimension group. If this parameter
-- is not present, then it signifies that all of the dimensions in the
-- group were requested, or are present in the response.
--
-- Valid values for elements in the @Dimensions@ array are:
--
-- -   @db.application.name@ - The name of the application that is
--     connected to the database. Valid values are as follows:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Amazon DocumentDB
--
-- -   @db.host.id@ - The host ID of the connected client (all engines).
--
-- -   @db.host.name@ - The host name of the connected client (all
--     engines).
--
-- -   @db.name@ - The name of the database to which the client is
--     connected. Valid values are as follows:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Aurora MySQL
--
--     -   Amazon RDS MySQL
--
--     -   Amazon RDS MariaDB
--
--     -   Amazon DocumentDB
--
-- -   @db.query.id@ - The query ID generated by Performance Insights (only
--     Amazon DocumentDB).
--
-- -   @db.query.db_id@ - The query ID generated by the database (only
--     Amazon DocumentDB).
--
-- -   @db.query.statement@ - The text of the query that is being run (only
--     Amazon DocumentDB).
--
-- -   @db.query.tokenized_id@
--
-- -   @db.query.tokenized.id@ - The query digest ID generated by
--     Performance Insights (only Amazon DocumentDB).
--
-- -   @db.query.tokenized.db_id@ - The query digest ID generated by
--     Performance Insights (only Amazon DocumentDB).
--
-- -   @db.query.tokenized.statement@ - The text of the query digest (only
--     Amazon DocumentDB).
--
-- -   @db.session_type.name@ - The type of the current session (only
--     Amazon DocumentDB).
--
-- -   @db.sql.id@ - The hash of the full, non-tokenized SQL statement
--     generated by Performance Insights (all engines except Amazon
--     DocumentDB).
--
-- -   @db.sql.db_id@ - Either the SQL ID generated by the database engine,
--     or a value generated by Performance Insights that begins with @pi-@
--     (all engines except Amazon DocumentDB).
--
-- -   @db.sql.statement@ - The full text of the SQL statement that is
--     running, as in @SELECT * FROM employees@ (all engines except Amazon
--     DocumentDB)
--
-- -   @db.sql.tokenized_id@
--
-- -   @db.sql_tokenized.id@ - The hash of the SQL digest generated by
--     Performance Insights (all engines except Amazon DocumentDB). In the
--     console, @db.sql_tokenized.id@ is called the Support ID because
--     Amazon Web Services Support can look at this data to help you
--     troubleshoot database issues.
--
-- -   @db.sql_tokenized.db_id@ - Either the native database ID used to
--     refer to the SQL statement, or a synthetic ID such as
--     @pi-2372568224@ that Performance Insights generates if the native
--     database ID isn\'t available (all engines except Amazon DocumentDB).
--
-- -   @db.sql_tokenized.statement@ - The text of the SQL digest, as in
--     @SELECT * FROM employees WHERE employee_id = ?@ (all engines except
--     Amazon DocumentDB)
--
-- -   @db.user.id@ - The ID of the user logged in to the database (all
--     engines except Amazon DocumentDB).
--
-- -   @db.user.name@ - The name of the user logged in to the database (all
--     engines except Amazon DocumentDB).
--
-- -   @db.wait_event.name@ - The event for which the backend is waiting
--     (all engines except Amazon DocumentDB).
--
-- -   @db.wait_event.type@ - The type of event for which the backend is
--     waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_event_type.name@ - The name of the event type for which the
--     backend is waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_state.name@ - The event for which the backend is waiting
--     (only Amazon DocumentDB).
--
-- 'limit', 'dimensionGroup_limit' - The maximum number of items to fetch for this dimension group.
--
-- 'group'', 'dimensionGroup_group' - The name of the dimension group. Valid values are as follows:
--
-- -   @db@ - The name of the database to which the client is connected.
--     The following values are permitted:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Aurora MySQL
--
--     -   Amazon RDS MySQL
--
--     -   Amazon RDS MariaDB
--
--     -   Amazon DocumentDB
--
-- -   @db.application@ - The name of the application that is connected to
--     the database. The following values are permitted:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Amazon DocumentDB
--
-- -   @db.host@ - The host name of the connected client (all engines).
--
-- -   @db.query@ - The query that is currently running (only Amazon
--     DocumentDB).
--
-- -   @db.query_tokenized@ - The digest query (only Amazon DocumentDB).
--
-- -   @db.session_type@ - The type of the current session (only Aurora
--     PostgreSQL and RDS PostgreSQL).
--
-- -   @db.sql@ - The text of the SQL statement that is currently running
--     (all engines except Amazon DocumentDB).
--
-- -   @db.sql_tokenized@ - The SQL digest (all engines except Amazon
--     DocumentDB).
--
-- -   @db.user@ - The user logged in to the database (all engines except
--     Amazon DocumentDB).
--
-- -   @db.wait_event@ - The event for which the database backend is
--     waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_event_type@ - The type of event for which the database
--     backend is waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_state@ - The event for which the database backend is
--     waiting (only Amazon DocumentDB).
newDimensionGroup ::
  -- | 'group''
  Prelude.Text ->
  DimensionGroup
newDimensionGroup :: Text -> DimensionGroup
newDimensionGroup Text
pGroup_ =
  DimensionGroup'
    { $sel:dimensions:DimensionGroup' :: Maybe (NonEmpty Text)
dimensions = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:DimensionGroup' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:group':DimensionGroup' :: Text
group' = Text
pGroup_
    }

-- | A list of specific dimensions from a dimension group. If this parameter
-- is not present, then it signifies that all of the dimensions in the
-- group were requested, or are present in the response.
--
-- Valid values for elements in the @Dimensions@ array are:
--
-- -   @db.application.name@ - The name of the application that is
--     connected to the database. Valid values are as follows:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Amazon DocumentDB
--
-- -   @db.host.id@ - The host ID of the connected client (all engines).
--
-- -   @db.host.name@ - The host name of the connected client (all
--     engines).
--
-- -   @db.name@ - The name of the database to which the client is
--     connected. Valid values are as follows:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Aurora MySQL
--
--     -   Amazon RDS MySQL
--
--     -   Amazon RDS MariaDB
--
--     -   Amazon DocumentDB
--
-- -   @db.query.id@ - The query ID generated by Performance Insights (only
--     Amazon DocumentDB).
--
-- -   @db.query.db_id@ - The query ID generated by the database (only
--     Amazon DocumentDB).
--
-- -   @db.query.statement@ - The text of the query that is being run (only
--     Amazon DocumentDB).
--
-- -   @db.query.tokenized_id@
--
-- -   @db.query.tokenized.id@ - The query digest ID generated by
--     Performance Insights (only Amazon DocumentDB).
--
-- -   @db.query.tokenized.db_id@ - The query digest ID generated by
--     Performance Insights (only Amazon DocumentDB).
--
-- -   @db.query.tokenized.statement@ - The text of the query digest (only
--     Amazon DocumentDB).
--
-- -   @db.session_type.name@ - The type of the current session (only
--     Amazon DocumentDB).
--
-- -   @db.sql.id@ - The hash of the full, non-tokenized SQL statement
--     generated by Performance Insights (all engines except Amazon
--     DocumentDB).
--
-- -   @db.sql.db_id@ - Either the SQL ID generated by the database engine,
--     or a value generated by Performance Insights that begins with @pi-@
--     (all engines except Amazon DocumentDB).
--
-- -   @db.sql.statement@ - The full text of the SQL statement that is
--     running, as in @SELECT * FROM employees@ (all engines except Amazon
--     DocumentDB)
--
-- -   @db.sql.tokenized_id@
--
-- -   @db.sql_tokenized.id@ - The hash of the SQL digest generated by
--     Performance Insights (all engines except Amazon DocumentDB). In the
--     console, @db.sql_tokenized.id@ is called the Support ID because
--     Amazon Web Services Support can look at this data to help you
--     troubleshoot database issues.
--
-- -   @db.sql_tokenized.db_id@ - Either the native database ID used to
--     refer to the SQL statement, or a synthetic ID such as
--     @pi-2372568224@ that Performance Insights generates if the native
--     database ID isn\'t available (all engines except Amazon DocumentDB).
--
-- -   @db.sql_tokenized.statement@ - The text of the SQL digest, as in
--     @SELECT * FROM employees WHERE employee_id = ?@ (all engines except
--     Amazon DocumentDB)
--
-- -   @db.user.id@ - The ID of the user logged in to the database (all
--     engines except Amazon DocumentDB).
--
-- -   @db.user.name@ - The name of the user logged in to the database (all
--     engines except Amazon DocumentDB).
--
-- -   @db.wait_event.name@ - The event for which the backend is waiting
--     (all engines except Amazon DocumentDB).
--
-- -   @db.wait_event.type@ - The type of event for which the backend is
--     waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_event_type.name@ - The name of the event type for which the
--     backend is waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_state.name@ - The event for which the backend is waiting
--     (only Amazon DocumentDB).
dimensionGroup_dimensions :: Lens.Lens' DimensionGroup (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
dimensionGroup_dimensions :: Lens' DimensionGroup (Maybe (NonEmpty Text))
dimensionGroup_dimensions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DimensionGroup' {Maybe (NonEmpty Text)
dimensions :: Maybe (NonEmpty Text)
$sel:dimensions:DimensionGroup' :: DimensionGroup -> Maybe (NonEmpty Text)
dimensions} -> Maybe (NonEmpty Text)
dimensions) (\s :: DimensionGroup
s@DimensionGroup' {} Maybe (NonEmpty Text)
a -> DimensionGroup
s {$sel:dimensions:DimensionGroup' :: Maybe (NonEmpty Text)
dimensions = Maybe (NonEmpty Text)
a} :: DimensionGroup) 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 fetch for this dimension group.
dimensionGroup_limit :: Lens.Lens' DimensionGroup (Prelude.Maybe Prelude.Natural)
dimensionGroup_limit :: Lens' DimensionGroup (Maybe Natural)
dimensionGroup_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DimensionGroup' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DimensionGroup' :: DimensionGroup -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DimensionGroup
s@DimensionGroup' {} Maybe Natural
a -> DimensionGroup
s {$sel:limit:DimensionGroup' :: Maybe Natural
limit = Maybe Natural
a} :: DimensionGroup)

-- | The name of the dimension group. Valid values are as follows:
--
-- -   @db@ - The name of the database to which the client is connected.
--     The following values are permitted:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Aurora MySQL
--
--     -   Amazon RDS MySQL
--
--     -   Amazon RDS MariaDB
--
--     -   Amazon DocumentDB
--
-- -   @db.application@ - The name of the application that is connected to
--     the database. The following values are permitted:
--
--     -   Aurora PostgreSQL
--
--     -   Amazon RDS PostgreSQL
--
--     -   Amazon DocumentDB
--
-- -   @db.host@ - The host name of the connected client (all engines).
--
-- -   @db.query@ - The query that is currently running (only Amazon
--     DocumentDB).
--
-- -   @db.query_tokenized@ - The digest query (only Amazon DocumentDB).
--
-- -   @db.session_type@ - The type of the current session (only Aurora
--     PostgreSQL and RDS PostgreSQL).
--
-- -   @db.sql@ - The text of the SQL statement that is currently running
--     (all engines except Amazon DocumentDB).
--
-- -   @db.sql_tokenized@ - The SQL digest (all engines except Amazon
--     DocumentDB).
--
-- -   @db.user@ - The user logged in to the database (all engines except
--     Amazon DocumentDB).
--
-- -   @db.wait_event@ - The event for which the database backend is
--     waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_event_type@ - The type of event for which the database
--     backend is waiting (all engines except Amazon DocumentDB).
--
-- -   @db.wait_state@ - The event for which the database backend is
--     waiting (only Amazon DocumentDB).
dimensionGroup_group :: Lens.Lens' DimensionGroup Prelude.Text
dimensionGroup_group :: Lens' DimensionGroup Text
dimensionGroup_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DimensionGroup' {Text
group' :: Text
$sel:group':DimensionGroup' :: DimensionGroup -> Text
group'} -> Text
group') (\s :: DimensionGroup
s@DimensionGroup' {} Text
a -> DimensionGroup
s {$sel:group':DimensionGroup' :: Text
group' = Text
a} :: DimensionGroup)

instance Prelude.Hashable DimensionGroup where
  hashWithSalt :: Int -> DimensionGroup -> Int
hashWithSalt Int
_salt DimensionGroup' {Maybe Natural
Maybe (NonEmpty Text)
Text
group' :: Text
limit :: Maybe Natural
dimensions :: Maybe (NonEmpty Text)
$sel:group':DimensionGroup' :: DimensionGroup -> Text
$sel:limit:DimensionGroup' :: DimensionGroup -> Maybe Natural
$sel:dimensions:DimensionGroup' :: DimensionGroup -> Maybe (NonEmpty Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
dimensions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
group'

instance Prelude.NFData DimensionGroup where
  rnf :: DimensionGroup -> ()
rnf DimensionGroup' {Maybe Natural
Maybe (NonEmpty Text)
Text
group' :: Text
limit :: Maybe Natural
dimensions :: Maybe (NonEmpty Text)
$sel:group':DimensionGroup' :: DimensionGroup -> Text
$sel:limit:DimensionGroup' :: DimensionGroup -> Maybe Natural
$sel:dimensions:DimensionGroup' :: DimensionGroup -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
dimensions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
group'

instance Data.ToJSON DimensionGroup where
  toJSON :: DimensionGroup -> Value
toJSON DimensionGroup' {Maybe Natural
Maybe (NonEmpty Text)
Text
group' :: Text
limit :: Maybe Natural
dimensions :: Maybe (NonEmpty Text)
$sel:group':DimensionGroup' :: DimensionGroup -> Text
$sel:limit:DimensionGroup' :: DimensionGroup -> Maybe Natural
$sel:dimensions:DimensionGroup' :: DimensionGroup -> Maybe (NonEmpty Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Dimensions" 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)
dimensions,
            (Key
"Limit" 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
limit,
            forall a. a -> Maybe a
Prelude.Just (Key
"Group" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
group')
          ]
      )