{-# 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.IoT.CreateRoleAlias
-- 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 role alias.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions CreateRoleAlias>
-- action.
module Amazonka.IoT.CreateRoleAlias
  ( -- * Creating a Request
    CreateRoleAlias (..),
    newCreateRoleAlias,

    -- * Request Lenses
    createRoleAlias_credentialDurationSeconds,
    createRoleAlias_tags,
    createRoleAlias_roleAlias,
    createRoleAlias_roleArn,

    -- * Destructuring the Response
    CreateRoleAliasResponse (..),
    newCreateRoleAliasResponse,

    -- * Response Lenses
    createRoleAliasResponse_roleAlias,
    createRoleAliasResponse_roleAliasArn,
    createRoleAliasResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoT.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateRoleAlias' smart constructor.
data CreateRoleAlias = CreateRoleAlias'
  { -- | How long (in seconds) the credentials will be valid. The default value
    -- is 3,600 seconds.
    --
    -- This value must be less than or equal to the maximum session duration of
    -- the IAM role that the role alias references.
    CreateRoleAlias -> Maybe Natural
credentialDurationSeconds :: Prelude.Maybe Prelude.Natural,
    -- | Metadata which can be used to manage the role alias.
    --
    -- For URI Request parameters use format: ...key1=value1&key2=value2...
    --
    -- For the CLI command-line parameter use format: &&tags
    -- \"key1=value1&key2=value2...\"
    --
    -- For the cli-input-json file use format: \"tags\":
    -- \"key1=value1&key2=value2...\"
    CreateRoleAlias -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The role alias that points to a role ARN. This allows you to change the
    -- role without having to update the device.
    CreateRoleAlias -> Text
roleAlias :: Prelude.Text,
    -- | The role ARN.
    CreateRoleAlias -> Text
roleArn :: Prelude.Text
  }
  deriving (CreateRoleAlias -> CreateRoleAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRoleAlias -> CreateRoleAlias -> Bool
$c/= :: CreateRoleAlias -> CreateRoleAlias -> Bool
== :: CreateRoleAlias -> CreateRoleAlias -> Bool
$c== :: CreateRoleAlias -> CreateRoleAlias -> Bool
Prelude.Eq, ReadPrec [CreateRoleAlias]
ReadPrec CreateRoleAlias
Int -> ReadS CreateRoleAlias
ReadS [CreateRoleAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRoleAlias]
$creadListPrec :: ReadPrec [CreateRoleAlias]
readPrec :: ReadPrec CreateRoleAlias
$creadPrec :: ReadPrec CreateRoleAlias
readList :: ReadS [CreateRoleAlias]
$creadList :: ReadS [CreateRoleAlias]
readsPrec :: Int -> ReadS CreateRoleAlias
$creadsPrec :: Int -> ReadS CreateRoleAlias
Prelude.Read, Int -> CreateRoleAlias -> ShowS
[CreateRoleAlias] -> ShowS
CreateRoleAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRoleAlias] -> ShowS
$cshowList :: [CreateRoleAlias] -> ShowS
show :: CreateRoleAlias -> String
$cshow :: CreateRoleAlias -> String
showsPrec :: Int -> CreateRoleAlias -> ShowS
$cshowsPrec :: Int -> CreateRoleAlias -> ShowS
Prelude.Show, forall x. Rep CreateRoleAlias x -> CreateRoleAlias
forall x. CreateRoleAlias -> Rep CreateRoleAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRoleAlias x -> CreateRoleAlias
$cfrom :: forall x. CreateRoleAlias -> Rep CreateRoleAlias x
Prelude.Generic)

-- |
-- Create a value of 'CreateRoleAlias' 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:
--
-- 'credentialDurationSeconds', 'createRoleAlias_credentialDurationSeconds' - How long (in seconds) the credentials will be valid. The default value
-- is 3,600 seconds.
--
-- This value must be less than or equal to the maximum session duration of
-- the IAM role that the role alias references.
--
-- 'tags', 'createRoleAlias_tags' - Metadata which can be used to manage the role alias.
--
-- For URI Request parameters use format: ...key1=value1&key2=value2...
--
-- For the CLI command-line parameter use format: &&tags
-- \"key1=value1&key2=value2...\"
--
-- For the cli-input-json file use format: \"tags\":
-- \"key1=value1&key2=value2...\"
--
-- 'roleAlias', 'createRoleAlias_roleAlias' - The role alias that points to a role ARN. This allows you to change the
-- role without having to update the device.
--
-- 'roleArn', 'createRoleAlias_roleArn' - The role ARN.
newCreateRoleAlias ::
  -- | 'roleAlias'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  CreateRoleAlias
newCreateRoleAlias :: Text -> Text -> CreateRoleAlias
newCreateRoleAlias Text
pRoleAlias_ Text
pRoleArn_ =
  CreateRoleAlias'
    { $sel:credentialDurationSeconds:CreateRoleAlias' :: Maybe Natural
credentialDurationSeconds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateRoleAlias' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:roleAlias:CreateRoleAlias' :: Text
roleAlias = Text
pRoleAlias_,
      $sel:roleArn:CreateRoleAlias' :: Text
roleArn = Text
pRoleArn_
    }

-- | How long (in seconds) the credentials will be valid. The default value
-- is 3,600 seconds.
--
-- This value must be less than or equal to the maximum session duration of
-- the IAM role that the role alias references.
createRoleAlias_credentialDurationSeconds :: Lens.Lens' CreateRoleAlias (Prelude.Maybe Prelude.Natural)
createRoleAlias_credentialDurationSeconds :: Lens' CreateRoleAlias (Maybe Natural)
createRoleAlias_credentialDurationSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAlias' {Maybe Natural
credentialDurationSeconds :: Maybe Natural
$sel:credentialDurationSeconds:CreateRoleAlias' :: CreateRoleAlias -> Maybe Natural
credentialDurationSeconds} -> Maybe Natural
credentialDurationSeconds) (\s :: CreateRoleAlias
s@CreateRoleAlias' {} Maybe Natural
a -> CreateRoleAlias
s {$sel:credentialDurationSeconds:CreateRoleAlias' :: Maybe Natural
credentialDurationSeconds = Maybe Natural
a} :: CreateRoleAlias)

