{-# 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.UpdateThemeAlias
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an alias of a theme.
module Amazonka.QuickSight.UpdateThemeAlias
  ( -- * Creating a Request
    UpdateThemeAlias (..),
    newUpdateThemeAlias,

    -- * Request Lenses
    updateThemeAlias_awsAccountId,
    updateThemeAlias_themeId,
    updateThemeAlias_aliasName,
    updateThemeAlias_themeVersionNumber,

    -- * Destructuring the Response
    UpdateThemeAliasResponse (..),
    newUpdateThemeAliasResponse,

    -- * Response Lenses
    updateThemeAliasResponse_requestId,
    updateThemeAliasResponse_themeAlias,
    updateThemeAliasResponse_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:/ 'newUpdateThemeAlias' smart constructor.
data UpdateThemeAlias = UpdateThemeAlias'
  { -- | The ID of the Amazon Web Services account that contains the theme alias
    -- that you\'re updating.
    UpdateThemeAlias -> Text
awsAccountId :: Prelude.Text,
    -- | The ID for the theme.
    UpdateThemeAlias -> Text
themeId :: Prelude.Text,
    -- | The name of the theme alias that you want to update.
    UpdateThemeAlias -> Text
aliasName :: Prelude.Text,
    -- | The version number of the theme that the alias should reference.
    UpdateThemeAlias -> Natural
themeVersionNumber :: Prelude.Natural
  }
  deriving (UpdateThemeAlias -> UpdateThemeAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateThemeAlias -> UpdateThemeAlias -> Bool
$c/= :: UpdateThemeAlias -> UpdateThemeAlias -> Bool
== :: UpdateThemeAlias -> UpdateThemeAlias -> Bool
$c== :: UpdateThemeAlias -> UpdateThemeAlias -> Bool
Prelude.Eq, ReadPrec [UpdateThemeAlias]
ReadPrec UpdateThemeAlias
Int -> ReadS UpdateThemeAlias
ReadS [UpdateThemeAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateThemeAlias]
$creadListPrec :: ReadPrec [UpdateThemeAlias]
readPrec :: ReadPrec UpdateThemeAlias
$creadPrec :: ReadPrec UpdateThemeAlias
readList :: ReadS [UpdateThemeAlias]
$creadList :: ReadS [UpdateThemeAlias]
readsPrec :: Int -> ReadS UpdateThemeAlias
$creadsPrec :: Int -> ReadS UpdateThemeAlias
Prelude.Read, Int -> UpdateThemeAlias -> ShowS
[UpdateThemeAlias] -> ShowS
UpdateThemeAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateThemeAlias] -> ShowS
$cshowList :: [UpdateThemeAlias] -> ShowS
show :: UpdateThemeAlias -> String
$cshow :: UpdateThemeAlias -> String
showsPrec :: Int -> UpdateThemeAlias -> ShowS
$cshowsPrec :: Int -> UpdateThemeAlias -> ShowS
Prelude.Show, forall x. Rep UpdateThemeAlias x -> UpdateThemeAlias
forall x. UpdateThemeAlias -> Rep UpdateThemeAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateThemeAlias x -> UpdateThemeAlias
$cfrom :: forall x. UpdateThemeAlias -> Rep UpdateThemeAlias x
Prelude.Generic)

-- |
-- Create a value of 'UpdateThemeAlias' 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', 'updateThemeAlias_awsAccountId' - The ID of the Amazon Web Services account that contains the theme alias
-- that you\'re updating.
--
-- 'themeId', 'updateThemeAlias_themeId' - The ID for the theme.
--
-- 'aliasName', 'updateThemeAlias_aliasName' - The name of the theme alias that you want to update.
--
-- 'themeVersionNumber', 'updateThemeAlias_themeVersionNumber' - The version number of the theme that the alias should reference.
newUpdateThemeAlias ::
  -- | 'awsAccountId'
  Prelude.Text ->
  -- | 'themeId'
  Prelude.Text ->
  -- | 'aliasName'
  Prelude.Text ->
  -- | 'themeVersionNumber'
  Prelude.Natural ->
  UpdateThemeAlias
newUpdateThemeAlias :: Text -> Text -> Text -> Natural -> UpdateThemeAlias
newUpdateThemeAlias
  Text
pAwsAccountId_
  Text
pThemeId_
  Text
pAliasName_
  Natural
pThemeVersionNumber_ =
    UpdateThemeAlias'
      { $sel:awsAccountId:UpdateThemeAlias' :: Text
awsAccountId = Text
pAwsAccountId_,
        $sel:themeId:UpdateThemeAlias' :: Text
themeId = Text
pThemeId_,
        $sel:aliasName:UpdateThemeAlias' :: Text
aliasName = Text
pAliasName_,
        $sel:themeVersionNumber:UpdateThemeAlias' :: Natural
themeVersionNumber = Natural
pThemeVersionNumber_
      }

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

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

-- | The name of the theme alias that you want to update.
updateThemeAlias_aliasName :: Lens.Lens' UpdateThemeAlias Prelude.Text
updateThemeAlias_aliasName :: Lens' UpdateThemeAlias Text
updateThemeAlias_aliasName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThemeAlias' {Text
aliasName :: Text
$sel:aliasName:UpdateThemeAlias' :: UpdateThemeAlias -> Text
aliasName} -> Text
aliasName) (\s :: UpdateThemeAlias
s@UpdateThemeAlias' {} Text
a -> UpdateThemeAlias
s {$sel:aliasName:UpdateThemeAlias' :: Text
aliasName = Text
a} :: UpdateThemeAlias)

-- | The version number of the theme that the alias should reference.
updateThemeAlias_themeVersionNumber :: Lens.Lens' UpdateThemeAlias Prelude.Natural
updateThemeAlias_themeVersionNumber :: Lens' UpdateThemeAlias Natural
updateThemeAlias_themeVersionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateThemeAlias' {Natural
themeVersionNumber :: Natural
$sel:themeVersionNumber:UpdateThemeAlias' :: UpdateThemeAlias -> Natural
themeVersionNumber} -> Natural
themeVersionNumber) (\s :: UpdateThemeAlias
s@UpdateThemeAlias' {} Natural
a -> UpdateThemeAlias
s {$sel:themeVersionNumber:UpdateThemeAlias' :: Natural
themeVersionNumber = Natural
a} :: UpdateThemeAlias)

instance Core.AWSRequest UpdateThemeAlias where
  type
    AWSResponse UpdateThemeAlias =
      UpdateThemeAliasResponse
  request :: (Service -> Service)
-> UpdateThemeAlias -> Request UpdateThemeAlias
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateThemeAlias
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateThemeAlias)))
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 -> UpdateThemeAliasResponse
UpdateThemeAliasResponse'
            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 UpdateThemeAlias where
  hashWithSalt :: Int -> UpdateThemeAlias -> Int
hashWithSalt Int
_salt UpdateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:UpdateThemeAlias' :: UpdateThemeAlias -> Natural
$sel:aliasName:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:themeId:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:awsAccountId:UpdateThemeAlias' :: UpdateThemeAlias -> 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 UpdateThemeAlias where
  rnf :: UpdateThemeAlias -> ()
rnf UpdateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:UpdateThemeAlias' :: UpdateThemeAlias -> Natural
$sel:aliasName:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:themeId:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:awsAccountId:UpdateThemeAlias' :: UpdateThemeAlias -> 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 UpdateThemeAlias where
  toHeaders :: UpdateThemeAlias -> 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 UpdateThemeAlias where
  toJSON :: UpdateThemeAlias -> Value
toJSON UpdateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:UpdateThemeAlias' :: UpdateThemeAlias -> Natural
$sel:aliasName:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:themeId:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:awsAccountId:UpdateThemeAlias' :: UpdateThemeAlias -> 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 UpdateThemeAlias where
  toPath :: UpdateThemeAlias -> ByteString
toPath UpdateThemeAlias' {Natural
Text
themeVersionNumber :: Natural
aliasName :: Text
themeId :: Text
awsAccountId :: Text
$sel:themeVersionNumber:UpdateThemeAlias' :: UpdateThemeAlias -> Natural
$sel:aliasName:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:themeId:UpdateThemeAlias' :: UpdateThemeAlias -> Text
$sel:awsAccountId:UpdateThemeAlias' :: UpdateThemeAlias -> 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 UpdateThemeAlias where
  toQuery :: UpdateThemeAlias -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

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

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

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

instance Prelude.NFData UpdateThemeAliasResponse where
  rnf :: UpdateThemeAliasResponse -> ()
rnf UpdateThemeAliasResponse' {Int
Maybe Text
Maybe ThemeAlias
status :: Int
themeAlias :: Maybe ThemeAlias
requestId :: Maybe Text
$sel:status:UpdateThemeAliasResponse' :: UpdateThemeAliasResponse -> Int
$sel:themeAlias:UpdateThemeAliasResponse' :: UpdateThemeAliasResponse -> Maybe ThemeAlias
$sel:requestId:UpdateThemeAliasResponse' :: UpdateThemeAliasResponse -> 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