{-# 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.DashboardVisualId
-- 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.DashboardVisualId 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

-- | A structure that contains the following elements:
--
-- -   The @DashboardId@ of the dashboard that has the visual that you want
--     to embed.
--
-- -   The @SheetId@ of the sheet that has the visual that you want to
--     embed.
--
-- -   The @VisualId@ of the visual that you want to embed.
--
-- The @DashboardId@, @SheetId@, and @VisualId@ can be found in the
-- @IDs for developers@ section of the @Embed visual@ pane of the visual\'s
-- on-visual menu of the Amazon QuickSight console. You can also get the
-- @DashboardId@ with a @ListDashboards@ API operation.
--
-- /See:/ 'newDashboardVisualId' smart constructor.
data DashboardVisualId = DashboardVisualId'
  { -- | The ID of the dashboard that has the visual that you want to embed. The
    -- @DashboardId@ can be found in the @IDs for developers@ section of the
    -- @Embed visual@ pane of the visual\'s on-visual menu of the Amazon
    -- QuickSight console. You can also get the @DashboardId@ with a
    -- @ListDashboards@ API operation.
    DashboardVisualId -> Text
dashboardId :: Prelude.Text,
    -- | The ID of the sheet that the has visual that you want to embed. The
    -- @SheetId@ can be found in the @IDs for developers@ section of the
    -- @Embed visual@ pane of the visual\'s on-visual menu of the Amazon
    -- QuickSight console.
    DashboardVisualId -> Text
sheetId :: Prelude.Text,
    -- | The ID of the visual that you want to embed. The @VisualID@ can be found
    -- in the @IDs for developers@ section of the @Embed visual@ pane of the
    -- visual\'s on-visual menu of the Amazon QuickSight console.
    DashboardVisualId -> Text
visualId :: Prelude.Text
  }
  deriving (DashboardVisualId -> DashboardVisualId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DashboardVisualId -> DashboardVisualId -> Bool
$c/= :: DashboardVisualId -> DashboardVisualId -> Bool
== :: DashboardVisualId -> DashboardVisualId -> Bool
$c== :: DashboardVisualId -> DashboardVisualId -> Bool
Prelude.Eq, ReadPrec [DashboardVisualId]
ReadPrec DashboardVisualId
Int -> ReadS DashboardVisualId
ReadS [DashboardVisualId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DashboardVisualId]
$creadListPrec :: ReadPrec [DashboardVisualId]
readPrec :: ReadPrec DashboardVisualId
$creadPrec :: ReadPrec DashboardVisualId
readList :: ReadS [DashboardVisualId]
$creadList :: ReadS [DashboardVisualId]
readsPrec :: Int -> ReadS DashboardVisualId
$creadsPrec :: Int -> ReadS DashboardVisualId
Prelude.Read, Int -> DashboardVisualId -> ShowS
[DashboardVisualId] -> ShowS
DashboardVisualId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DashboardVisualId] -> ShowS
$cshowList :: [DashboardVisualId] -> ShowS
show :: DashboardVisualId -> String
$cshow :: DashboardVisualId -> String
showsPrec :: Int -> DashboardVisualId -> ShowS
$cshowsPrec :: Int -> DashboardVisualId -> ShowS
Prelude.Show, forall x. Rep DashboardVisualId x -> DashboardVisualId
forall x. DashboardVisualId -> Rep DashboardVisualId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DashboardVisualId x -> DashboardVisualId
$cfrom :: forall x. DashboardVisualId -> Rep DashboardVisualId x
Prelude.Generic)

-- |
-- Create a value of 'DashboardVisualId' 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:
--
-- 'dashboardId', 'dashboardVisualId_dashboardId' - The ID of the dashboard that has the visual that you want to embed. The
-- @DashboardId@ can be found in the @IDs for developers@ section of the
-- @Embed visual@ pane of the visual\'s on-visual menu of the Amazon
-- QuickSight console. You can also get the @DashboardId@ with a
-- @ListDashboards@ API operation.
--
-- 'sheetId', 'dashboardVisualId_sheetId' - The ID of the sheet that the has visual that you want to embed. The
-- @SheetId@ can be found in the @IDs for developers@ section of the
-- @Embed visual@ pane of the visual\'s on-visual menu of the Amazon
-- QuickSight console.
--
-- 'visualId', 'dashboardVisualId_visualId' - The ID of the visual that you want to embed. The @VisualID@ can be found
-- in the @IDs for developers@ section of the @Embed visual@ pane of the
-- visual\'s on-visual menu of the Amazon QuickSight console.
newDashboardVisualId ::
  -- | 'dashboardId'
  Prelude.Text ->
  -- | 'sheetId'
  Prelude.Text ->
  -- | 'visualId'
  Prelude.Text ->
  DashboardVisualId
newDashboardVisualId :: Text -> Text -> Text -> DashboardVisualId
newDashboardVisualId
  Text
pDashboardId_
  Text
pSheetId_
  Text
pVisualId_ =
    DashboardVisualId'
      { $sel:dashboardId:DashboardVisualId' :: Text
dashboardId = Text
pDashboardId_,
        $sel:sheetId:DashboardVisualId' :: Text
sheetId = Text
pSheetId_,
        $sel:visualId:DashboardVisualId' :: Text
visualId = Text
pVisualId_
      }

-- | The ID of the dashboard that has the visual that you want to embed. The
-- @DashboardId@ can be found in the @IDs for developers@ section of the
-- @Embed visual@ pane of the visual\'s on-visual menu of the Amazon
-- QuickSight console. You can also get the @DashboardId@ with a
-- @ListDashboards@ API operation.
dashboardVisualId_dashboardId :: Lens.Lens' DashboardVisualId Prelude.Text
dashboardVisualId_dashboardId :: Lens' DashboardVisualId Text
dashboardVisualId_dashboardId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVisualId' {Text
dashboardId :: Text
$sel:dashboardId:DashboardVisualId' :: DashboardVisualId -> Text
dashboardId} -> Text
dashboardId) (\s :: DashboardVisualId
s@DashboardVisualId' {} Text
a -> DashboardVisualId
s {$sel:dashboardId:DashboardVisualId' :: Text
dashboardId = Text
a} :: DashboardVisualId)

-- | The ID of the sheet that the has visual that you want to embed. The
-- @SheetId@ can be found in the @IDs for developers@ section of the
-- @Embed visual@ pane of the visual\'s on-visual menu of the Amazon
-- QuickSight console.
dashboardVisualId_sheetId :: Lens.Lens' DashboardVisualId Prelude.Text
dashboardVisualId_sheetId :: Lens' DashboardVisualId Text
dashboardVisualId_sheetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVisualId' {Text
sheetId :: Text
$sel:sheetId:DashboardVisualId' :: DashboardVisualId -> Text
sheetId} -> Text
sheetId) (\s :: DashboardVisualId
s@DashboardVisualId' {} Text
a -> DashboardVisualId
s {$sel:sheetId:DashboardVisualId' :: Text
sheetId = Text
a} :: DashboardVisualId)

-- | The ID of the visual that you want to embed. The @VisualID@ can be found
-- in the @IDs for developers@ section of the @Embed visual@ pane of the
-- visual\'s on-visual menu of the Amazon QuickSight console.
dashboardVisualId_visualId :: Lens.Lens' DashboardVisualId Prelude.Text
dashboardVisualId_visualId :: Lens' DashboardVisualId Text
dashboardVisualId_visualId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVisualId' {Text
visualId :: Text
$sel:visualId:DashboardVisualId' :: DashboardVisualId -> Text
visualId} -> Text
visualId) (\s :: DashboardVisualId
s@DashboardVisualId' {} Text
a -> DashboardVisualId
s {$sel:visualId:DashboardVisualId' :: Text
visualId = Text
a} :: DashboardVisualId)

instance Prelude.Hashable DashboardVisualId where
  hashWithSalt :: Int -> DashboardVisualId -> Int
hashWithSalt Int
_salt DashboardVisualId' {Text
visualId :: Text
sheetId :: Text
dashboardId :: Text
$sel:visualId:DashboardVisualId' :: DashboardVisualId -> Text
$sel:sheetId:DashboardVisualId' :: DashboardVisualId -> Text
$sel:dashboardId:DashboardVisualId' :: DashboardVisualId -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dashboardId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sheetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
visualId

instance Prelude.NFData DashboardVisualId where
  rnf :: DashboardVisualId -> ()
rnf DashboardVisualId' {Text
visualId :: Text
sheetId :: Text
dashboardId :: Text
$sel:visualId:DashboardVisualId' :: DashboardVisualId -> Text
$sel:sheetId:DashboardVisualId' :: DashboardVisualId -> Text
$sel:dashboardId:DashboardVisualId' :: DashboardVisualId -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
dashboardId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sheetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
visualId

instance Data.ToJSON DashboardVisualId where
  toJSON :: DashboardVisualId -> Value
toJSON DashboardVisualId' {Text
visualId :: Text
sheetId :: Text
dashboardId :: Text
$sel:visualId:DashboardVisualId' :: DashboardVisualId -> Text
$sel:sheetId:DashboardVisualId' :: DashboardVisualId -> Text
$sel:dashboardId:DashboardVisualId' :: DashboardVisualId -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"DashboardId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
dashboardId),
            forall a. a -> Maybe a
Prelude.Just (Key
"SheetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sheetId),
            forall a. a -> Maybe a
Prelude.Just (Key
"VisualId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
visualId)
          ]
      )