{-# 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.IAM.CreateServiceLinkedRole
-- 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 an IAM role that is linked to a specific Amazon Web Services
-- service. The service controls the attached policies and when the role
-- can be deleted. This helps ensure that the service is not broken by an
-- unexpectedly changed or deleted role, which could put your Amazon Web
-- Services resources into an unknown state. Allowing the service to
-- control the role helps improve service stability and proper cleanup when
-- a service and its role are no longer needed. For more information, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/using-service-linked-roles.html Using service-linked roles>
-- in the /IAM User Guide/.
--
-- To attach a policy to this service-linked role, you must make the
-- request using the Amazon Web Services service that depends on this role.
module Amazonka.IAM.CreateServiceLinkedRole
  ( -- * Creating a Request
    CreateServiceLinkedRole (..),
    newCreateServiceLinkedRole,

    -- * Request Lenses
    createServiceLinkedRole_customSuffix,
    createServiceLinkedRole_description,
    createServiceLinkedRole_aWSServiceName,

    -- * Destructuring the Response
    CreateServiceLinkedRoleResponse (..),
    newCreateServiceLinkedRoleResponse,

    -- * Response Lenses
    createServiceLinkedRoleResponse_role,
    createServiceLinkedRoleResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateServiceLinkedRole' smart constructor.
data CreateServiceLinkedRole = CreateServiceLinkedRole'
  { -- | A string that you provide, which is combined with the service-provided
    -- prefix to form the complete role name. If you make multiple requests for
    -- the same service, then you must supply a different @CustomSuffix@ for
    -- each request. Otherwise the request fails with a duplicate role name
    -- error. For example, you could add @-1@ or @-debug@ to the suffix.
    --
    -- Some services do not support the @CustomSuffix@ parameter. If you
    -- provide an optional suffix and the operation fails, try the operation
    -- again without the suffix.
    CreateServiceLinkedRole -> Maybe Text
customSuffix :: Prelude.Maybe Prelude.Text,
    -- | The description of the role.
    CreateServiceLinkedRole -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The service principal for the Amazon Web Services service to which this
    -- role is attached. You use a string similar to a URL but without the
    -- http:\/\/ in front. For example: @elasticbeanstalk.amazonaws.com@.
    --
    -- Service principals are unique and case-sensitive. To find the exact
    -- service principal for your service-linked role, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_aws-services-that-work-with-iam.html Amazon Web Services services that work with IAM>
    -- in the /IAM User Guide/. Look for the services that have __Yes__ in the
    -- __Service-Linked Role__ column. Choose the __Yes__ link to view the
    -- service-linked role documentation for that service.
    CreateServiceLinkedRole -> Text
aWSServiceName :: Prelude.Text
  }
  deriving (CreateServiceLinkedRole -> CreateServiceLinkedRole -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateServiceLinkedRole -> CreateServiceLinkedRole -> Bool
$c/= :: CreateServiceLinkedRole -> CreateServiceLinkedRole -> Bool
== :: CreateServiceLinkedRole -> CreateServiceLinkedRole -> Bool
$c== :: CreateServiceLinkedRole -> CreateServiceLinkedRole -> Bool
Prelude.Eq, ReadPrec [CreateServiceLinkedRole]
ReadPrec CreateServiceLinkedRole
Int -> ReadS CreateServiceLinkedRole
ReadS [CreateServiceLinkedRole]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateServiceLinkedRole]
$creadListPrec :: ReadPrec [CreateServiceLinkedRole]
readPrec :: ReadPrec CreateServiceLinkedRole
$creadPrec :: ReadPrec CreateServiceLinkedRole
readList :: ReadS [CreateServiceLinkedRole]
$creadList :: ReadS [CreateServiceLinkedRole]
readsPrec :: Int -> ReadS CreateServiceLinkedRole
$creadsPrec :: Int -> ReadS CreateServiceLinkedRole
Prelude.Read, Int -> CreateServiceLinkedRole -> ShowS
[CreateServiceLinkedRole] -> ShowS
CreateServiceLinkedRole -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateServiceLinkedRole] -> ShowS
$cshowList :: [CreateServiceLinkedRole] -> ShowS
show :: CreateServiceLinkedRole -> String
$cshow :: CreateServiceLinkedRole -> String
showsPrec :: Int -> CreateServiceLinkedRole -> ShowS
$cshowsPrec :: Int -> CreateServiceLinkedRole -> ShowS
Prelude.Show, forall x. Rep CreateServiceLinkedRole x -> CreateServiceLinkedRole
forall x. CreateServiceLinkedRole -> Rep CreateServiceLinkedRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateServiceLinkedRole x -> CreateServiceLinkedRole
$cfrom :: forall x. CreateServiceLinkedRole -> Rep CreateServiceLinkedRole x
Prelude.Generic)

