{-# 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.HistogramVisual
-- 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.HistogramVisual 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.HistogramConfiguration
import Amazonka.QuickSight.Types.VisualCustomAction
import Amazonka.QuickSight.Types.VisualSubtitleLabelOptions
import Amazonka.QuickSight.Types.VisualTitleLabelOptions

-- | A histogram.
--
-- For more information, see
-- <https://docs.aws.amazon.com/quicksight/latest/user/histogram-charts.html Using histograms>
-- in the /Amazon QuickSight User Guide/.
--
-- /See:/ 'newHistogramVisual' smart constructor.
data HistogramVisual = HistogramVisual'
  { -- | The list of custom actions that are configured for a visual.
    HistogramVisual -> Maybe [VisualCustomAction]
actions :: Prelude.Maybe [VisualCustomAction],
    -- | The configuration for a @HistogramVisual@.
    HistogramVisual -> Maybe HistogramConfiguration
chartConfiguration :: Prelude.Maybe HistogramConfiguration,
    -- | The subtitle that is displayed on the visual.
    HistogramVisual -> Maybe VisualSubtitleLabelOptions
subtitle :: Prelude.Maybe VisualSubtitleLabelOptions,
    -- | The title that is displayed on the visual.
    HistogramVisual -> 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.
    HistogramVisual -> Text
visualId :: Prelude.Text
  }
  deriving (HistogramVisual -> HistogramVisual -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HistogramVisual -> HistogramVisual -> Bool
$c/= :: HistogramVisual -> HistogramVisual -> Bool
== :: HistogramVisual -> HistogramVisual -> Bool
$c== :: HistogramVisual -> HistogramVisual -> Bool
Prelude.Eq, Int -> HistogramVisual -> ShowS
[HistogramVisual] -> ShowS
HistogramVisual -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HistogramVisual] -> ShowS
$cshowList :: [HistogramVisual] -> ShowS
show :: HistogramVisual -> String
$cshow :: HistogramVisual -> String
showsPrec :: Int -> HistogramVisual -> ShowS
$cshowsPrec :: Int -> HistogramVisual -> ShowS
Prelude.Show, forall x. Rep HistogramVisual x -> HistogramVisual
forall x. HistogramVisual -> Rep HistogramVisual x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HistogramVisual x -> HistogramVisual
$cfrom :: forall x. HistogramVisual -> Rep HistogramVisual x
Prelude.Generic)

-- |
-- Create a value of 'HistogramVisual' 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', 'histogramVisual_actions' - The list of custom actions that are configured for a visual.
--
-- 'chartConfiguration', 'histogramVisual_chartConfiguration' - The configuration for a @HistogramVisual@.
--
-- 'subtitle', 'histogramVisual_subtitle' - The subtitle that is displayed on the visual.
--
-- 'title', 'histogramVisual_title' - The title that is displayed on the visual.
--
-- 'visualId', 'histogramVisual_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.
newHistogramVisual ::
  -- | 'visualId'
  Prelude.Text ->
  HistogramVisual
newHistogramVisual :: Text -> HistogramVisual
newHistogramVisual Text
pVisualId_ =
  HistogramVisual'
    { $sel:actions:HistogramVisual' :: Maybe [VisualCustomAction]
actions = forall a. Maybe a
Prelude.Nothing,
      $sel:chartConfiguration:HistogramVisual' :: Maybe HistogramConfiguration
chartConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:subtitle:HistogramVisual' :: Maybe VisualSubtitleLabelOptions
subtitle = forall a. Maybe a
Prelude.Nothing,
      $sel:title:HistogramVisual' :: Maybe VisualTitleLabelOptions
title = forall a. Maybe a
Prelude.Nothing,
      $sel:visualId:HistogramVisual' :: Text
visualId = Text
pVisualId_
    }

-- | The list of custom actions that are configured for a visual.
histogramVisual_actions :: Lens.Lens' HistogramVisual (Prelude.Maybe [VisualCustomAction])
histogramVisual_actions :: Lens' HistogramVisual (Maybe [VisualCustomAction])
histogramVisual_actions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistogramVisual' {Maybe [VisualCustomAction]
actions :: Maybe [VisualCustomAction]
$sel:actions:HistogramVisual' :: HistogramVisual -> Maybe [VisualCustomAction]
actions} -> Maybe [VisualCustomAction]
actions) (\s :: HistogramVisual
s@HistogramVisual' {} Maybe [VisualCustomAction]
a -> HistogramVisual
s {$sel:actions:HistogramVisual' :: Maybe [VisualCustomAction]
actions = Maybe [VisualCustomAction]
a} :: HistogramVisual) 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 for a @HistogramVisual@.
histogramVisual_chartConfiguration :: Lens.Lens' HistogramVisual (Prelude.Maybe HistogramConfiguration)
histogramVisual_chartConfiguration :: Lens' HistogramVisual (Maybe HistogramConfiguration)
histogramVisual_chartConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistogramVisual' {Maybe HistogramConfiguration
chartConfiguration :: Maybe HistogramConfiguration
$sel:chartConfiguration:HistogramVisual' :: HistogramVisual -> Maybe HistogramConfiguration
chartConfiguration} -> Maybe HistogramConfiguration
chartConfiguration) (\s :: HistogramVisual
s@HistogramVisual' {} Maybe HistogramConfiguration
a -> HistogramVisual
s {$sel:chartConfiguration:HistogramVisual' :: Maybe HistogramConfiguration
chartConfiguration = Maybe HistogramConfiguration
a} :: HistogramVisual)

