{-# 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 #-}
module Amazonka.QuickSight.Types.ThemeConfiguration 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.DataColorPalette
import Amazonka.QuickSight.Types.SheetStyle
import Amazonka.QuickSight.Types.Typography
import Amazonka.QuickSight.Types.UIColorPalette
data ThemeConfiguration = ThemeConfiguration'
  { 
    ThemeConfiguration -> Maybe DataColorPalette
dataColorPalette :: Prelude.Maybe DataColorPalette,
    
    ThemeConfiguration -> Maybe SheetStyle
sheet :: Prelude.Maybe SheetStyle,
    ThemeConfiguration -> Maybe Typography
typography :: Prelude.Maybe Typography,
    
    
    ThemeConfiguration -> Maybe UIColorPalette
uIColorPalette :: Prelude.Maybe UIColorPalette
  }
  deriving (ThemeConfiguration -> ThemeConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThemeConfiguration -> ThemeConfiguration -> Bool
$c/= :: ThemeConfiguration -> ThemeConfiguration -> Bool
== :: ThemeConfiguration -> ThemeConfiguration -> Bool
$c== :: ThemeConfiguration -> ThemeConfiguration -> Bool
Prelude.Eq, ReadPrec [ThemeConfiguration]
ReadPrec ThemeConfiguration
Int -> ReadS ThemeConfiguration
ReadS [ThemeConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ThemeConfiguration]
$creadListPrec :: ReadPrec [ThemeConfiguration]
readPrec :: ReadPrec ThemeConfiguration
$creadPrec :: ReadPrec ThemeConfiguration
readList :: ReadS [ThemeConfiguration]
$creadList :: ReadS [ThemeConfiguration]
readsPrec :: Int -> ReadS ThemeConfiguration
$creadsPrec :: Int -> ReadS ThemeConfiguration
Prelude.Read, Int -> ThemeConfiguration -> ShowS
[ThemeConfiguration] -> ShowS
ThemeConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ThemeConfiguration] -> ShowS
$cshowList :: [ThemeConfiguration] -> ShowS
show :: ThemeConfiguration -> String
$cshow :: ThemeConfiguration -> String
showsPrec :: Int -> ThemeConfiguration -> ShowS
$cshowsPrec :: Int -> ThemeConfiguration -> ShowS
Prelude.Show, forall x. Rep ThemeConfiguration x -> ThemeConfiguration
forall x. ThemeConfiguration -> Rep ThemeConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ThemeConfiguration x -> ThemeConfiguration
$cfrom :: forall x. ThemeConfiguration -> Rep ThemeConfiguration x
Prelude.Generic)
newThemeConfiguration ::
  ThemeConfiguration
newThemeConfiguration :: ThemeConfiguration
newThemeConfiguration =
  ThemeConfiguration'
    { $sel:dataColorPalette:ThemeConfiguration' :: Maybe DataColorPalette
dataColorPalette =
        forall a. Maybe a
Prelude.Nothing,
      $sel:sheet:ThemeConfiguration' :: Maybe SheetStyle
sheet = forall a. Maybe a
Prelude.Nothing,
      $sel:typography:ThemeConfiguration' :: Maybe Typography
typography = forall a. Maybe a
Prelude.Nothing,
      $sel:uIColorPalette:ThemeConfiguration' :: Maybe UIColorPalette
uIColorPalette = forall a. Maybe a
Prelude.Nothing
    }