-- | Metadata which can be used to manage the role alias.
--
-- For URI Request parameters use format: ...key1=value1&key2=value2...
--
-- For the CLI command-line parameter use format: &&tags
-- \"key1=value1&key2=value2...\"
--
-- For the cli-input-json file use format: \"tags\":
-- \"key1=value1&key2=value2...\"
createRoleAlias_tags :: Lens.Lens' CreateRoleAlias (Prelude.Maybe [Tag])
createRoleAlias_tags :: Lens' CreateRoleAlias (Maybe [Tag])
createRoleAlias_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAlias' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateRoleAlias' :: CreateRoleAlias -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateRoleAlias
s@CreateRoleAlias' {} Maybe [Tag]
a -> CreateRoleAlias
s {$sel:tags:CreateRoleAlias' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateRoleAlias) 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 role alias that points to a role ARN. This allows you to change the
-- role without having to update the device.
createRoleAlias_roleAlias :: Lens.Lens' CreateRoleAlias Prelude.Text
createRoleAlias_roleAlias :: Lens' CreateRoleAlias Text
createRoleAlias_roleAlias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAlias' {Text
roleAlias :: Text
$sel:roleAlias:CreateRoleAlias' :: CreateRoleAlias -> Text
roleAlias} -> Text
roleAlias) (\s :: CreateRoleAlias
s@CreateRoleAlias' {} Text
a -> CreateRoleAlias
s {$sel:roleAlias:CreateRoleAlias' :: Text
roleAlias = Text
a} :: CreateRoleAlias)

-- | The role ARN.
createRoleAlias_roleArn :: Lens.Lens' CreateRoleAlias Prelude.Text
createRoleAlias_roleArn :: Lens' CreateRoleAlias Text
createRoleAlias_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAlias' {Text
roleArn :: Text
$sel:roleArn:CreateRoleAlias' :: CreateRoleAlias -> Text
roleArn} -> Text
roleArn) (\s :: CreateRoleAlias
s@CreateRoleAlias' {} Text
a -> CreateRoleAlias
s {$sel:roleArn:CreateRoleAlias' :: Text
roleArn = Text
a} :: CreateRoleAlias)

instance Core.AWSRequest CreateRoleAlias where
  type
    AWSResponse CreateRoleAlias =
      CreateRoleAliasResponse
  request :: (Service -> Service) -> CreateRoleAlias -> Request CreateRoleAlias
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 CreateRoleAlias
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateRoleAlias)))
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 Text -> Int -> CreateRoleAliasResponse
CreateRoleAliasResponse'
            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
"roleAlias")
            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
"roleAliasArn")
            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 CreateRoleAlias where
  hashWithSalt :: Int -> CreateRoleAlias -> Int