-- | The subtitle that is displayed on the visual.
histogramVisual_subtitle :: Lens.Lens' HistogramVisual (Prelude.Maybe VisualSubtitleLabelOptions)
histogramVisual_subtitle :: Lens' HistogramVisual (Maybe VisualSubtitleLabelOptions)
histogramVisual_subtitle = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistogramVisual' {Maybe VisualSubtitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
$sel:subtitle:HistogramVisual' :: HistogramVisual -> Maybe VisualSubtitleLabelOptions
subtitle} -> Maybe VisualSubtitleLabelOptions
subtitle) (\s :: HistogramVisual
s@HistogramVisual' {} Maybe VisualSubtitleLabelOptions
a -> HistogramVisual
s {$sel:subtitle:HistogramVisual' :: Maybe VisualSubtitleLabelOptions
subtitle = Maybe VisualSubtitleLabelOptions
a} :: HistogramVisual)

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

-- | 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.
histogramVisual_visualId :: Lens.Lens' HistogramVisual Prelude.Text
histogramVisual_visualId :: Lens' HistogramVisual Text
histogramVisual_visualId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistogramVisual' {Text
visualId :: Text
$sel:visualId:HistogramVisual' :: HistogramVisual -> Text
visualId} -> Text
visualId) (\s :: HistogramVisual
s@HistogramVisual' {} Text
a -> HistogramVisual
s {$sel:visualId:HistogramVisual' :: Text
visualId = Text
a} :: HistogramVisual)

instance Data.FromJSON HistogramVisual where
  parseJSON :: Value -> Parser HistogramVisual
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HistogramVisual"
      ( \Object
x ->
          Maybe [VisualCustomAction]
-> Maybe HistogramConfiguration
-> Maybe VisualSubtitleLabelOptions
-> Maybe VisualTitleLabelOptions
-> Text
-> HistogramVisual
HistogramVisual'
            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
"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 HistogramVisual where
  hashWithSalt :: Int -> HistogramVisual -> Int
hashWithSalt Int
_salt HistogramVisual' {Maybe [VisualCustomAction]
Maybe HistogramConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
chartConfiguration :: Maybe HistogramConfiguration
actions :: Maybe [VisualCustomAction]
$sel:visualId:HistogramVisual' :: HistogramVisual -> Text
$sel:title:HistogramVisual' :: HistogramVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:HistogramVisual' :: HistogramVisual -> Maybe VisualSubtitleLabelOptions
$sel:chartConfiguration:HistogramVisual' :: HistogramVisual -> Maybe HistogramConfiguration
$sel:actions:HistogramVisual' :: HistogramVisual -> 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 HistogramConfiguration
chartConfiguration
      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 HistogramVisual where
  rnf :: HistogramVisual -> ()
rnf HistogramVisual' {Maybe [VisualCustomAction]
Maybe HistogramConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
chartConfiguration :: Maybe HistogramConfiguration
actions :: Maybe [VisualCustomAction]
$sel:visualId:HistogramVisual' :: HistogramVisual -> Text
$sel:title:HistogramVisual' :: HistogramVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:HistogramVisual' :: HistogramVisual -> Maybe VisualSubtitleLabelOptions
$sel:chartConfiguration:HistogramVisual' :: HistogramVisual -> Maybe HistogramConfiguration
$sel:actions:HistogramVisual' :: HistogramVisual -> 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 HistogramConfiguration
chartConfiguration
      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 HistogramVisual where
  toJSON :: HistogramVisual -> Value
toJSON HistogramVisual' {Maybe [VisualCustomAction]
Maybe HistogramConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
chartConfiguration :: Maybe HistogramConfiguration
actions :: Maybe [VisualCustomAction]
$sel:visualId:HistogramVisual' :: HistogramVisual -> Text
$sel:title:HistogramVisual' :: HistogramVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:HistogramVisual' :: HistogramVisual -> Maybe VisualSubtitleLabelOptions
$sel:chartConfiguration:HistogramVisual' :: HistogramVisual -> Maybe HistogramConfiguration
$sel:actions:HistogramVisual' :: HistogramVisual -> 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 HistogramConfiguration
chartConfiguration,
            (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)
          ]
      )