-- |
-- Create a value of 'CreateServiceLinkedRole' 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:
--
-- 'customSuffix', 'createServiceLinkedRole_customSuffix' - A string that you provide, which is combined with the service-provided
-- prefix to form the complete role name. If you make multiple requests for
-- the same service, then you must supply a different @CustomSuffix@ for
-- each request. Otherwise the request fails with a duplicate role name
-- error. For example, you could add @-1@ or @-debug@ to the suffix.
--
-- Some services do not support the @CustomSuffix@ parameter. If you
-- provide an optional suffix and the operation fails, try the operation
-- again without the suffix.
--
-- 'description', 'createServiceLinkedRole_description' - The description of the role.
--
-- 'aWSServiceName', 'createServiceLinkedRole_aWSServiceName' - The service principal for the Amazon Web Services service to which this
-- role is attached. You use a string similar to a URL but without the
-- http:\/\/ in front. For example: @elasticbeanstalk.amazonaws.com@.
--
-- Service principals are unique and case-sensitive. To find the exact
-- service principal for your service-linked role, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_aws-services-that-work-with-iam.html Amazon Web Services services that work with IAM>
-- in the /IAM User Guide/. Look for the services that have __Yes__ in the
-- __Service-Linked Role__ column. Choose the __Yes__ link to view the
-- service-linked role documentation for that service.
newCreateServiceLinkedRole ::
  -- | 'aWSServiceName'
  Prelude.Text ->
  CreateServiceLinkedRole
newCreateServiceLinkedRole :: Text -> CreateServiceLinkedRole
newCreateServiceLinkedRole Text
pAWSServiceName_ =
  CreateServiceLinkedRole'
    { $sel:customSuffix:CreateServiceLinkedRole' :: Maybe Text
customSuffix =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:CreateServiceLinkedRole' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:aWSServiceName:CreateServiceLinkedRole' :: Text
aWSServiceName = Text
pAWSServiceName_
    }

-- | A string that you provide, which is combined with the service-provided
-- prefix to form the complete role name. If you make multiple requests for
-- the same service, then you must supply a different @CustomSuffix@ for
-- each request. Otherwise the request fails with a duplicate role name
-- error. For example, you could add @-1@ or @-debug@ to the suffix.
--
-- Some services do not support the @CustomSuffix@ parameter. If you
-- provide an optional suffix and the operation fails, try the operation
-- again without the suffix.
createServiceLinkedRole_customSuffix :: Lens.Lens' CreateServiceLinkedRole (Prelude.Maybe Prelude.Text)
createServiceLinkedRole_customSuffix :: Lens' CreateServiceLinkedRole (Maybe Text)
createServiceLinkedRole_customSuffix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceLinkedRole' {Maybe Text
customSuffix :: Maybe Text
$sel:customSuffix:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
customSuffix} -> Maybe Text
customSuffix) (\s :: CreateServiceLinkedRole
s@CreateServiceLinkedRole' {} Maybe Text
a -> CreateServiceLinkedRole
s {$sel:customSuffix:CreateServiceLinkedRole' :: Maybe Text
customSuffix = Maybe Text
a} :: CreateServiceLinkedRole)

-- | The description of the role.
createServiceLinkedRole_description :: Lens.Lens' CreateServiceLinkedRole (Prelude.Maybe Prelude.Text)
createServiceLinkedRole_description :: Lens' CreateServiceLinkedRole (Maybe Text)
createServiceLinkedRole_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceLinkedRole' {Maybe Text
description :: Maybe Text
$sel:description:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateServiceLinkedRole
s@CreateServiceLinkedRole' {} Maybe Text
a -> CreateServiceLinkedRole
s {$sel:description:CreateServiceLinkedRole' :: Maybe Text
description = Maybe Text
a} :: CreateServiceLinkedRole)