hashWithSalt Int
_salt CreateRoleAlias' {Maybe Natural
Maybe [Tag]
Text
roleArn :: Text
roleAlias :: Text
tags :: Maybe [Tag]
credentialDurationSeconds :: Maybe Natural
$sel:roleArn:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:roleAlias:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:tags:CreateRoleAlias' :: CreateRoleAlias -> Maybe [Tag]
$sel:credentialDurationSeconds:CreateRoleAlias' :: CreateRoleAlias -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
credentialDurationSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleAlias
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData CreateRoleAlias where
  rnf :: CreateRoleAlias -> ()
rnf CreateRoleAlias' {Maybe Natural
Maybe [Tag]
Text
roleArn :: Text
roleAlias :: Text
tags :: Maybe [Tag]
credentialDurationSeconds :: Maybe Natural
$sel:roleArn:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:roleAlias:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:tags:CreateRoleAlias' :: CreateRoleAlias -> Maybe [Tag]
$sel:credentialDurationSeconds:CreateRoleAlias' :: CreateRoleAlias -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
credentialDurationSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleAlias
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

instance Data.ToHeaders CreateRoleAlias where
  toHeaders :: CreateRoleAlias -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateRoleAlias where
  toJSON :: CreateRoleAlias -> Value
toJSON CreateRoleAlias' {Maybe Natural
Maybe [Tag]
Text
roleArn :: Text
roleAlias :: Text
tags :: Maybe [Tag]
credentialDurationSeconds :: Maybe Natural
$sel:roleArn:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:roleAlias:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:tags:CreateRoleAlias' :: CreateRoleAlias -> Maybe [Tag]
$sel:credentialDurationSeconds:CreateRoleAlias' :: CreateRoleAlias -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"credentialDurationSeconds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
credentialDurationSeconds,
            (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"roleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn)
          ]
      )

instance Data.ToPath CreateRoleAlias where
  toPath :: CreateRoleAlias -> ByteString
toPath CreateRoleAlias' {Maybe Natural
Maybe [Tag]
Text
roleArn :: Text
roleAlias :: Text
tags :: Maybe [Tag]
credentialDurationSeconds :: Maybe Natural
$sel:roleArn:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:roleAlias:CreateRoleAlias' :: CreateRoleAlias -> Text
$sel:tags:CreateRoleAlias' :: CreateRoleAlias -> Maybe [Tag]
$sel:credentialDurationSeconds:CreateRoleAlias' :: CreateRoleAlias -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/role-aliases/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
roleAlias]

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

