{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.CreateThemeAlias
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a theme alias for a theme.
module Amazonka.QuickSight.CreateThemeAlias
  ( -- * Creating a Request
    CreateThemeAlias (..),
    newCreateThemeAlias,

    -- * Request Lenses
    createThemeAlias_awsAccountId,
    createThemeAlias_themeId,
    createThemeAlias_aliasName,
    createThemeAlias_themeVersionNumber,

    -- * Destructuring the Response
    CreateThemeAliasResponse (..),
    newCreateThemeAliasResponse,

    -- * Response Lenses
    createThemeAliasResponse_requestId,
    createThemeAliasResponse_themeAlias,
    createThemeAliasResponse_status,
  )
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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateThemeAlias' smart constructor.
data CreateThemeAlias = CreateThemeAlias'
  { -- | The ID of the Amazon Web Services account that contains the theme for
    -- the new theme alias.
    CreateThemeAlias -> Text
awsAccountId :: Prelude.Text,
    -- | An ID for the theme alias.
    CreateThemeAlias -> Text
themeId :: Prelude.Text,
    -- | The name that you want to give to the theme alias that you are creating.
    -- The alias name can\'t begin with a @$@. Alias names that start with @$@
    -- are reserved by Amazon QuickSight.
    CreateThemeAlias -> Text
aliasName :: Prelude.Text,
    -- | The version number of the theme.
    CreateThemeAlias -> Natural
themeVersionNumber :: Prelude.Natural
  }
  deriving (CreateThemeAlias -> CreateThemeAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateThemeAlias -> CreateThemeAlias -> Bool
$c/= :: CreateThemeAlias -> CreateThemeAlias -> Bool
== :: CreateThemeAlias -> CreateThemeAlias -> Bool
$c== :: CreateThemeAlias -> CreateThemeAlias -> Bool
Prelude.Eq, ReadPrec [CreateThemeAlias]
ReadPrec CreateThemeAlias
Int -> ReadS CreateThemeAlias
ReadS [CreateThemeAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateThemeAlias]
$creadListPrec :: ReadPrec [CreateThemeAlias]
readPrec :: ReadPrec CreateThemeAlias
$creadPrec :: ReadPrec CreateThemeAlias
readList :: ReadS [CreateThemeAlias]
$creadList :: ReadS [CreateThemeAlias]
readsPrec :: Int -> ReadS CreateThemeAlias
$creadsPrec :: Int -> ReadS CreateThemeAlias
Prelude.Read, Int -> CreateThemeAlias -> ShowS
[CreateThemeAlias] -> ShowS
CreateThemeAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateThemeAlias] -> ShowS
$cshowList :: [CreateThemeAlias] -> ShowS
show :: CreateThemeAlias -> String
$cshow :: CreateThemeAlias -> String
showsPrec :: Int -> CreateThemeAlias -> ShowS
$cshowsPrec :: Int -> CreateThemeAlias -> ShowS
Prelude.Show, forall x. Rep CreateThemeAlias x -> CreateThemeAlias
forall x. CreateThemeAlias -> Rep CreateThemeAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateThemeAlias x -> CreateThemeAlias
$cfrom :: forall x. CreateThemeAlias -> Rep CreateThemeAlias x
Prelude.Generic)

-- |
-- Create a value of 'CreateThemeAlias' 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:
--
-- 'awsAccountId', 'createThemeAlias_awsAccountId' - The ID of the Amazon Web Services account that contains the theme for
-- the new theme alias.
--
-- 'themeId', 'createThemeAlias_themeId' - An ID for the theme alias.
--
-- 'aliasName', 'createThemeAlias_aliasName' - The name that you want to give to the theme alias that you are creating.
-- The alias name can\'t begin with a @$@. Alias names that start with @$@
-- are reserved by Amazon QuickSight.
--
-- 'themeVersionNumber', 'createThemeAlias_themeVersionNumber' - The version number of the theme.
newCreateThemeAlias ::
  -- | 'awsAccountId'
  Prelude.Text ->
  -- | 'themeId'
  Prelude.Text ->
  -- | 'aliasName'
  Prelude.Text ->
  -- | 'themeVersionNumber'
  Prelude.Natural ->
  CreateThemeAlias