-- | The service principal for the Amazon Web Services service to which this
-- role is attached. You use a string similar to a URL but without the
-- http:\/\/ in front. For example: @elasticbeanstalk.amazonaws.com@.
--
-- Service principals are unique and case-sensitive. To find the exact
-- service principal for your service-linked role, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_aws-services-that-work-with-iam.html Amazon Web Services services that work with IAM>
-- in the /IAM User Guide/. Look for the services that have __Yes__ in the
-- __Service-Linked Role__ column. Choose the __Yes__ link to view the
-- service-linked role documentation for that service.
createServiceLinkedRole_aWSServiceName :: Lens.Lens' CreateServiceLinkedRole Prelude.Text
createServiceLinkedRole_aWSServiceName :: Lens' CreateServiceLinkedRole Text
createServiceLinkedRole_aWSServiceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceLinkedRole' {Text
aWSServiceName :: Text
$sel:aWSServiceName:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Text
aWSServiceName} -> Text
aWSServiceName) (\s :: CreateServiceLinkedRole
s@CreateServiceLinkedRole' {} Text
a -> CreateServiceLinkedRole
s {$sel:aWSServiceName:CreateServiceLinkedRole' :: Text
aWSServiceName = Text
a} :: CreateServiceLinkedRole)

instance Core.AWSRequest CreateServiceLinkedRole where
  type
    AWSResponse CreateServiceLinkedRole =
      CreateServiceLinkedRoleResponse
  request :: (Service -> Service)
-> CreateServiceLinkedRole -> Request CreateServiceLinkedRole
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateServiceLinkedRole
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateServiceLinkedRole)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"CreateServiceLinkedRoleResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Role -> Int -> CreateServiceLinkedRoleResponse
CreateServiceLinkedRoleResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Role")
            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 CreateServiceLinkedRole where
  hashWithSalt :: Int -> CreateServiceLinkedRole -> Int
hashWithSalt Int
_salt CreateServiceLinkedRole' {Maybe Text
Text
aWSServiceName :: Text
description :: Maybe Text
customSuffix :: Maybe Text
$sel:aWSServiceName:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Text
$sel:description:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
$sel:customSuffix:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customSuffix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
aWSServiceName

instance Prelude.NFData CreateServiceLinkedRole where
  rnf :: CreateServiceLinkedRole -> ()
rnf CreateServiceLinkedRole' {Maybe Text
Text
aWSServiceName :: Text
description :: Maybe Text
customSuffix :: Maybe Text
$sel:aWSServiceName:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Text
$sel:description:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
$sel:customSuffix:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customSuffix
      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 Text
aWSServiceName

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

instance Data.ToPath CreateServiceLinkedRole where
  toPath :: CreateServiceLinkedRole -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery CreateServiceLinkedRole where
  toQuery :: CreateServiceLinkedRole -> QueryString
toQuery CreateServiceLinkedRole' {Maybe Text
Text
aWSServiceName :: Text
description :: Maybe Text
customSuffix :: Maybe Text
$sel:aWSServiceName:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Text
$sel:description:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
$sel:customSuffix:CreateServiceLinkedRole' :: CreateServiceLinkedRole -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateServiceLinkedRole" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"CustomSuffix" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
customSuffix,
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
        ByteString
"AWSServiceName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
aWSServiceName
      ]

