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

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

-- |
-- Create a value of 'LineChartVisual' 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', 'lineChartVisual_actions' - The list of custom actions that are configured for a visual.
--
-- 'chartConfiguration', 'lineChartVisual_chartConfiguration' - The configuration of a line chart.
--
-- 'columnHierarchies', 'lineChartVisual_columnHierarchies' - The column hierarchy that is used during drill-downs and drill-ups.
--
-- 'subtitle', 'lineChartVisual_subtitle' - The subtitle that is displayed on the visual.
--
-- 'title', 'lineChartVisual_title' - The title that is displayed on the visual.
--
-- 'visualId', 'lineChartVisual_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.
newLineChartVisual ::
  -- | 'visualId'
  Prelude.Text ->
  LineChartVisual
newLineChartVisual :: Text -> LineChartVisual
newLineChartVisual Text
pVisualId_ =
  LineChartVisual'
    { $sel:actions:LineChartVisual' :: Maybe [VisualCustomAction]
actions = forall a. Maybe a
Prelude.Nothing,
      $sel:chartConfiguration:LineChartVisual' :: Maybe LineChartConfiguration
chartConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:columnHierarchies:LineChartVisual' :: Maybe [ColumnHierarchy]
columnHierarchies = forall a. Maybe a
Prelude.Nothing,
      $sel:subtitle:LineChartVisual' :: Maybe VisualSubtitleLabelOptions
subtitle = forall a. Maybe a
Prelude.Nothing,
      $sel:title:LineChartVisual' :: Maybe VisualTitleLabelOptions
title = forall a. Maybe a
Prelude.Nothing,
      $sel:visualId:LineChartVisual' :: Text
visualId = Text
pVisualId_
    }

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

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

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

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

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