themeConfiguration_dataColorPalette :: Lens.Lens' ThemeConfiguration (Prelude.Maybe DataColorPalette)
themeConfiguration_dataColorPalette :: Lens' ThemeConfiguration (Maybe DataColorPalette)
themeConfiguration_dataColorPalette = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ThemeConfiguration' {Maybe DataColorPalette
dataColorPalette :: Maybe DataColorPalette
$sel:dataColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe DataColorPalette
dataColorPalette} -> Maybe DataColorPalette
dataColorPalette) (\s :: ThemeConfiguration
s@ThemeConfiguration' {} Maybe DataColorPalette
a -> ThemeConfiguration
s {$sel:dataColorPalette:ThemeConfiguration' :: Maybe DataColorPalette
dataColorPalette = Maybe DataColorPalette
a} :: ThemeConfiguration)
themeConfiguration_sheet :: Lens.Lens' ThemeConfiguration (Prelude.Maybe SheetStyle)
themeConfiguration_sheet :: Lens' ThemeConfiguration (Maybe SheetStyle)
themeConfiguration_sheet = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ThemeConfiguration' {Maybe SheetStyle
sheet :: Maybe SheetStyle
$sel:sheet:ThemeConfiguration' :: ThemeConfiguration -> Maybe SheetStyle
sheet} -> Maybe SheetStyle
sheet) (\s :: ThemeConfiguration
s@ThemeConfiguration' {} Maybe SheetStyle
a -> ThemeConfiguration
s {$sel:sheet:ThemeConfiguration' :: Maybe SheetStyle
sheet = Maybe SheetStyle
a} :: ThemeConfiguration)
themeConfiguration_typography :: Lens.Lens' ThemeConfiguration (Prelude.Maybe Typography)
themeConfiguration_typography :: Lens' ThemeConfiguration (Maybe Typography)
themeConfiguration_typography = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ThemeConfiguration' {Maybe Typography
typography :: Maybe Typography
$sel:typography:ThemeConfiguration' :: ThemeConfiguration -> Maybe Typography
typography} -> Maybe Typography
typography) (\s :: ThemeConfiguration
s@ThemeConfiguration' {} Maybe Typography
a -> ThemeConfiguration
s {$sel:typography:ThemeConfiguration' :: Maybe Typography
typography = Maybe Typography
a} :: ThemeConfiguration)
themeConfiguration_uIColorPalette :: Lens.Lens' ThemeConfiguration (Prelude.Maybe UIColorPalette)
themeConfiguration_uIColorPalette :: Lens' ThemeConfiguration (Maybe UIColorPalette)
themeConfiguration_uIColorPalette = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ThemeConfiguration' {Maybe UIColorPalette
uIColorPalette :: Maybe UIColorPalette
$sel:uIColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe UIColorPalette
uIColorPalette} -> Maybe UIColorPalette
uIColorPalette) (\s :: ThemeConfiguration
s@ThemeConfiguration' {} Maybe UIColorPalette
a -> ThemeConfiguration
s {$sel:uIColorPalette:ThemeConfiguration' :: Maybe UIColorPalette
uIColorPalette = Maybe UIColorPalette
a} :: ThemeConfiguration)
instance Data.FromJSON ThemeConfiguration where
  parseJSON :: Value -> Parser ThemeConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ThemeConfiguration"
      ( \Object
x ->
          Maybe DataColorPalette
-> Maybe SheetStyle
-> Maybe Typography
-> Maybe UIColorPalette
-> ThemeConfiguration
ThemeConfiguration'
            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
"DataColorPalette")
            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
"Sheet")
            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
"Typography")
            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
"UIColorPalette")
      )
instance Prelude.Hashable ThemeConfiguration where
  hashWithSalt :: Int -> ThemeConfiguration -> Int
hashWithSalt Int
_salt ThemeConfiguration' {Maybe DataColorPalette
Maybe SheetStyle
Maybe Typography
Maybe UIColorPalette
uIColorPalette :: Maybe UIColorPalette
typography :: Maybe Typography
sheet :: Maybe SheetStyle
dataColorPalette :: Maybe DataColorPalette
$sel:uIColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe UIColorPalette
$sel:typography:ThemeConfiguration' :: ThemeConfiguration -> Maybe Typography
$sel:sheet:ThemeConfiguration' :: ThemeConfiguration -> Maybe SheetStyle
$sel:dataColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe DataColorPalette
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataColorPalette
dataColorPalette
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SheetStyle
sheet
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Typography
typography
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UIColorPalette
uIColorPalette
instance Prelude.NFData ThemeConfiguration where
  rnf :: ThemeConfiguration -> ()
rnf ThemeConfiguration' {Maybe DataColorPalette
Maybe SheetStyle
Maybe Typography
Maybe UIColorPalette
uIColorPalette :: Maybe UIColorPalette
typography :: Maybe Typography
sheet :: Maybe SheetStyle
dataColorPalette :: Maybe DataColorPalette
$sel:uIColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe UIColorPalette
$sel:typography:ThemeConfiguration' :: ThemeConfiguration -> Maybe Typography
$sel:sheet:ThemeConfiguration' :: ThemeConfiguration -> Maybe SheetStyle
$sel:dataColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe DataColorPalette
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DataColorPalette
dataColorPalette
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SheetStyle
sheet
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Typography
typography
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UIColorPalette
uIColorPalette
instance Data.ToJSON ThemeConfiguration where
  toJSON :: ThemeConfiguration -> Value
toJSON ThemeConfiguration' {Maybe DataColorPalette
Maybe SheetStyle
Maybe Typography
Maybe UIColorPalette
uIColorPalette :: Maybe UIColorPalette
typography :: Maybe Typography
sheet :: Maybe SheetStyle
dataColorPalette :: Maybe DataColorPalette
$sel:uIColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe UIColorPalette
$sel:typography:ThemeConfiguration' :: ThemeConfiguration -> Maybe Typography
$sel:sheet:ThemeConfiguration' :: ThemeConfiguration -> Maybe SheetStyle
$sel:dataColorPalette:ThemeConfiguration' :: ThemeConfiguration -> Maybe DataColorPalette
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DataColorPalette" 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 DataColorPalette
dataColorPalette,
            (Key
"Sheet" 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 SheetStyle
sheet,
            (Key
"Typography" 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 Typography
typography,
            (Key
"UIColorPalette" 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 UIColorPalette
uIColorPalette
          ]
      )