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

-- | An insight visual.
--
-- For more information, see
-- <https://docs.aws.amazon.com/quicksight/latest/user/computational-insights.html Working with insights>
-- in the /Amazon QuickSight User Guide/.
--
-- /See:/ 'newInsightVisual' smart constructor.
data InsightVisual = InsightVisual'
  { -- | The list of custom actions that are configured for a visual.
    InsightVisual -> Maybe [VisualCustomAction]
actions :: Prelude.Maybe [VisualCustomAction],
    -- | The configuration of an insight visual.
    InsightVisual -> Maybe InsightConfiguration
insightConfiguration :: Prelude.Maybe InsightConfiguration,
    -- | The subtitle that is displayed on the visual.
    InsightVisual -> Maybe VisualSubtitleLabelOptions
subtitle :: Prelude.Maybe VisualSubtitleLabelOptions,
    -- | The title that is displayed on the visual.
    InsightVisual -> 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.
    InsightVisual -> Text
visualId :: Prelude.Text,
    -- | The dataset that is used in the insight visual.
    InsightVisual -> Text
dataSetIdentifier :: Prelude.Text
  }
  deriving (InsightVisual -> InsightVisual -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InsightVisual -> InsightVisual -> Bool
$c/= :: InsightVisual -> InsightVisual -> Bool
== :: InsightVisual -> InsightVisual -> Bool
$c== :: InsightVisual -> InsightVisual -> Bool
Prelude.Eq, Int -> InsightVisual -> ShowS
[InsightVisual] -> ShowS
InsightVisual -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InsightVisual] -> ShowS
$cshowList :: [InsightVisual] -> ShowS
show :: InsightVisual -> String
$cshow :: InsightVisual -> String
showsPrec :: Int -> InsightVisual -> ShowS
$cshowsPrec :: Int -> InsightVisual -> ShowS
Prelude.Show, forall x. Rep InsightVisual x -> InsightVisual
forall x. InsightVisual -> Rep InsightVisual x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InsightVisual x -> InsightVisual
$cfrom :: forall x. InsightVisual -> Rep InsightVisual x
Prelude.Generic)

-- |
-- Create a value of 'InsightVisual' 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', 'insightVisual_actions' - The list of custom actions that are configured for a visual.
--
-- 'insightConfiguration', 'insightVisual_insightConfiguration' - The configuration of an insight visual.
--
-- 'subtitle', 'insightVisual_subtitle' - The subtitle that is displayed on the visual.
--
-- 'title', 'insightVisual_title' - The title that is displayed on the visual.
--
-- 'visualId', 'insightVisual_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.
--
-- 'dataSetIdentifier', 'insightVisual_dataSetIdentifier' - The dataset that is used in the insight visual.
newInsightVisual ::
  -- | 'visualId'
  Prelude.Text ->
  -- | 'dataSetIdentifier'
  Prelude.Text ->
  InsightVisual
newInsightVisual :: Text -> Text -> InsightVisual
newInsightVisual Text
pVisualId_ Text
pDataSetIdentifier_ =
  InsightVisual'
    { $sel:actions:InsightVisual' :: Maybe [VisualCustomAction]
actions = forall a. Maybe a
Prelude.Nothing,
      $sel:insightConfiguration:InsightVisual' :: Maybe InsightConfiguration
insightConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:subtitle:InsightVisual' :: Maybe VisualSubtitleLabelOptions
subtitle = forall a. Maybe a
Prelude.Nothing,
      $sel:title:InsightVisual' :: Maybe VisualTitleLabelOptions
title = forall a. Maybe a
Prelude.Nothing,
      $sel:visualId:InsightVisual' :: Text
visualId = Text
pVisualId_,
      $sel:dataSetIdentifier:InsightVisual' :: Text
dataSetIdentifier = Text
pDataSetIdentifier_
    }

-- | The list of custom actions that are configured for a visual.
insightVisual_actions :: Lens.Lens' InsightVisual (Prelude.Maybe [VisualCustomAction])
insightVisual_actions :: Lens' InsightVisual (Maybe [VisualCustomAction])
insightVisual_actions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InsightVisual' {Maybe [VisualCustomAction]
actions :: Maybe [VisualCustomAction]
$sel:actions:InsightVisual' :: InsightVisual -> Maybe [VisualCustomAction]
actions} -> Maybe [VisualCustomAction]
actions) (\s :: InsightVisual
s@InsightVisual' {} Maybe [VisualCustomAction]
a -> InsightVisual
s {$sel:actions:InsightVisual' :: Maybe [VisualCustomAction]
actions = Maybe [VisualCustomAction]
a} :: InsightVisual) 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 of an insight visual.
insightVisual_insightConfiguration :: Lens.Lens' InsightVisual (Prelude.Maybe InsightConfiguration)
insightVisual_insightConfiguration :: Lens' InsightVisual (Maybe InsightConfiguration)
insightVisual_insightConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InsightVisual' {Maybe InsightConfiguration
insightConfiguration :: Maybe InsightConfiguration
$sel:insightConfiguration:InsightVisual' :: InsightVisual -> Maybe InsightConfiguration
insightConfiguration} -> Maybe InsightConfiguration
insightConfiguration) (\s :: InsightVisual
s@InsightVisual' {} Maybe InsightConfiguration
a -> InsightVisual
s {$sel:insightConfiguration:InsightVisual' :: Maybe InsightConfiguration
insightConfiguration = Maybe InsightConfiguration
a} :: InsightVisual)

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

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

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

-- | The dataset that is used in the insight visual.
insightVisual_dataSetIdentifier :: Lens.Lens' InsightVisual Prelude.Text
insightVisual_dataSetIdentifier :: Lens' InsightVisual Text
insightVisual_dataSetIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\InsightVisual' {Text
dataSetIdentifier :: Text
$sel:dataSetIdentifier:InsightVisual' :: InsightVisual -> Text
dataSetIdentifier} -> Text
dataSetIdentifier) (\s :: InsightVisual
s@InsightVisual' {} Text
a -> InsightVisual
s {$sel:dataSetIdentifier:InsightVisual' :: Text
dataSetIdentifier = Text
a} :: InsightVisual)

instance Data.FromJSON InsightVisual where
  parseJSON :: Value -> Parser InsightVisual
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"InsightVisual"
      ( \Object
x ->
          Maybe [VisualCustomAction]
-> Maybe InsightConfiguration
-> Maybe VisualSubtitleLabelOptions
-> Maybe VisualTitleLabelOptions
-> Text
-> Text
-> InsightVisual
InsightVisual'
            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
"InsightConfiguration")
            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")
            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
"DataSetIdentifier")
      )

instance Prelude.Hashable InsightVisual where
  hashWithSalt :: Int -> InsightVisual -> Int
hashWithSalt Int
_salt InsightVisual' {Maybe [VisualCustomAction]
Maybe InsightConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
dataSetIdentifier :: Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
insightConfiguration :: Maybe InsightConfiguration
actions :: Maybe [VisualCustomAction]
$sel:dataSetIdentifier:InsightVisual' :: InsightVisual -> Text
$sel:visualId:InsightVisual' :: InsightVisual -> Text
$sel:title:InsightVisual' :: InsightVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:InsightVisual' :: InsightVisual -> Maybe VisualSubtitleLabelOptions
$sel:insightConfiguration:InsightVisual' :: InsightVisual -> Maybe InsightConfiguration
$sel:actions:InsightVisual' :: InsightVisual -> 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 InsightConfiguration
insightConfiguration
      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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dataSetIdentifier

instance Prelude.NFData InsightVisual where
  rnf :: InsightVisual -> ()
rnf InsightVisual' {Maybe [VisualCustomAction]
Maybe InsightConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
dataSetIdentifier :: Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
insightConfiguration :: Maybe InsightConfiguration
actions :: Maybe [VisualCustomAction]
$sel:dataSetIdentifier:InsightVisual' :: InsightVisual -> Text
$sel:visualId:InsightVisual' :: InsightVisual -> Text
$sel:title:InsightVisual' :: InsightVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:InsightVisual' :: InsightVisual -> Maybe VisualSubtitleLabelOptions
$sel:insightConfiguration:InsightVisual' :: InsightVisual -> Maybe InsightConfiguration
$sel:actions:InsightVisual' :: InsightVisual -> 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 InsightConfiguration
insightConfiguration
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dataSetIdentifier

instance Data.ToJSON InsightVisual where
  toJSON :: InsightVisual -> Value
toJSON InsightVisual' {Maybe [VisualCustomAction]
Maybe InsightConfiguration
Maybe VisualSubtitleLabelOptions
Maybe VisualTitleLabelOptions
Text
dataSetIdentifier :: Text
visualId :: Text
title :: Maybe VisualTitleLabelOptions
subtitle :: Maybe VisualSubtitleLabelOptions
insightConfiguration :: Maybe InsightConfiguration
actions :: Maybe [VisualCustomAction]
$sel:dataSetIdentifier:InsightVisual' :: InsightVisual -> Text
$sel:visualId:InsightVisual' :: InsightVisual -> Text
$sel:title:InsightVisual' :: InsightVisual -> Maybe VisualTitleLabelOptions
$sel:subtitle:InsightVisual' :: InsightVisual -> Maybe VisualSubtitleLabelOptions
$sel:insightConfiguration:InsightVisual' :: InsightVisual -> Maybe InsightConfiguration
$sel:actions:InsightVisual' :: InsightVisual -> 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
"InsightConfiguration" 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 InsightConfiguration
insightConfiguration,
            (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),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"DataSetIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
dataSetIdentifier)
          ]
      )