-- | /See:/ 'newCreateServiceLinkedRoleResponse' smart constructor.
data CreateServiceLinkedRoleResponse = CreateServiceLinkedRoleResponse'
  { -- | A Role object that contains details about the newly created role.
    CreateServiceLinkedRoleResponse -> Maybe Role
role' :: Prelude.Maybe Role,
    -- | The response's http status code.
    CreateServiceLinkedRoleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateServiceLinkedRoleResponse
-> CreateServiceLinkedRoleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateServiceLinkedRoleResponse
-> CreateServiceLinkedRoleResponse -> Bool
$c/= :: CreateServiceLinkedRoleResponse
-> CreateServiceLinkedRoleResponse -> Bool
== :: CreateServiceLinkedRoleResponse
-> CreateServiceLinkedRoleResponse -> Bool
$c== :: CreateServiceLinkedRoleResponse
-> CreateServiceLinkedRoleResponse -> Bool
Prelude.Eq, ReadPrec [CreateServiceLinkedRoleResponse]
ReadPrec CreateServiceLinkedRoleResponse
Int -> ReadS CreateServiceLinkedRoleResponse
ReadS [CreateServiceLinkedRoleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateServiceLinkedRoleResponse]
$creadListPrec :: ReadPrec [CreateServiceLinkedRoleResponse]
readPrec :: ReadPrec CreateServiceLinkedRoleResponse
$creadPrec :: ReadPrec CreateServiceLinkedRoleResponse
readList :: ReadS [CreateServiceLinkedRoleResponse]
$creadList :: ReadS [CreateServiceLinkedRoleResponse]
readsPrec :: Int -> ReadS CreateServiceLinkedRoleResponse
$creadsPrec :: Int -> ReadS CreateServiceLinkedRoleResponse
Prelude.Read, Int -> CreateServiceLinkedRoleResponse -> ShowS
[CreateServiceLinkedRoleResponse] -> ShowS
CreateServiceLinkedRoleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateServiceLinkedRoleResponse] -> ShowS
$cshowList :: [CreateServiceLinkedRoleResponse] -> ShowS
show :: CreateServiceLinkedRoleResponse -> String
$cshow :: CreateServiceLinkedRoleResponse -> String
showsPrec :: Int -> CreateServiceLinkedRoleResponse -> ShowS
$cshowsPrec :: Int -> CreateServiceLinkedRoleResponse -> ShowS
Prelude.Show, forall x.
Rep CreateServiceLinkedRoleResponse x
-> CreateServiceLinkedRoleResponse
forall x.
CreateServiceLinkedRoleResponse
-> Rep CreateServiceLinkedRoleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateServiceLinkedRoleResponse x
-> CreateServiceLinkedRoleResponse
$cfrom :: forall x.
CreateServiceLinkedRoleResponse
-> Rep CreateServiceLinkedRoleResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateServiceLinkedRoleResponse' 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:
--
-- 'role'', 'createServiceLinkedRoleResponse_role' - A Role object that contains details about the newly created role.
--
-- 'httpStatus', 'createServiceLinkedRoleResponse_httpStatus' - The response's http status code.
newCreateServiceLinkedRoleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateServiceLinkedRoleResponse
newCreateServiceLinkedRoleResponse :: Int -> CreateServiceLinkedRoleResponse
newCreateServiceLinkedRoleResponse Int
pHttpStatus_ =
  CreateServiceLinkedRoleResponse'
    { $sel:role':CreateServiceLinkedRoleResponse' :: Maybe Role
role' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateServiceLinkedRoleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A Role object that contains details about the newly created role.
createServiceLinkedRoleResponse_role :: Lens.Lens' CreateServiceLinkedRoleResponse (Prelude.Maybe Role)
createServiceLinkedRoleResponse_role :: Lens' CreateServiceLinkedRoleResponse (Maybe Role)
createServiceLinkedRoleResponse_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateServiceLinkedRoleResponse' {Maybe Role
role' :: Maybe Role
$sel:role':CreateServiceLinkedRoleResponse' :: CreateServiceLinkedRoleResponse -> Maybe Role
role'} -> Maybe Role
role') (\s :: CreateServiceLinkedRoleResponse
s@CreateServiceLinkedRoleResponse' {} Maybe Role
a -> CreateServiceLinkedRoleResponse
s {$sel:role':CreateServiceLinkedRoleResponse' :: Maybe Role
role' = Maybe Role
a} :: CreateServiceLinkedRoleResponse)

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

instance
  Prelude.NFData
    CreateServiceLinkedRoleResponse
  where
  rnf :: CreateServiceLinkedRoleResponse -> ()
rnf CreateServiceLinkedRoleResponse' {Int
Maybe Role
httpStatus :: Int
role' :: Maybe Role
$sel:httpStatus:CreateServiceLinkedRoleResponse' :: CreateServiceLinkedRoleResponse -> Int
$sel:role':CreateServiceLinkedRoleResponse' :: CreateServiceLinkedRoleResponse -> Maybe Role
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Role
role'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus