{-# 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.DashboardVersion
-- 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.DashboardVersion 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.DashboardError
import Amazonka.QuickSight.Types.ResourceStatus
import Amazonka.QuickSight.Types.Sheet

-- | Dashboard version.
--
-- /See:/ 'newDashboardVersion' smart constructor.
data DashboardVersion = DashboardVersion'
  { -- | The Amazon Resource Name (ARN) of the resource.
    DashboardVersion -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The time that this dashboard version was created.
    DashboardVersion -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Numbers (ARNs) for the datasets that are associated
    -- with this version of the dashboard.
    DashboardVersion -> Maybe [Text]
dataSetArns :: Prelude.Maybe [Prelude.Text],
    -- | Description.
    DashboardVersion -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Errors associated with this dashboard version.
    DashboardVersion -> Maybe (NonEmpty DashboardError)
errors :: Prelude.Maybe (Prelude.NonEmpty DashboardError),
    -- | A list of the associated sheets with the unique identifier and name of
    -- each sheet.
    DashboardVersion -> Maybe [Sheet]
sheets :: Prelude.Maybe [Sheet],
    -- | Source entity ARN.
    DashboardVersion -> Maybe Text
sourceEntityArn :: Prelude.Maybe Prelude.Text,
    -- | The HTTP status of the request.
    DashboardVersion -> Maybe ResourceStatus
status :: Prelude.Maybe ResourceStatus,
    -- | The ARN of the theme associated with a version of the dashboard.
    DashboardVersion -> Maybe Text
themeArn :: Prelude.Maybe Prelude.Text,
    -- | Version number for this version of the dashboard.
    DashboardVersion -> Maybe Natural
versionNumber :: Prelude.Maybe Prelude.Natural
  }
  deriving (DashboardVersion -> DashboardVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DashboardVersion -> DashboardVersion -> Bool
$c/= :: DashboardVersion -> DashboardVersion -> Bool
== :: DashboardVersion -> DashboardVersion -> Bool
$c== :: DashboardVersion -> DashboardVersion -> Bool
Prelude.Eq, ReadPrec [DashboardVersion]
ReadPrec DashboardVersion
Int -> ReadS DashboardVersion
ReadS [DashboardVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DashboardVersion]
$creadListPrec :: ReadPrec [DashboardVersion]
readPrec :: ReadPrec DashboardVersion
$creadPrec :: ReadPrec DashboardVersion
readList :: ReadS [DashboardVersion]
$creadList :: ReadS [DashboardVersion]
readsPrec :: Int -> ReadS DashboardVersion
$creadsPrec :: Int -> ReadS DashboardVersion
Prelude.Read, Int -> DashboardVersion -> ShowS
[DashboardVersion] -> ShowS
DashboardVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DashboardVersion] -> ShowS
$cshowList :: [DashboardVersion] -> ShowS
show :: DashboardVersion -> String
$cshow :: DashboardVersion -> String
showsPrec :: Int -> DashboardVersion -> ShowS
$cshowsPrec :: Int -> DashboardVersion -> ShowS
Prelude.Show, forall x. Rep DashboardVersion x -> DashboardVersion
forall x. DashboardVersion -> Rep DashboardVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DashboardVersion x -> DashboardVersion
$cfrom :: forall x. DashboardVersion -> Rep DashboardVersion x
Prelude.Generic)

-- |
-- Create a value of 'DashboardVersion' 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:
--
-- 'arn', 'dashboardVersion_arn' - The Amazon Resource Name (ARN) of the resource.
--
-- 'createdTime', 'dashboardVersion_createdTime' - The time that this dashboard version was created.
--
-- 'dataSetArns', 'dashboardVersion_dataSetArns' - The Amazon Resource Numbers (ARNs) for the datasets that are associated
-- with this version of the dashboard.
--
-- 'description', 'dashboardVersion_description' - Description.
--
-- 'errors', 'dashboardVersion_errors' - Errors associated with this dashboard version.
--
-- 'sheets', 'dashboardVersion_sheets' - A list of the associated sheets with the unique identifier and name of
-- each sheet.
--
-- 'sourceEntityArn', 'dashboardVersion_sourceEntityArn' - Source entity ARN.
--
-- 'status', 'dashboardVersion_status' - The HTTP status of the request.
--
-- 'themeArn', 'dashboardVersion_themeArn' - The ARN of the theme associated with a version of the dashboard.
--
-- 'versionNumber', 'dashboardVersion_versionNumber' - Version number for this version of the dashboard.
newDashboardVersion ::
  DashboardVersion
newDashboardVersion :: DashboardVersion
newDashboardVersion =
  DashboardVersion'
    { $sel:arn:DashboardVersion' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTime:DashboardVersion' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSetArns:DashboardVersion' :: Maybe [Text]
dataSetArns = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DashboardVersion' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:errors:DashboardVersion' :: Maybe (NonEmpty DashboardError)
errors = forall a. Maybe a
Prelude.Nothing,
      $sel:sheets:DashboardVersion' :: Maybe [Sheet]
sheets = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceEntityArn:DashboardVersion' :: Maybe Text
sourceEntityArn = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DashboardVersion' :: Maybe ResourceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:themeArn:DashboardVersion' :: Maybe Text
themeArn = forall a. Maybe a
Prelude.Nothing,
      $sel:versionNumber:DashboardVersion' :: Maybe Natural
versionNumber = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the resource.
dashboardVersion_arn :: Lens.Lens' DashboardVersion (Prelude.Maybe Prelude.Text)
dashboardVersion_arn :: Lens' DashboardVersion (Maybe Text)
dashboardVersion_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe Text
arn :: Maybe Text
$sel:arn:DashboardVersion' :: DashboardVersion -> Maybe Text
arn} -> Maybe Text
arn) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe Text
a -> DashboardVersion
s {$sel:arn:DashboardVersion' :: Maybe Text
arn = Maybe Text
a} :: DashboardVersion)

-- | The time that this dashboard version was created.
dashboardVersion_createdTime :: Lens.Lens' DashboardVersion (Prelude.Maybe Prelude.UTCTime)
dashboardVersion_createdTime :: Lens' DashboardVersion (Maybe UTCTime)
dashboardVersion_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:DashboardVersion' :: DashboardVersion -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe POSIX
a -> DashboardVersion
s {$sel:createdTime:DashboardVersion' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: DashboardVersion) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Amazon Resource Numbers (ARNs) for the datasets that are associated
-- with this version of the dashboard.
dashboardVersion_dataSetArns :: Lens.Lens' DashboardVersion (Prelude.Maybe [Prelude.Text])
dashboardVersion_dataSetArns :: Lens' DashboardVersion (Maybe [Text])
dashboardVersion_dataSetArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe [Text]
dataSetArns :: Maybe [Text]
$sel:dataSetArns:DashboardVersion' :: DashboardVersion -> Maybe [Text]
dataSetArns} -> Maybe [Text]
dataSetArns) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe [Text]
a -> DashboardVersion
s {$sel:dataSetArns:DashboardVersion' :: Maybe [Text]
dataSetArns = Maybe [Text]
a} :: DashboardVersion) 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

-- | Description.
dashboardVersion_description :: Lens.Lens' DashboardVersion (Prelude.Maybe Prelude.Text)
dashboardVersion_description :: Lens' DashboardVersion (Maybe Text)
dashboardVersion_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe Text
description :: Maybe Text
$sel:description:DashboardVersion' :: DashboardVersion -> Maybe Text
description} -> Maybe Text
description) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe Text
a -> DashboardVersion
s {$sel:description:DashboardVersion' :: Maybe Text
description = Maybe Text
a} :: DashboardVersion)

-- | Errors associated with this dashboard version.
dashboardVersion_errors :: Lens.Lens' DashboardVersion (Prelude.Maybe (Prelude.NonEmpty DashboardError))
dashboardVersion_errors :: Lens' DashboardVersion (Maybe (NonEmpty DashboardError))
dashboardVersion_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe (NonEmpty DashboardError)
errors :: Maybe (NonEmpty DashboardError)
$sel:errors:DashboardVersion' :: DashboardVersion -> Maybe (NonEmpty DashboardError)
errors} -> Maybe (NonEmpty DashboardError)
errors) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe (NonEmpty DashboardError)
a -> DashboardVersion
s {$sel:errors:DashboardVersion' :: Maybe (NonEmpty DashboardError)
errors = Maybe (NonEmpty DashboardError)
a} :: DashboardVersion) 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

-- | A list of the associated sheets with the unique identifier and name of
-- each sheet.
dashboardVersion_sheets :: Lens.Lens' DashboardVersion (Prelude.Maybe [Sheet])
dashboardVersion_sheets :: Lens' DashboardVersion (Maybe [Sheet])
dashboardVersion_sheets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe [Sheet]
sheets :: Maybe [Sheet]
$sel:sheets:DashboardVersion' :: DashboardVersion -> Maybe [Sheet]
sheets} -> Maybe [Sheet]
sheets) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe [Sheet]
a -> DashboardVersion
s {$sel:sheets:DashboardVersion' :: Maybe [Sheet]
sheets = Maybe [Sheet]
a} :: DashboardVersion) 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

-- | Source entity ARN.
dashboardVersion_sourceEntityArn :: Lens.Lens' DashboardVersion (Prelude.Maybe Prelude.Text)
dashboardVersion_sourceEntityArn :: Lens' DashboardVersion (Maybe Text)
dashboardVersion_sourceEntityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe Text
sourceEntityArn :: Maybe Text
$sel:sourceEntityArn:DashboardVersion' :: DashboardVersion -> Maybe Text
sourceEntityArn} -> Maybe Text
sourceEntityArn) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe Text
a -> DashboardVersion
s {$sel:sourceEntityArn:DashboardVersion' :: Maybe Text
sourceEntityArn = Maybe Text
a} :: DashboardVersion)

-- | The HTTP status of the request.
dashboardVersion_status :: Lens.Lens' DashboardVersion (Prelude.Maybe ResourceStatus)
dashboardVersion_status :: Lens' DashboardVersion (Maybe ResourceStatus)
dashboardVersion_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe ResourceStatus
status :: Maybe ResourceStatus
$sel:status:DashboardVersion' :: DashboardVersion -> Maybe ResourceStatus
status} -> Maybe ResourceStatus
status) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe ResourceStatus
a -> DashboardVersion
s {$sel:status:DashboardVersion' :: Maybe ResourceStatus
status = Maybe ResourceStatus
a} :: DashboardVersion)

-- | The ARN of the theme associated with a version of the dashboard.
dashboardVersion_themeArn :: Lens.Lens' DashboardVersion (Prelude.Maybe Prelude.Text)
dashboardVersion_themeArn :: Lens' DashboardVersion (Maybe Text)
dashboardVersion_themeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe Text
themeArn :: Maybe Text
$sel:themeArn:DashboardVersion' :: DashboardVersion -> Maybe Text
themeArn} -> Maybe Text
themeArn) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe Text
a -> DashboardVersion
s {$sel:themeArn:DashboardVersion' :: Maybe Text
themeArn = Maybe Text
a} :: DashboardVersion)

-- | Version number for this version of the dashboard.
dashboardVersion_versionNumber :: Lens.Lens' DashboardVersion (Prelude.Maybe Prelude.Natural)
dashboardVersion_versionNumber :: Lens' DashboardVersion (Maybe Natural)
dashboardVersion_versionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DashboardVersion' {Maybe Natural
versionNumber :: Maybe Natural
$sel:versionNumber:DashboardVersion' :: DashboardVersion -> Maybe Natural
versionNumber} -> Maybe Natural
versionNumber) (\s :: DashboardVersion
s@DashboardVersion' {} Maybe Natural
a -> DashboardVersion
s {$sel:versionNumber:DashboardVersion' :: Maybe Natural
versionNumber = Maybe Natural
a} :: DashboardVersion)

instance Data.FromJSON DashboardVersion where
  parseJSON :: Value -> Parser DashboardVersion
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DashboardVersion"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe [Text]
-> Maybe Text
-> Maybe (NonEmpty DashboardError)
-> Maybe [Sheet]
-> Maybe Text
-> Maybe ResourceStatus
-> Maybe Text
-> Maybe Natural
-> DashboardVersion
DashboardVersion'
            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
"Arn")
            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
"CreatedTime")
            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
"DataSetArns" 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
"Description")
            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
"Errors")
            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
"Sheets" 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
"SourceEntityArn")
            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
"Status")
            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
"ThemeArn")
            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
"VersionNumber")
      )

instance Prelude.Hashable DashboardVersion where
  hashWithSalt :: Int -> DashboardVersion -> Int
hashWithSalt Int
_salt DashboardVersion' {Maybe Natural
Maybe [Text]
Maybe [Sheet]
Maybe (NonEmpty DashboardError)
Maybe Text
Maybe POSIX
Maybe ResourceStatus
versionNumber :: Maybe Natural
themeArn :: Maybe Text
status :: Maybe ResourceStatus
sourceEntityArn :: Maybe Text
sheets :: Maybe [Sheet]
errors :: Maybe (NonEmpty DashboardError)
description :: Maybe Text
dataSetArns :: Maybe [Text]
createdTime :: Maybe POSIX
arn :: Maybe Text
$sel:versionNumber:DashboardVersion' :: DashboardVersion -> Maybe Natural
$sel:themeArn:DashboardVersion' :: DashboardVersion -> Maybe Text
$sel:status:DashboardVersion' :: DashboardVersion -> Maybe ResourceStatus
$sel:sourceEntityArn:DashboardVersion' :: DashboardVersion -> Maybe Text
$sel:sheets:DashboardVersion' :: DashboardVersion -> Maybe [Sheet]
$sel:errors:DashboardVersion' :: DashboardVersion -> Maybe (NonEmpty DashboardError)
$sel:description:DashboardVersion' :: DashboardVersion -> Maybe Text
$sel:dataSetArns:DashboardVersion' :: DashboardVersion -> Maybe [Text]
$sel:createdTime:DashboardVersion' :: DashboardVersion -> Maybe POSIX
$sel:arn:DashboardVersion' :: DashboardVersion -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
dataSetArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty DashboardError)
errors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Sheet]
sheets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceEntityArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
themeArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
versionNumber

instance Prelude.NFData DashboardVersion where
  rnf :: DashboardVersion -> ()
rnf DashboardVersion' {Maybe Natural
Maybe [Text]
Maybe [Sheet]
Maybe (NonEmpty DashboardError)
Maybe Text
Maybe POSIX
Maybe ResourceStatus
versionNumber :: Maybe Natural
themeArn :: Maybe Text
status :: Maybe ResourceStatus
sourceEntityArn :: Maybe Text
sheets :: Maybe [Sheet]
errors :: Maybe (NonEmpty DashboardError)
description :: Maybe Text
dataSetArns :: Maybe [Text]
createdTime :: Maybe POSIX
arn :: Maybe Text
$sel:versionNumber:DashboardVersion' :: DashboardVersion -> Maybe Natural
$sel:themeArn:DashboardVersion' :: DashboardVersion -> Maybe Text
$sel:status:DashboardVersion' :: DashboardVersion -> Maybe ResourceStatus
$sel:sourceEntityArn:DashboardVersion' :: DashboardVersion -> Maybe Text
$sel:sheets:DashboardVersion' :: DashboardVersion -> Maybe [Sheet]
$sel:errors:DashboardVersion' :: DashboardVersion -> Maybe (NonEmpty DashboardError)
$sel:description:DashboardVersion' :: DashboardVersion -> Maybe Text
$sel:dataSetArns:DashboardVersion' :: DashboardVersion -> Maybe [Text]
$sel:createdTime:DashboardVersion' :: DashboardVersion -> Maybe POSIX
$sel:arn:DashboardVersion' :: DashboardVersion -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
dataSetArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DashboardError)
errors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Sheet]
sheets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceEntityArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
themeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
versionNumber