{-# 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.QuickSight.Types.KPIConfiguration
-- 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.QuickSight.Types.KPIConfiguration 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
import Amazonka.QuickSight.Types.KPIFieldWells
import Amazonka.QuickSight.Types.KPIOptions
import Amazonka.QuickSight.Types.KPISortConfiguration

-- | The configuration of a KPI visual.
--
-- /See:/ 'newKPIConfiguration' smart constructor.
data KPIConfiguration = KPIConfiguration'
  { -- | The field well configuration of a KPI visual.
    KPIConfiguration -> Maybe KPIFieldWells
fieldWells :: Prelude.Maybe KPIFieldWells,
    -- | The options that determine the presentation of a KPI visual.
    KPIConfiguration -> Maybe KPIOptions
kPIOptions :: Prelude.Maybe KPIOptions,
    -- | The sort configuration of a KPI visual.
    KPIConfiguration -> Maybe KPISortConfiguration
sortConfiguration :: Prelude.Maybe KPISortConfiguration
  }
  deriving (KPIConfiguration -> KPIConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KPIConfiguration -> KPIConfiguration -> Bool
$c/= :: KPIConfiguration -> KPIConfiguration -> Bool
== :: KPIConfiguration -> KPIConfiguration -> Bool
$c== :: KPIConfiguration -> KPIConfiguration -> Bool
Prelude.Eq, Int -> KPIConfiguration -> ShowS
[KPIConfiguration] -> ShowS
KPIConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KPIConfiguration] -> ShowS
$cshowList :: [KPIConfiguration] -> ShowS
show :: KPIConfiguration -> String
$cshow :: KPIConfiguration -> String
showsPrec :: Int -> KPIConfiguration -> ShowS
$cshowsPrec :: Int -> KPIConfiguration -> ShowS
Prelude.Show, forall x. Rep KPIConfiguration x -> KPIConfiguration
forall x. KPIConfiguration -> Rep KPIConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KPIConfiguration x -> KPIConfiguration
$cfrom :: forall x. KPIConfiguration -> Rep KPIConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'KPIConfiguration' 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:
--
-- 'fieldWells', 'kPIConfiguration_fieldWells' - The field well configuration of a KPI visual.
--
-- 'kPIOptions', 'kPIConfiguration_kPIOptions' - The options that determine the presentation of a KPI visual.
--
-- 'sortConfiguration', 'kPIConfiguration_sortConfiguration' - The sort configuration of a KPI visual.
newKPIConfiguration ::
  KPIConfiguration
newKPIConfiguration :: KPIConfiguration
newKPIConfiguration =
  KPIConfiguration'
    { $sel:fieldWells:KPIConfiguration' :: Maybe KPIFieldWells
fieldWells = forall a. Maybe a
Prelude.Nothing,
      $sel:kPIOptions:KPIConfiguration' :: Maybe KPIOptions
kPIOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:sortConfiguration:KPIConfiguration' :: Maybe KPISortConfiguration
sortConfiguration = forall a. Maybe a
Prelude.Nothing
    }

-- | The field well configuration of a KPI visual.
kPIConfiguration_fieldWells :: Lens.Lens' KPIConfiguration (Prelude.Maybe KPIFieldWells)
kPIConfiguration_fieldWells :: Lens' KPIConfiguration (Maybe KPIFieldWells)
kPIConfiguration_fieldWells = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KPIConfiguration' {Maybe KPIFieldWells
fieldWells :: Maybe KPIFieldWells
$sel:fieldWells:KPIConfiguration' :: KPIConfiguration -> Maybe KPIFieldWells
fieldWells} -> Maybe KPIFieldWells
fieldWells) (\s :: KPIConfiguration
s@KPIConfiguration' {} Maybe KPIFieldWells
a -> KPIConfiguration
s {$sel:fieldWells:KPIConfiguration' :: Maybe KPIFieldWells
fieldWells = Maybe KPIFieldWells
a} :: KPIConfiguration)

-- | The options that determine the presentation of a KPI visual.
kPIConfiguration_kPIOptions :: Lens.Lens' KPIConfiguration (Prelude.Maybe KPIOptions)
kPIConfiguration_kPIOptions :: Lens' KPIConfiguration (Maybe KPIOptions)
kPIConfiguration_kPIOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KPIConfiguration' {Maybe KPIOptions
kPIOptions :: Maybe KPIOptions
$sel:kPIOptions:KPIConfiguration' :: KPIConfiguration -> Maybe KPIOptions
kPIOptions} -> Maybe KPIOptions
kPIOptions) (\s :: KPIConfiguration
s@KPIConfiguration' {} Maybe KPIOptions
a -> KPIConfiguration
s {$sel:kPIOptions:KPIConfiguration' :: Maybe KPIOptions
kPIOptions = Maybe KPIOptions
a} :: KPIConfiguration)

-- | The sort configuration of a KPI visual.
kPIConfiguration_sortConfiguration :: Lens.Lens' KPIConfiguration (Prelude.Maybe KPISortConfiguration)
kPIConfiguration_sortConfiguration :: Lens' KPIConfiguration (Maybe KPISortConfiguration)
kPIConfiguration_sortConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\KPIConfiguration' {Maybe KPISortConfiguration
sortConfiguration :: Maybe KPISortConfiguration
$sel:sortConfiguration:KPIConfiguration' :: KPIConfiguration -> Maybe KPISortConfiguration
sortConfiguration} -> Maybe KPISortConfiguration
sortConfiguration) (\s :: KPIConfiguration
s@KPIConfiguration' {} Maybe KPISortConfiguration
a -> KPIConfiguration
s {$sel:sortConfiguration:KPIConfiguration' :: Maybe KPISortConfiguration
sortConfiguration = Maybe KPISortConfiguration
a} :: KPIConfiguration)

instance Data.FromJSON KPIConfiguration where
  parseJSON :: Value -> Parser KPIConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"KPIConfiguration"
      ( \Object
x ->
          Maybe KPIFieldWells
-> Maybe KPIOptions
-> Maybe KPISortConfiguration
-> KPIConfiguration
KPIConfiguration'
            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
"FieldWells")
            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
"KPIOptions")
            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
"SortConfiguration")
      )

instance Prelude.Hashable KPIConfiguration where
  hashWithSalt :: Int -> KPIConfiguration -> Int
hashWithSalt Int
_salt KPIConfiguration' {Maybe KPISortConfiguration
Maybe KPIFieldWells
Maybe KPIOptions
sortConfiguration :: Maybe KPISortConfiguration
kPIOptions :: Maybe KPIOptions
fieldWells :: Maybe KPIFieldWells
$sel:sortConfiguration:KPIConfiguration' :: KPIConfiguration -> Maybe KPISortConfiguration
$sel:kPIOptions:KPIConfiguration' :: KPIConfiguration -> Maybe KPIOptions
$sel:fieldWells:KPIConfiguration' :: KPIConfiguration -> Maybe KPIFieldWells
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KPIFieldWells
fieldWells
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KPIOptions
kPIOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe KPISortConfiguration
sortConfiguration

instance Prelude.NFData KPIConfiguration where
  rnf :: KPIConfiguration -> ()
rnf KPIConfiguration' {Maybe KPISortConfiguration
Maybe KPIFieldWells
Maybe KPIOptions
sortConfiguration :: Maybe KPISortConfiguration
kPIOptions :: Maybe KPIOptions
fieldWells :: Maybe KPIFieldWells
$sel:sortConfiguration:KPIConfiguration' :: KPIConfiguration -> Maybe KPISortConfiguration
$sel:kPIOptions:KPIConfiguration' :: KPIConfiguration -> Maybe KPIOptions
$sel:fieldWells:KPIConfiguration' :: KPIConfiguration -> Maybe KPIFieldWells
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe KPIFieldWells
fieldWells
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KPIOptions
kPIOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe KPISortConfiguration
sortConfiguration

instance Data.ToJSON KPIConfiguration where
  toJSON :: KPIConfiguration -> Value
toJSON KPIConfiguration' {Maybe KPISortConfiguration
Maybe KPIFieldWells
Maybe KPIOptions
sortConfiguration :: Maybe KPISortConfiguration
kPIOptions :: Maybe KPIOptions
fieldWells :: Maybe KPIFieldWells
$sel:sortConfiguration:KPIConfiguration' :: KPIConfiguration -> Maybe KPISortConfiguration
$sel:kPIOptions:KPIConfiguration' :: KPIConfiguration -> Maybe KPIOptions
$sel:fieldWells:KPIConfiguration' :: KPIConfiguration -> Maybe KPIFieldWells
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FieldWells" 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 KPIFieldWells
fieldWells,
            (Key
"KPIOptions" 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 KPIOptions
kPIOptions,
            (Key
"SortConfiguration" 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 KPISortConfiguration
sortConfiguration
          ]
      )