{-# 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.TemplateVersion
-- 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.TemplateVersion 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.DataSetConfiguration
import Amazonka.QuickSight.Types.ResourceStatus
import Amazonka.QuickSight.Types.Sheet
import Amazonka.QuickSight.Types.TemplateError

-- | A version of a template.
--
-- /See:/ 'newTemplateVersion' smart constructor.
data TemplateVersion = TemplateVersion'
  { -- | The time that this template version was created.
    TemplateVersion -> Maybe POSIX
createdTime :: Prelude.Maybe Data.POSIX,
    -- | Schema of the dataset identified by the placeholder. Any dashboard
    -- created from this template should be bound to new datasets matching the
    -- same schema described through this API operation.
    TemplateVersion -> Maybe [DataSetConfiguration]
dataSetConfigurations :: Prelude.Maybe [DataSetConfiguration],
    -- | The description of the template.
    TemplateVersion -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Errors associated with this template version.
    TemplateVersion -> Maybe (NonEmpty TemplateError)
errors :: Prelude.Maybe (Prelude.NonEmpty TemplateError),
    -- | A list of the associated sheets with the unique identifier and name of
    -- each sheet.
    TemplateVersion -> Maybe [Sheet]
sheets :: Prelude.Maybe [Sheet],
    -- | The Amazon Resource Name (ARN) of an analysis or template that was used
    -- to create this template.
    TemplateVersion -> Maybe Text
sourceEntityArn :: Prelude.Maybe Prelude.Text,
    -- | The HTTP status of the request.
    TemplateVersion -> Maybe ResourceStatus
status :: Prelude.Maybe ResourceStatus,
    -- | The ARN of the theme associated with this version of the template.
    TemplateVersion -> Maybe Text
themeArn :: Prelude.Maybe Prelude.Text,
    -- | The version number of the template version.
    TemplateVersion -> Maybe Natural
versionNumber :: Prelude.Maybe Prelude.Natural
  }
  deriving (TemplateVersion -> TemplateVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemplateVersion -> TemplateVersion -> Bool
$c/= :: TemplateVersion -> TemplateVersion -> Bool
== :: TemplateVersion -> TemplateVersion -> Bool
$c== :: TemplateVersion -> TemplateVersion -> Bool
Prelude.Eq, ReadPrec [TemplateVersion]
ReadPrec TemplateVersion
Int -> ReadS TemplateVersion
ReadS [TemplateVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TemplateVersion]
$creadListPrec :: ReadPrec [TemplateVersion]
readPrec :: ReadPrec TemplateVersion
$creadPrec :: ReadPrec TemplateVersion
readList :: ReadS [TemplateVersion]
$creadList :: ReadS [TemplateVersion]
readsPrec :: Int -> ReadS TemplateVersion
$creadsPrec :: Int -> ReadS TemplateVersion
Prelude.Read, Int -> TemplateVersion -> ShowS
[TemplateVersion] -> ShowS
TemplateVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemplateVersion] -> ShowS
$cshowList :: [TemplateVersion] -> ShowS
show :: TemplateVersion -> String
$cshow :: TemplateVersion -> String
showsPrec :: Int -> TemplateVersion -> ShowS
$cshowsPrec :: Int -> TemplateVersion -> ShowS
Prelude.Show, forall x. Rep TemplateVersion x -> TemplateVersion
forall x. TemplateVersion -> Rep TemplateVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TemplateVersion x -> TemplateVersion
$cfrom :: forall x. TemplateVersion -> Rep TemplateVersion x
Prelude.Generic)

-- |
-- Create a value of 'TemplateVersion' 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:
--
-- 'createdTime', 'templateVersion_createdTime' - The time that this template version was created.
--
-- 'dataSetConfigurations', 'templateVersion_dataSetConfigurations' - Schema of the dataset identified by the placeholder. Any dashboard
-- created from this template should be bound to new datasets matching the
-- same schema described through this API operation.
--
-- 'description', 'templateVersion_description' - The description of the template.
--
-- 'errors', 'templateVersion_errors' - Errors associated with this template version.
--
-- 'sheets', 'templateVersion_sheets' - A list of the associated sheets with the unique identifier and name of
-- each sheet.
--
-- 'sourceEntityArn', 'templateVersion_sourceEntityArn' - The Amazon Resource Name (ARN) of an analysis or template that was used
-- to create this template.
--
-- 'status', 'templateVersion_status' - The HTTP status of the request.
--
-- 'themeArn', 'templateVersion_themeArn' - The ARN of the theme associated with this version of the template.
--
-- 'versionNumber', 'templateVersion_versionNumber' - The version number of the template version.
newTemplateVersion ::
  TemplateVersion
newTemplateVersion :: TemplateVersion
newTemplateVersion =
  TemplateVersion'
    { $sel:createdTime:TemplateVersion' :: Maybe POSIX
createdTime = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSetConfigurations:TemplateVersion' :: Maybe [DataSetConfiguration]
dataSetConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:description:TemplateVersion' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:errors:TemplateVersion' :: Maybe (NonEmpty TemplateError)
errors = forall a. Maybe a
Prelude.Nothing,
      $sel:sheets:TemplateVersion' :: Maybe [Sheet]
sheets = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceEntityArn:TemplateVersion' :: Maybe Text
sourceEntityArn = forall a. Maybe a
Prelude.Nothing,
      $sel:status:TemplateVersion' :: Maybe ResourceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:themeArn:TemplateVersion' :: Maybe Text
themeArn = forall a. Maybe a
Prelude.Nothing,
      $sel:versionNumber:TemplateVersion' :: Maybe Natural
versionNumber = forall a. Maybe a
Prelude.Nothing
    }

-- | The time that this template version was created.
templateVersion_createdTime :: Lens.Lens' TemplateVersion (Prelude.Maybe Prelude.UTCTime)
templateVersion_createdTime :: Lens' TemplateVersion (Maybe UTCTime)
templateVersion_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe POSIX
createdTime :: Maybe POSIX
$sel:createdTime:TemplateVersion' :: TemplateVersion -> Maybe POSIX
createdTime} -> Maybe POSIX
createdTime) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe POSIX
a -> TemplateVersion
s {$sel:createdTime:TemplateVersion' :: Maybe POSIX
createdTime = Maybe POSIX
a} :: TemplateVersion) 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

-- | Schema of the dataset identified by the placeholder. Any dashboard
-- created from this template should be bound to new datasets matching the
-- same schema described through this API operation.
templateVersion_dataSetConfigurations :: Lens.Lens' TemplateVersion (Prelude.Maybe [DataSetConfiguration])
templateVersion_dataSetConfigurations :: Lens' TemplateVersion (Maybe [DataSetConfiguration])
templateVersion_dataSetConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe [DataSetConfiguration]
dataSetConfigurations :: Maybe [DataSetConfiguration]
$sel:dataSetConfigurations:TemplateVersion' :: TemplateVersion -> Maybe [DataSetConfiguration]
dataSetConfigurations} -> Maybe [DataSetConfiguration]
dataSetConfigurations) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe [DataSetConfiguration]
a -> TemplateVersion
s {$sel:dataSetConfigurations:TemplateVersion' :: Maybe [DataSetConfiguration]
dataSetConfigurations = Maybe [DataSetConfiguration]
a} :: TemplateVersion) 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 description of the template.
templateVersion_description :: Lens.Lens' TemplateVersion (Prelude.Maybe Prelude.Text)
templateVersion_description :: Lens' TemplateVersion (Maybe Text)
templateVersion_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe Text
description :: Maybe Text
$sel:description:TemplateVersion' :: TemplateVersion -> Maybe Text
description} -> Maybe Text
description) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe Text
a -> TemplateVersion
s {$sel:description:TemplateVersion' :: Maybe Text
description = Maybe Text
a} :: TemplateVersion)

-- | Errors associated with this template version.
templateVersion_errors :: Lens.Lens' TemplateVersion (Prelude.Maybe (Prelude.NonEmpty TemplateError))
templateVersion_errors :: Lens' TemplateVersion (Maybe (NonEmpty TemplateError))
templateVersion_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe (NonEmpty TemplateError)
errors :: Maybe (NonEmpty TemplateError)
$sel:errors:TemplateVersion' :: TemplateVersion -> Maybe (NonEmpty TemplateError)
errors} -> Maybe (NonEmpty TemplateError)
errors) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe (NonEmpty TemplateError)
a -> TemplateVersion
s {$sel:errors:TemplateVersion' :: Maybe (NonEmpty TemplateError)
errors = Maybe (NonEmpty TemplateError)
a} :: TemplateVersion) 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.
templateVersion_sheets :: Lens.Lens' TemplateVersion (Prelude.Maybe [Sheet])
templateVersion_sheets :: Lens' TemplateVersion (Maybe [Sheet])
templateVersion_sheets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe [Sheet]
sheets :: Maybe [Sheet]
$sel:sheets:TemplateVersion' :: TemplateVersion -> Maybe [Sheet]
sheets} -> Maybe [Sheet]
sheets) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe [Sheet]
a -> TemplateVersion
s {$sel:sheets:TemplateVersion' :: Maybe [Sheet]
sheets = Maybe [Sheet]
a} :: TemplateVersion) 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 Amazon Resource Name (ARN) of an analysis or template that was used
-- to create this template.
templateVersion_sourceEntityArn :: Lens.Lens' TemplateVersion (Prelude.Maybe Prelude.Text)
templateVersion_sourceEntityArn :: Lens' TemplateVersion (Maybe Text)
templateVersion_sourceEntityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe Text
sourceEntityArn :: Maybe Text
$sel:sourceEntityArn:TemplateVersion' :: TemplateVersion -> Maybe Text
sourceEntityArn} -> Maybe Text
sourceEntityArn) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe Text
a -> TemplateVersion
s {$sel:sourceEntityArn:TemplateVersion' :: Maybe Text
sourceEntityArn = Maybe Text
a} :: TemplateVersion)

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

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

-- | The version number of the template version.
templateVersion_versionNumber :: Lens.Lens' TemplateVersion (Prelude.Maybe Prelude.Natural)
templateVersion_versionNumber :: Lens' TemplateVersion (Maybe Natural)
templateVersion_versionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TemplateVersion' {Maybe Natural
versionNumber :: Maybe Natural
$sel:versionNumber:TemplateVersion' :: TemplateVersion -> Maybe Natural
versionNumber} -> Maybe Natural
versionNumber) (\s :: TemplateVersion
s@TemplateVersion' {} Maybe Natural
a -> TemplateVersion
s {$sel:versionNumber:TemplateVersion' :: Maybe Natural
versionNumber = Maybe Natural
a} :: TemplateVersion)

instance Data.FromJSON TemplateVersion where
  parseJSON :: Value -> Parser TemplateVersion
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TemplateVersion"
      ( \Object
x ->
          Maybe POSIX
-> Maybe [DataSetConfiguration]
-> Maybe Text
-> Maybe (NonEmpty TemplateError)
-> Maybe [Sheet]
-> Maybe Text
-> Maybe ResourceStatus
-> Maybe Text
-> Maybe Natural
-> TemplateVersion
TemplateVersion'
            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
"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
"DataSetConfigurations"
                            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 TemplateVersion where
  hashWithSalt :: Int -> TemplateVersion -> Int
hashWithSalt Int
_salt TemplateVersion' {Maybe Natural
Maybe [DataSetConfiguration]
Maybe [Sheet]
Maybe (NonEmpty TemplateError)
Maybe Text
Maybe POSIX
Maybe ResourceStatus
versionNumber :: Maybe Natural
themeArn :: Maybe Text
status :: Maybe ResourceStatus
sourceEntityArn :: Maybe Text
sheets :: Maybe [Sheet]
errors :: Maybe (NonEmpty TemplateError)
description :: Maybe Text
dataSetConfigurations :: Maybe [DataSetConfiguration]
createdTime :: Maybe POSIX
$sel:versionNumber:TemplateVersion' :: TemplateVersion -> Maybe Natural
$sel:themeArn:TemplateVersion' :: TemplateVersion -> Maybe Text
$sel:status:TemplateVersion' :: TemplateVersion -> Maybe ResourceStatus
$sel:sourceEntityArn:TemplateVersion' :: TemplateVersion -> Maybe Text
$sel:sheets:TemplateVersion' :: TemplateVersion -> Maybe [Sheet]
$sel:errors:TemplateVersion' :: TemplateVersion -> Maybe (NonEmpty TemplateError)
$sel:description:TemplateVersion' :: TemplateVersion -> Maybe Text
$sel:dataSetConfigurations:TemplateVersion' :: TemplateVersion -> Maybe [DataSetConfiguration]
$sel:createdTime:TemplateVersion' :: TemplateVersion -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DataSetConfiguration]
dataSetConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty TemplateError)
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 TemplateVersion where
  rnf :: TemplateVersion -> ()
rnf TemplateVersion' {Maybe Natural
Maybe [DataSetConfiguration]
Maybe [Sheet]
Maybe (NonEmpty TemplateError)
Maybe Text
Maybe POSIX
Maybe ResourceStatus
versionNumber :: Maybe Natural
themeArn :: Maybe Text
status :: Maybe ResourceStatus
sourceEntityArn :: Maybe Text
sheets :: Maybe [Sheet]
errors :: Maybe (NonEmpty TemplateError)
description :: Maybe Text
dataSetConfigurations :: Maybe [DataSetConfiguration]
createdTime :: Maybe POSIX
$sel:versionNumber:TemplateVersion' :: TemplateVersion -> Maybe Natural
$sel:themeArn:TemplateVersion' :: TemplateVersion -> Maybe Text
$sel:status:TemplateVersion' :: TemplateVersion -> Maybe ResourceStatus
$sel:sourceEntityArn:TemplateVersion' :: TemplateVersion -> Maybe Text
$sel:sheets:TemplateVersion' :: TemplateVersion -> Maybe [Sheet]
$sel:errors:TemplateVersion' :: TemplateVersion -> Maybe (NonEmpty TemplateError)
$sel:description:TemplateVersion' :: TemplateVersion -> Maybe Text
$sel:dataSetConfigurations:TemplateVersion' :: TemplateVersion -> Maybe [DataSetConfiguration]
$sel:createdTime:TemplateVersion' :: TemplateVersion -> Maybe POSIX
..} =
    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 [DataSetConfiguration]
dataSetConfigurations
      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 TemplateError)
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