-- | /See:/ 'newCreateRoleAliasResponse' smart constructor.
data CreateRoleAliasResponse = CreateRoleAliasResponse'
  { -- | The role alias.
    CreateRoleAliasResponse -> Maybe Text
roleAlias :: Prelude.Maybe Prelude.Text,
    -- | The role alias ARN.
    CreateRoleAliasResponse -> Maybe Text
roleAliasArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateRoleAliasResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateRoleAliasResponse -> CreateRoleAliasResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRoleAliasResponse -> CreateRoleAliasResponse -> Bool
$c/= :: CreateRoleAliasResponse -> CreateRoleAliasResponse -> Bool
== :: CreateRoleAliasResponse -> CreateRoleAliasResponse -> Bool
$c== :: CreateRoleAliasResponse -> CreateRoleAliasResponse -> Bool
Prelude.Eq, ReadPrec [CreateRoleAliasResponse]
ReadPrec CreateRoleAliasResponse
Int -> ReadS CreateRoleAliasResponse
ReadS [CreateRoleAliasResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRoleAliasResponse]
$creadListPrec :: ReadPrec [CreateRoleAliasResponse]
readPrec :: ReadPrec CreateRoleAliasResponse
$creadPrec :: ReadPrec CreateRoleAliasResponse
readList :: ReadS [CreateRoleAliasResponse]
$creadList :: ReadS [CreateRoleAliasResponse]
readsPrec :: Int -> ReadS CreateRoleAliasResponse
$creadsPrec :: Int -> ReadS CreateRoleAliasResponse
Prelude.Read, Int -> CreateRoleAliasResponse -> ShowS
[CreateRoleAliasResponse] -> ShowS
CreateRoleAliasResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRoleAliasResponse] -> ShowS
$cshowList :: [CreateRoleAliasResponse] -> ShowS
show :: CreateRoleAliasResponse -> String
$cshow :: CreateRoleAliasResponse -> String
showsPrec :: Int -> CreateRoleAliasResponse -> ShowS
$cshowsPrec :: Int -> CreateRoleAliasResponse -> ShowS
Prelude.Show, forall x. Rep CreateRoleAliasResponse x -> CreateRoleAliasResponse
forall x. CreateRoleAliasResponse -> Rep CreateRoleAliasResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRoleAliasResponse x -> CreateRoleAliasResponse
$cfrom :: forall x. CreateRoleAliasResponse -> Rep CreateRoleAliasResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateRoleAliasResponse' 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:
--
-- 'roleAlias', 'createRoleAliasResponse_roleAlias' - The role alias.
--
-- 'roleAliasArn', 'createRoleAliasResponse_roleAliasArn' - The role alias ARN.
--
-- 'httpStatus', 'createRoleAliasResponse_httpStatus' - The response's http status code.
newCreateRoleAliasResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateRoleAliasResponse
newCreateRoleAliasResponse :: Int -> CreateRoleAliasResponse
newCreateRoleAliasResponse Int
pHttpStatus_ =
  CreateRoleAliasResponse'
    { $sel:roleAlias:CreateRoleAliasResponse' :: Maybe Text
roleAlias =
        forall a. Maybe a
Prelude.Nothing,
      $sel:roleAliasArn:CreateRoleAliasResponse' :: Maybe Text
roleAliasArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateRoleAliasResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The role alias.
createRoleAliasResponse_roleAlias :: Lens.Lens' CreateRoleAliasResponse (Prelude.Maybe Prelude.Text)
createRoleAliasResponse_roleAlias :: Lens' CreateRoleAliasResponse (Maybe Text)
createRoleAliasResponse_roleAlias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAliasResponse' {Maybe Text
roleAlias :: Maybe Text
$sel:roleAlias:CreateRoleAliasResponse' :: CreateRoleAliasResponse -> Maybe Text
roleAlias} -> Maybe Text
roleAlias) (\s :: CreateRoleAliasResponse
s@CreateRoleAliasResponse' {} Maybe Text
a -> CreateRoleAliasResponse
s {$sel:roleAlias:CreateRoleAliasResponse' :: Maybe Text
roleAlias = Maybe Text
a} :: CreateRoleAliasResponse)

-- | The role alias ARN.
createRoleAliasResponse_roleAliasArn :: Lens.Lens' CreateRoleAliasResponse (Prelude.Maybe Prelude.Text)
createRoleAliasResponse_roleAliasArn :: Lens' CreateRoleAliasResponse (Maybe Text)
createRoleAliasResponse_roleAliasArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAliasResponse' {Maybe Text
roleAliasArn :: Maybe Text
$sel:roleAliasArn:CreateRoleAliasResponse' :: CreateRoleAliasResponse -> Maybe Text
roleAliasArn} -> Maybe Text
roleAliasArn) (\s :: CreateRoleAliasResponse
s@CreateRoleAliasResponse' {} Maybe Text
a -> CreateRoleAliasResponse
s {$sel:roleAliasArn:CreateRoleAliasResponse' :: Maybe Text
roleAliasArn = Maybe Text
a} :: CreateRoleAliasResponse)

-- | The response's http status code.
createRoleAliasResponse_httpStatus :: Lens.Lens' CreateRoleAliasResponse Prelude.Int
createRoleAliasResponse_httpStatus :: Lens' CreateRoleAliasResponse Int
createRoleAliasResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRoleAliasResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateRoleAliasResponse' :: CreateRoleAliasResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateRoleAliasResponse
s@CreateRoleAliasResponse' {} Int
a -> CreateRoleAliasResponse
s {$sel:httpStatus:CreateRoleAliasResponse' :: Int
httpStatus = Int
a} :: CreateRoleAliasResponse)

instance Prelude.NFData CreateRoleAliasResponse where
  rnf :: CreateRoleAliasResponse -> ()
rnf CreateRoleAliasResponse' {Int
Maybe Text
httpStatus :: Int
roleAliasArn :: Maybe Text
roleAlias :: Maybe Text
$sel:httpStatus:CreateRoleAliasResponse' :: CreateRoleAliasResponse -> Int
$sel:roleAliasArn:CreateRoleAliasResponse' :: CreateRoleAliasResponse -> Maybe Text
$sel:roleAlias:CreateRoleAliasResponse' :: CreateRoleAliasResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleAlias
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleAliasArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus