{-# 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.TreeMapVisual
-- 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.TreeMapVisual 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.ColumnHierarchy
import Amazonka.QuickSight.Types.TreeMapConfiguration
import Amazonka.QuickSight.Types.VisualCustomAction
import Amazonka.QuickSight.Types.VisualSubtitleLabelOptions
import Amazonka.QuickSight.Types.VisualTitleLabelOptions

-- | A tree map.
--
-- For more information, see
-- <https://docs.aws.amazon.com/quicksight/latest/user/tree-map.html Using tree maps>
-- in the /Amazon QuickSight User Guide/.
--
-- /See:/ 'newTreeMapVisual' smart constructor.
data TreeMapVisual = TreeMapVisual'
  { -- | The list of custom actions that are configured for a visual.
    TreeMapVisual -> Maybe [VisualCustomAction]
actions :: Prelude.Maybe [VisualCustomAction],
    -- | The configuration settings of the visual.
    TreeMapVisual -> Maybe TreeMapConfiguration
chartConfiguration :: Prelude.Maybe TreeMapConfiguration,
    -- | The column hierarchy that is used during drill-downs and drill-ups.
    TreeMapVisual -> Maybe [ColumnHierarchy]
columnHierarchies :: Prelude.Maybe [ColumnHierarchy],
    -- | The subtitle that is displayed on the visual.
    TreeMapVisual -> Maybe VisualSubtitleLabelOptions
subtitle :: Prelude.Maybe VisualSubtitleLabelOptions,
    -- | The title that is displayed on the visual.
    TreeMapVisual -> Maybe VisualTitleLabelOptions
title :: Prelude.Maybe VisualTitleLabelOptions,
    -- | The unique identifier of a visual. This identifier must be unique within
    -- the context of a dashboard, template, or analysis. Two dashboards,
    -- analyses, or templates can have visuals with the same identifiers..
    TreeMapVisual -> Text
visualId :: Prelude.Text
  }
  deriving (TreeMapVisual -> TreeMapVisual -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TreeMapVisual -> TreeMapVisual -> Bool
$c/= :: TreeMapVisual -> TreeMapVisual -> Bool
== :: TreeMapVisual -> TreeMapVisual -> Bool
$c== :: TreeMapVisual -> TreeMapVisual -> Bool
Prelude.Eq, Int -> TreeMapVisual -> ShowS
[TreeMapVisual] -> ShowS
TreeMapVisual -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TreeMapVisual] -> ShowS
$cshowList :: [TreeMapVisual] -> ShowS
show :: TreeMapVisual -> String
$cshow :: TreeMapVisual -> String
showsPrec :: Int -> TreeMapVisual -> ShowS
$cshowsPrec :: Int -> TreeMapVisual -> ShowS
Prelude.Show, forall x. Rep TreeMapVisual x -> TreeMapVisual
forall x. TreeMapVisual -> Rep TreeMapVisual x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TreeMapVisual x -> TreeMapVisual
$cfrom :: forall x. TreeMapVisual -> Rep TreeMapVisual x
Prelude.Generic)

-- |
-- Create a value of 'TreeMapVisual' 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:
--
-- 'actions', 'treeMapVisual_actions' - The list of custom actions that are configured for a visual.
--
-- 'chartConfiguration', 'treeMapVisual_chartConfiguration' - The configuration settings of the visual.
--
-- 'columnHierarchies', 'treeMapVisual_columnHierarchies' - The column hierarchy that is used during drill-downs and drill-ups.
--
-- 'subtitle', 'treeMapVisual_subtitle' - The subtitle that is displayed on the visual.
--
-- 'title', 'treeMapVisual_title' - The title that is displayed on the visual.
--
-- 'visualId', 'treeMapVisual_visualId' - The unique identifier of a visual. This identifier must be unique within
-- the context of a dashboard, template, or analysis. Two dashboards,
-- analyses, or templates can have visuals with the same identifiers..
newTreeMapVisual ::
  -- | 'visualId'
  Prelude.Text ->
  TreeMapVisual
newTreeMapVisual :: Text -> TreeMapVisual
newTreeMapVisual Text
pVisualId_ =
  TreeMapVisual'
    { $sel:actions:TreeMapVisual' :: Maybe [VisualCustomAction]
actions = forall a. Maybe a
Prelude.Nothing,
      $sel:chartConfiguration:TreeMapVisual' :: Maybe TreeMapConfiguration
chartConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:columnHierarchies:TreeMapVisual' :: Maybe [ColumnHierarchy]
columnHierarchies = forall a. Maybe a
Prelude.Nothing,
      $sel:subtitle:TreeMapVisual' :: Maybe VisualSubtitleLabelOptions
subtitle = forall a. Maybe a
Prelude.Nothing,
      $sel:title:TreeMapVisual' :: Maybe VisualTitleLabelOptions
title = forall a. Maybe a
Prelude.Nothing,
      $sel:visualId:TreeMapVisual' :: Text
visualId = Text
pVisualId_
    }

-- | The list of custom actions that are configured for a visual.
treeMapVisual_actions :: Lens.Lens' TreeMapVisual (Prelude.Maybe [VisualCustomAction])
treeMapVisual_actions :: Lens' TreeMapVisual (Maybe [VisualCustomAction])
treeMapVisual_actions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TreeMapVisual' {Maybe [VisualCustomAction]
actions :: Maybe [VisualCustomAction]
$sel:actions:TreeMapVisual' :: TreeMapVisual -> Maybe [VisualCustomAction]
actions} -> Maybe [VisualCustomAction]
actions) (\s :: TreeMapVisual
s@TreeMapVisual' {} Maybe [VisualCustomAction]
a -> TreeMapVisual
s {$sel:actions:TreeMapVisual' :: Maybe [VisualCustomAction]
actions = Maybe [VisualCustomAction]
a} :: TreeMapVisual) 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 configuration settings of the visual.
treeMapVisual_chartConfiguration :: Lens.Lens' TreeMapVisual (Prelude.Maybe TreeMapConfiguration)
treeMapVisual_chartConfiguration :: Lens' TreeMapVisual (Maybe TreeMapConfiguration)
treeMapVisual_chartConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TreeMapVisual' {Maybe TreeMapConfiguration
chartConfiguration :: Maybe TreeMapConfiguration
$sel:chartConfiguration:TreeMapVisual' :: TreeMapVisual -> Maybe TreeMapConfiguration
chartConfiguration} -> Maybe TreeMapConfiguration
chartConfiguration) (\s :: TreeMapVisual
s@TreeMapVisual' {} Maybe TreeMapConfiguration
a -> TreeMapVisual
s {$sel:chartConfiguration:TreeMapVisual' :: Maybe TreeMapConfiguration
chartConfiguration = Maybe TreeMapConfiguration
a} :: TreeMapVisual)

-- | The column hierarchy that is used during drill-downs and drill-ups.
treeMapVisual_columnHierarchies :: Lens.Lens' TreeMapVisual (Prelude.Maybe [ColumnHierarchy])
treeMapVisual_columnHierarchies :: Lens' TreeMapVisual (Maybe [ColumnHierarchy])
treeMapVisual_columnHierarchies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TreeMapVisual' {Maybe [ColumnHierarchy]
columnHierarchies :: Maybe [ColumnHierarchy]
$sel:columnHierarchies:TreeMapVisual' :: TreeMapVisual -> Maybe [ColumnHierarchy]
columnHierarchies} -> Maybe [ColumnHierarchy]
columnHierarchies) (\s :: TreeMapVisual
s@TreeMapVisual' {} Maybe [ColumnHierarchy]
a -> TreeMapVisual
s {$sel:columnHierarchies:TreeMapVisual' :: Maybe [ColumnHierarchy]
columnHierarchies = Maybe [ColumnHierarchy]
a} :: TreeMapVisual) 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 subtitle that is displayed on the visual.
treeMapVisual_subtitle :: Lens.Lens' TreeMapVisual (Prelude.Maybe VisualSubtitleLabelOptions)
treeMapVisual_subtitle :: Lens' TreeMapVisual (Maybe VisualSubtitleLabelOptions)
treeMapVisual_subtitle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TreeMapVisual' {Maybe VisualSubtitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
$sel:subtitle:TreeMapVisual' :: TreeMapVisual -> Maybe VisualSubtitleLabelOptions
subtitle} -> Maybe VisualSubtitleLabelOptions
subtitle) (\s :: TreeMapVisual
s@TreeMapVisual' {} Maybe VisualSubtitleLabelOptions
a -> TreeMapVisual
s {$sel:subtitle:TreeMapVisual' :: Maybe VisualSubtitleLabelOptions
subtitle = Maybe VisualSubtitleLabelOptions
a} :: TreeMapVisual)

-- | The title that is displayed on the visual.
treeMapVisual_title :: Lens.Lens' TreeMapVisual (Prelude.Maybe VisualTitleLabelOptions)
treeMapVisual_title :: Lens' TreeMapVisual (Maybe VisualTitleLabelOptions)
treeMapVisual_title = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TreeMapVisual' {Maybe VisualTitleLabelOptions
title :: Maybe VisualTitleLabelOptions
$sel:title:TreeMapVisual' :: TreeMapVisual -> Maybe VisualTitleLabelOptions
title} -> Maybe VisualTitleLabelOptions
title) (\s :: TreeMapVisual
s@TreeMapVisual' {} Maybe VisualTitleLabelOptions
a -> TreeMapVisual
s {$sel:title:TreeMapVisual' :: Maybe VisualTitleLabelOptions
title = Maybe VisualTitleLabelOptions
a} :: TreeMapVisual)

-- | The unique identifier of a visual. This identifier must be unique within
-- the context of a dashboard, template, or analysis. Two dashboards,
-- analyses, or templates can have visuals with the same identifiers..
treeMapVisual_visualId :: Lens.Lens' TreeMapVisual Prelude.Text
treeMapVisual_visualId :: Lens' TreeMapVisual Text
treeMapVisual_visualId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TreeMapVisual' {Text
visualId :: Text
$sel:visualId:TreeMapVisual' :: TreeMapVisual -> Text
visualId} -> Text
visualId) (\s :: TreeMapVisual
s@TreeMapVisual' {} Text
a -> TreeMapVisual
s {$sel:visualId:TreeMapVisual' :: Text
visualId = Text
a} :: TreeMapVisual)

instance Data.FromJSON TreeMapVisual where
  parseJSON :: Value -> Parser TreeMapVisual
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TreeMapVisual"
      ( \Object
x ->
          Maybe [VisualCustomAction]
-> Maybe TreeMapConfiguration
-> Maybe [ColumnHierarchy]
-> Maybe VisualSubtitleLabelOptions
-> Maybe VisualTitleLabelOptions
-> Text
-> TreeMapVisual
TreeMapVisual'
            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
"Actions" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"ChartConfiguration")
            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
"ColumnHierarchies"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"Subtitle")
            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
"Title")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"VisualId")
      )

instance Prelude.Hashable TreeMapVisual where
  hashWithSalt :: Int -> TreeMapVisual -> Int
hashWithSalt Int
_salt TreeMapVisual' {Maybe [ColumnHierarchy]
Maybe [VisualCustomAction]
Maybe TreeMapConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
columnHierarchies :: Maybe [ColumnHierarchy]
chartConfiguration :: Maybe TreeMapConfiguration
actions :: Maybe [VisualCustomAction]
$sel:visualId:TreeMapVisual' :: TreeMapVisual -> Text
$sel:title:TreeMapVisual' :: TreeMapVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:TreeMapVisual' :: TreeMapVisual -> Maybe VisualSubtitleLabelOptions
$sel:columnHierarchies:TreeMapVisual' :: TreeMapVisual -> Maybe [ColumnHierarchy]
$sel:chartConfiguration:TreeMapVisual' :: TreeMapVisual -> Maybe TreeMapConfiguration
$sel:actions:TreeMapVisual' :: TreeMapVisual -> Maybe [VisualCustomAction]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [VisualCustomAction]
actions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TreeMapConfiguration
chartConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ColumnHierarchy]
columnHierarchies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VisualSubtitleLabelOptions
subtitle
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VisualTitleLabelOptions
title
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
visualId

instance Prelude.NFData TreeMapVisual where
  rnf :: TreeMapVisual -> ()
rnf TreeMapVisual' {Maybe [ColumnHierarchy]
Maybe [VisualCustomAction]
Maybe TreeMapConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
columnHierarchies :: Maybe [ColumnHierarchy]
chartConfiguration :: Maybe TreeMapConfiguration
actions :: Maybe [VisualCustomAction]
$sel:visualId:TreeMapVisual' :: TreeMapVisual -> Text
$sel:title:TreeMapVisual' :: TreeMapVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:TreeMapVisual' :: TreeMapVisual -> Maybe VisualSubtitleLabelOptions
$sel:columnHierarchies:TreeMapVisual' :: TreeMapVisual -> Maybe [ColumnHierarchy]
$sel:chartConfiguration:TreeMapVisual' :: TreeMapVisual -> Maybe TreeMapConfiguration
$sel:actions:TreeMapVisual' :: TreeMapVisual -> Maybe [VisualCustomAction]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [VisualCustomAction]
actions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TreeMapConfiguration
chartConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ColumnHierarchy]
columnHierarchies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VisualSubtitleLabelOptions
subtitle
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VisualTitleLabelOptions
title
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
visualId

instance Data.ToJSON TreeMapVisual where
  toJSON :: TreeMapVisual -> Value
toJSON TreeMapVisual' {Maybe [ColumnHierarchy]
Maybe [VisualCustomAction]
Maybe TreeMapConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
columnHierarchies :: Maybe [ColumnHierarchy]
chartConfiguration :: Maybe TreeMapConfiguration
actions :: Maybe [VisualCustomAction]
$sel:visualId:TreeMapVisual' :: TreeMapVisual -> Text
$sel:title:TreeMapVisual' :: TreeMapVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:TreeMapVisual' :: TreeMapVisual -> Maybe VisualSubtitleLabelOptions
$sel:columnHierarchies:TreeMapVisual' :: TreeMapVisual -> Maybe [ColumnHierarchy]
$sel:chartConfiguration:TreeMapVisual' :: TreeMapVisual -> Maybe TreeMapConfiguration
$sel:actions:TreeMapVisual' :: TreeMapVisual -> Maybe [VisualCustomAction]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Actions" 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 [VisualCustomAction]
actions,
            (Key
"ChartConfiguration" 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 TreeMapConfiguration
chartConfiguration,
            (Key
"ColumnHierarchies" 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 [ColumnHierarchy]
columnHierarchies,
            (Key
"Subtitle" 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 VisualSubtitleLabelOptions
subtitle,
            (Key
"Title" 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 VisualTitleLabelOptions
title,
            forall a. a -> Maybe a
Prelude.Just (Key
"VisualId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
visualId)
          ]
      )