newCreateThemeAlias :: Text -> Text -> Text -> Natural -> CreateThemeAlias
newCreateThemeAlias
  Text
pAwsAccountId_
  Text
pThemeId_
  Text
pAliasName_
  Natural
pThemeVersionNumber_ =
    CreateThemeAlias'
      { $sel:awsAccountId:CreateThemeAlias' :: Text
awsAccountId = Text
pAwsAccountId_,
        $sel:themeId:CreateThemeAlias' :: Text
themeId = Text
pThemeId_,
        $sel:aliasName:CreateThemeAlias' :: Text
aliasName = Text
pAliasName_,
        $sel:themeVersionNumber:CreateThemeAlias' :: Natural
themeVersionNumber = Natural
pThemeVersionNumber_
      }

-- | The ID of the Amazon Web Services account that contains the theme for
-- the new theme alias.
createThemeAlias_awsAccountId :: Lens.Lens' CreateThemeAlias Prelude.Text
createThemeAlias_awsAccountId :: Lens' CreateThemeAlias Text
createThemeAlias_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThemeAlias' {Text
awsAccountId :: Text
$sel:awsAccountId:CreateThemeAlias' :: CreateThemeAlias -> Text
awsAccountId} -> Text
awsAccountId) (\s :: CreateThemeAlias
s@CreateThemeAlias' {} Text
a -> CreateThemeAlias
s {$sel:awsAccountId:CreateThemeAlias' :: Text
awsAccountId = Text
a} :: CreateThemeAlias)

-- | An ID for the theme alias.
createThemeAlias_themeId :: Lens.Lens' CreateThemeAlias Prelude.Text
createThemeAlias_themeId :: Lens' CreateThemeAlias Text
createThemeAlias_themeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThemeAlias' {Text
themeId :: Text
$sel:themeId:CreateThemeAlias' :: CreateThemeAlias -> Text
themeId} -> Text
themeId) (\s :: CreateThemeAlias
s@CreateThemeAlias' {} Text
a -> CreateThemeAlias
s {$sel:themeId:CreateThemeAlias' :: Text
themeId = Text
a} :: CreateThemeAlias)

-- | The name that you want to give to the theme alias that you are creating.
-- The alias name can\'t begin with a @$@. Alias names that start with @$@
-- are reserved by Amazon QuickSight.
createThemeAlias_aliasName :: Lens.Lens' CreateThemeAlias Prelude.Text
createThemeAlias_aliasName :: Lens' CreateThemeAlias Text
createThemeAlias_aliasName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThemeAlias' {Text
aliasName :: Text
$sel:aliasName:CreateThemeAlias' :: CreateThemeAlias -> Text
aliasName} -> Text
aliasName) (\s :: CreateThemeAlias
s@CreateThemeAlias' {} Text
a -> CreateThemeAlias
s {$sel:aliasName:CreateThemeAlias' :: Text
aliasName = Text
a} :: CreateThemeAlias)

-- | The version number of the theme.
createThemeAlias_themeVersionNumber :: Lens.Lens' CreateThemeAlias Prelude.Natural
createThemeAlias_themeVersionNumber :: Lens' CreateThemeAlias Natural
createThemeAlias_themeVersionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThemeAlias' {Natural
themeVersionNumber :: Natural
$sel:themeVersionNumber:CreateThemeAlias' :: CreateThemeAlias -> Natural
themeVersionNumber} -> Natural
themeVersionNumber) (\s :: CreateThemeAlias
s@CreateThemeAlias' {} Natural
a -> CreateThemeAlias
s {$sel:themeVersionNumber:CreateThemeAlias' :: Natural
themeVersionNumber = Natural
a} :: CreateThemeAlias)

instance Core.AWSRequest CreateThemeAlias where
  type
    AWSResponse CreateThemeAlias =
      CreateThemeAliasResponse
  request :: (Service -> Service)
-> CreateThemeAlias -> Request CreateThemeAlias
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateThemeAlias
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateThemeAlias)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe ThemeAlias -> Int -> CreateThemeAliasResponse
CreateThemeAliasResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RequestId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ThemeAlias")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateThemeAlias where
  hashWithSalt :: Int -> CreateThemeAlias -> Int
hashWithSalt Int
_salt CreateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:CreateThemeAlias' :: CreateThemeAlias -> Natural
$sel:aliasName:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:themeId:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:awsAccountId:CreateThemeAlias' :: CreateThemeAlias -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
awsAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
themeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
aliasName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
themeVersionNumber

instance Prelude.NFData CreateThemeAlias where
  rnf :: CreateThemeAlias -> ()
rnf CreateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:CreateThemeAlias' :: CreateThemeAlias -> Natural
$sel:aliasName:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:themeId:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:awsAccountId:CreateThemeAlias' :: CreateThemeAlias -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
awsAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
themeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
aliasName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
themeVersionNumber

instance Data.ToHeaders CreateThemeAlias where
  toHeaders :: CreateThemeAlias -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateThemeAlias where
  toJSON :: CreateThemeAlias -> Value
toJSON CreateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:CreateThemeAlias' :: CreateThemeAlias -> Natural
$sel:aliasName:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:themeId:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:awsAccountId:CreateThemeAlias' :: CreateThemeAlias -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ThemeVersionNumber" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
themeVersionNumber)
          ]
      )

instance Data.ToPath CreateThemeAlias where
  toPath :: CreateThemeAlias -> ByteString
toPath CreateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:CreateThemeAlias' :: CreateThemeAlias -> Natural
$sel:aliasName:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:themeId:CreateThemeAlias' :: CreateThemeAlias -> Text
$sel:awsAccountId:CreateThemeAlias' :: CreateThemeAlias -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/accounts/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
awsAccountId,
        ByteString
"/themes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
themeId,
        ByteString
"/aliases/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
aliasName
      ]

instance Data.ToQuery CreateThemeAlias where
  toQuery :: CreateThemeAlias -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newCreateThemeAliasResponse' smart constructor.
data CreateThemeAliasResponse = CreateThemeAliasResponse'
  { -- | The Amazon Web Services request ID for this operation.
    CreateThemeAliasResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | Information about the theme alias.
    CreateThemeAliasResponse -> Maybe ThemeAlias
themeAlias :: Prelude.Maybe ThemeAlias,
    -- | The HTTP status of the request.
    CreateThemeAliasResponse -> Int
status :: Prelude.Int
  }
  deriving (CreateThemeAliasResponse -> CreateThemeAliasResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateThemeAliasResponse -> CreateThemeAliasResponse -> Bool
$c/= :: CreateThemeAliasResponse -> CreateThemeAliasResponse -> Bool
== :: CreateThemeAliasResponse -> CreateThemeAliasResponse -> Bool
$c== :: CreateThemeAliasResponse -> CreateThemeAliasResponse -> Bool
Prelude.Eq, ReadPrec [CreateThemeAliasResponse]
ReadPrec CreateThemeAliasResponse
Int -> ReadS CreateThemeAliasResponse
ReadS [CreateThemeAliasResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateThemeAliasResponse]
$creadListPrec :: ReadPrec [CreateThemeAliasResponse]
readPrec :: ReadPrec CreateThemeAliasResponse
$creadPrec :: ReadPrec CreateThemeAliasResponse
readList :: ReadS [CreateThemeAliasResponse]
$creadList :: ReadS [CreateThemeAliasResponse]
readsPrec :: Int -> ReadS CreateThemeAliasResponse
$creadsPrec :: Int -> ReadS CreateThemeAliasResponse
Prelude.Read, Int -> CreateThemeAliasResponse -> ShowS
[CreateThemeAliasResponse] -> ShowS
CreateThemeAliasResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateThemeAliasResponse] -> ShowS
$cshowList :: [CreateThemeAliasResponse] -> ShowS
show :: CreateThemeAliasResponse -> String
$cshow :: CreateThemeAliasResponse -> String
showsPrec :: Int -> CreateThemeAliasResponse -> ShowS
$cshowsPrec :: Int -> CreateThemeAliasResponse -> ShowS
Prelude.Show, forall x.
Rep CreateThemeAliasResponse x -> CreateThemeAliasResponse
forall x.
CreateThemeAliasResponse -> Rep CreateThemeAliasResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateThemeAliasResponse x -> CreateThemeAliasResponse
$cfrom :: forall x.
CreateThemeAliasResponse -> Rep CreateThemeAliasResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateThemeAliasResponse' 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:
--
-- 'requestId', 'createThemeAliasResponse_requestId' - The Amazon Web Services request ID for this operation.
--
-- 'themeAlias', 'createThemeAliasResponse_themeAlias' - Information about the theme alias.
--
-- 'status', 'createThemeAliasResponse_status' - The HTTP status of the request.
newCreateThemeAliasResponse ::
  -- | 'status'
  Prelude.Int ->
  CreateThemeAliasResponse
newCreateThemeAliasResponse :: Int -> CreateThemeAliasResponse
newCreateThemeAliasResponse Int
pStatus_ =
  CreateThemeAliasResponse'
    { $sel:requestId:CreateThemeAliasResponse' :: Maybe Text
requestId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:themeAlias:CreateThemeAliasResponse' :: Maybe ThemeAlias
themeAlias = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateThemeAliasResponse' :: Int
status = Int
pStatus_
    }

-- | The Amazon Web Services request ID for this operation.
createThemeAliasResponse_requestId :: Lens.Lens' CreateThemeAliasResponse (Prelude.Maybe Prelude.Text)
createThemeAliasResponse_requestId :: Lens' CreateThemeAliasResponse (Maybe Text)
createThemeAliasResponse_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThemeAliasResponse' {Maybe Text
requestId :: Maybe Text
$sel:requestId:CreateThemeAliasResponse' :: CreateThemeAliasResponse -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: CreateThemeAliasResponse
s@CreateThemeAliasResponse' {} Maybe Text
a -> CreateThemeAliasResponse
s {$sel:requestId:CreateThemeAliasResponse' :: Maybe Text
requestId = Maybe Text
a} :: CreateThemeAliasResponse)

-- | Information about the theme alias.
createThemeAliasResponse_themeAlias :: Lens.Lens' CreateThemeAliasResponse (Prelude.Maybe ThemeAlias)
createThemeAliasResponse_themeAlias :: Lens' CreateThemeAliasResponse (Maybe ThemeAlias)
createThemeAliasResponse_themeAlias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThemeAliasResponse' {Maybe ThemeAlias
themeAlias :: Maybe ThemeAlias
$sel:themeAlias:CreateThemeAliasResponse' :: CreateThemeAliasResponse -> Maybe ThemeAlias
themeAlias} -> Maybe ThemeAlias
themeAlias) (\s :: CreateThemeAliasResponse
s@CreateThemeAliasResponse' {} Maybe ThemeAlias
a -> CreateThemeAliasResponse
s {$sel:themeAlias:CreateThemeAliasResponse' :: Maybe ThemeAlias
themeAlias = Maybe ThemeAlias
a} :: CreateThemeAliasResponse)

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

instance Prelude.NFData CreateThemeAliasResponse where
  rnf :: CreateThemeAliasResponse -> ()
rnf CreateThemeAliasResponse' {Int
Maybe Text
Maybe ThemeAlias
status :: Int
themeAlias :: Maybe ThemeAlias
requestId :: Maybe Text
$sel:status:CreateThemeAliasResponse' :: CreateThemeAliasResponse -> Int
$sel:themeAlias:CreateThemeAliasResponse' :: CreateThemeAliasResponse -> Maybe ThemeAlias
$sel:requestId:CreateThemeAliasResponse' :: CreateThemeAliasResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ThemeAlias
themeAlias
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
status