{-# 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.RAM.UpdateResourceShare
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies some of the properties of the specified resource share.
module Amazonka.RAM.UpdateResourceShare
  ( -- * Creating a Request
    UpdateResourceShare (..),
    newUpdateResourceShare,

    -- * Request Lenses
    updateResourceShare_allowExternalPrincipals,
    updateResourceShare_clientToken,
    updateResourceShare_name,
    updateResourceShare_resourceShareArn,

    -- * Destructuring the Response
    UpdateResourceShareResponse (..),
    newUpdateResourceShareResponse,

    -- * Response Lenses
    updateResourceShareResponse_clientToken,
    updateResourceShareResponse_resourceShare,
    updateResourceShareResponse_httpStatus,
  )
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.RAM.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateResourceShare' smart constructor.
data UpdateResourceShare = UpdateResourceShare'
  { -- | Specifies whether principals outside your organization in Organizations
    -- can be associated with a resource share.
    UpdateResourceShare -> Maybe Bool
allowExternalPrincipals :: Prelude.Maybe Prelude.Bool,
    -- | Specifies a unique, case-sensitive identifier that you provide to ensure
    -- the idempotency of the request. This lets you safely retry the request
    -- without accidentally performing the same operation a second time.
    -- Passing the same value to a later call to an operation requires that you
    -- also pass the same value for all other parameters. We recommend that you
    -- use a
    -- <https://wikipedia.org/wiki/Universally_unique_identifier UUID type of value.>.
    --
    -- If you don\'t provide this value, then Amazon Web Services generates a
    -- random one for you.
    UpdateResourceShare -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | If specified, the new name that you want to attach to the resource
    -- share.
    UpdateResourceShare -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Specifies the
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the resource share that you want to modify.
    UpdateResourceShare -> Text
resourceShareArn :: Prelude.Text
  }
  deriving (UpdateResourceShare -> UpdateResourceShare -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateResourceShare -> UpdateResourceShare -> Bool
$c/= :: UpdateResourceShare -> UpdateResourceShare -> Bool
== :: UpdateResourceShare -> UpdateResourceShare -> Bool
$c== :: UpdateResourceShare -> UpdateResourceShare -> Bool
Prelude.Eq, ReadPrec [UpdateResourceShare]
ReadPrec UpdateResourceShare
Int -> ReadS UpdateResourceShare
ReadS [UpdateResourceShare]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateResourceShare]
$creadListPrec :: ReadPrec [UpdateResourceShare]
readPrec :: ReadPrec UpdateResourceShare
$creadPrec :: ReadPrec UpdateResourceShare
readList :: ReadS [UpdateResourceShare]
$creadList :: ReadS [UpdateResourceShare]
readsPrec :: Int -> ReadS UpdateResourceShare
$creadsPrec :: Int -> ReadS UpdateResourceShare
Prelude.Read, Int -> UpdateResourceShare -> ShowS
[UpdateResourceShare] -> ShowS
UpdateResourceShare -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateResourceShare] -> ShowS
$cshowList :: [UpdateResourceShare] -> ShowS
show :: UpdateResourceShare -> String
$cshow :: UpdateResourceShare -> String
showsPrec :: Int -> UpdateResourceShare -> ShowS
$cshowsPrec :: Int -> UpdateResourceShare -> ShowS
Prelude.Show, forall x. Rep UpdateResourceShare x -> UpdateResourceShare
forall x. UpdateResourceShare -> Rep UpdateResourceShare x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateResourceShare x -> UpdateResourceShare
$cfrom :: forall x. UpdateResourceShare -> Rep UpdateResourceShare x
Prelude.Generic)

-- |
-- Create a value of 'UpdateResourceShare' 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:
--
-- 'allowExternalPrincipals', 'updateResourceShare_allowExternalPrincipals' - Specifies whether principals outside your organization in Organizations
-- can be associated with a resource share.
--
-- 'clientToken', 'updateResourceShare_clientToken' - Specifies a unique, case-sensitive identifier that you provide to ensure
-- the idempotency of the request. This lets you safely retry the request
-- without accidentally performing the same operation a second time.
-- Passing the same value to a later call to an operation requires that you
-- also pass the same value for all other parameters. We recommend that you
-- use a
-- <https://wikipedia.org/wiki/Universally_unique_identifier UUID type of value.>.
--
-- If you don\'t provide this value, then Amazon Web Services generates a
-- random one for you.
--
-- 'name', 'updateResourceShare_name' - If specified, the new name that you want to attach to the resource
-- share.
--
-- 'resourceShareArn', 'updateResourceShare_resourceShareArn' - Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share that you want to modify.
newUpdateResourceShare ::
  -- | 'resourceShareArn'
  Prelude.Text ->
  UpdateResourceShare
newUpdateResourceShare :: Text -> UpdateResourceShare
newUpdateResourceShare Text
pResourceShareArn_ =
  UpdateResourceShare'
    { $sel:allowExternalPrincipals:UpdateResourceShare' :: Maybe Bool
allowExternalPrincipals =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clientToken:UpdateResourceShare' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateResourceShare' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArn:UpdateResourceShare' :: Text
resourceShareArn = Text
pResourceShareArn_
    }

-- | Specifies whether principals outside your organization in Organizations
-- can be associated with a resource share.
updateResourceShare_allowExternalPrincipals :: Lens.Lens' UpdateResourceShare (Prelude.Maybe Prelude.Bool)
updateResourceShare_allowExternalPrincipals :: Lens' UpdateResourceShare (Maybe Bool)
updateResourceShare_allowExternalPrincipals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResourceShare' {Maybe Bool
allowExternalPrincipals :: Maybe Bool
$sel:allowExternalPrincipals:UpdateResourceShare' :: UpdateResourceShare -> Maybe Bool
allowExternalPrincipals} -> Maybe Bool
allowExternalPrincipals) (\s :: UpdateResourceShare
s@UpdateResourceShare' {} Maybe Bool
a -> UpdateResourceShare
s {$sel:allowExternalPrincipals:UpdateResourceShare' :: Maybe Bool
allowExternalPrincipals = Maybe Bool
a} :: UpdateResourceShare)

-- | Specifies a unique, case-sensitive identifier that you provide to ensure
-- the idempotency of the request. This lets you safely retry the request
-- without accidentally performing the same operation a second time.
-- Passing the same value to a later call to an operation requires that you
-- also pass the same value for all other parameters. We recommend that you
-- use a
-- <https://wikipedia.org/wiki/Universally_unique_identifier UUID type of value.>.
--
-- If you don\'t provide this value, then Amazon Web Services generates a
-- random one for you.
updateResourceShare_clientToken :: Lens.Lens' UpdateResourceShare (Prelude.Maybe Prelude.Text)
updateResourceShare_clientToken :: Lens' UpdateResourceShare (Maybe Text)
updateResourceShare_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResourceShare' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateResourceShare
s@UpdateResourceShare' {} Maybe Text
a -> UpdateResourceShare
s {$sel:clientToken:UpdateResourceShare' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateResourceShare)

-- | If specified, the new name that you want to attach to the resource
-- share.
updateResourceShare_name :: Lens.Lens' UpdateResourceShare (Prelude.Maybe Prelude.Text)
updateResourceShare_name :: Lens' UpdateResourceShare (Maybe Text)
updateResourceShare_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResourceShare' {Maybe Text
name :: Maybe Text
$sel:name:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateResourceShare
s@UpdateResourceShare' {} Maybe Text
a -> UpdateResourceShare
s {$sel:name:UpdateResourceShare' :: Maybe Text
name = Maybe Text
a} :: UpdateResourceShare)

-- | Specifies the
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share that you want to modify.
updateResourceShare_resourceShareArn :: Lens.Lens' UpdateResourceShare Prelude.Text
updateResourceShare_resourceShareArn :: Lens' UpdateResourceShare Text
updateResourceShare_resourceShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResourceShare' {Text
resourceShareArn :: Text
$sel:resourceShareArn:UpdateResourceShare' :: UpdateResourceShare -> Text
resourceShareArn} -> Text
resourceShareArn) (\s :: UpdateResourceShare
s@UpdateResourceShare' {} Text
a -> UpdateResourceShare
s {$sel:resourceShareArn:UpdateResourceShare' :: Text
resourceShareArn = Text
a} :: UpdateResourceShare)

instance Core.AWSRequest UpdateResourceShare where
  type
    AWSResponse UpdateResourceShare =
      UpdateResourceShareResponse
  request :: (Service -> Service)
-> UpdateResourceShare -> Request UpdateResourceShare
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 UpdateResourceShare
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateResourceShare)))
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 ResourceShare -> Int -> UpdateResourceShareResponse
UpdateResourceShareResponse'
            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
"clientToken")
            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
"resourceShare")
            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 UpdateResourceShare where
  hashWithSalt :: Int -> UpdateResourceShare -> Int
hashWithSalt Int
_salt UpdateResourceShare' {Maybe Bool
Maybe Text
Text
resourceShareArn :: Text
name :: Maybe Text
clientToken :: Maybe Text
allowExternalPrincipals :: Maybe Bool
$sel:resourceShareArn:UpdateResourceShare' :: UpdateResourceShare -> Text
$sel:name:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
$sel:clientToken:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
$sel:allowExternalPrincipals:UpdateResourceShare' :: UpdateResourceShare -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
allowExternalPrincipals
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceShareArn

instance Prelude.NFData UpdateResourceShare where
  rnf :: UpdateResourceShare -> ()
rnf UpdateResourceShare' {Maybe Bool
Maybe Text
Text
resourceShareArn :: Text
name :: Maybe Text
clientToken :: Maybe Text
allowExternalPrincipals :: Maybe Bool
$sel:resourceShareArn:UpdateResourceShare' :: UpdateResourceShare -> Text
$sel:name:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
$sel:clientToken:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
$sel:allowExternalPrincipals:UpdateResourceShare' :: UpdateResourceShare -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowExternalPrincipals
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceShareArn

instance Data.ToHeaders UpdateResourceShare where
  toHeaders :: UpdateResourceShare -> 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.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateResourceShare where
  toJSON :: UpdateResourceShare -> Value
toJSON UpdateResourceShare' {Maybe Bool
Maybe Text
Text
resourceShareArn :: Text
name :: Maybe Text
clientToken :: Maybe Text
allowExternalPrincipals :: Maybe Bool
$sel:resourceShareArn:UpdateResourceShare' :: UpdateResourceShare -> Text
$sel:name:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
$sel:clientToken:UpdateResourceShare' :: UpdateResourceShare -> Maybe Text
$sel:allowExternalPrincipals:UpdateResourceShare' :: UpdateResourceShare -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"allowExternalPrincipals" 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 Bool
allowExternalPrincipals,
            (Key
"clientToken" 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 Text
clientToken,
            (Key
"name" 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 Text
name,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"resourceShareArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceShareArn)
          ]
      )

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

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

-- | /See:/ 'newUpdateResourceShareResponse' smart constructor.
data UpdateResourceShareResponse = UpdateResourceShareResponse'
  { -- | The idempotency identifier associated with this request. If you want to
    -- repeat the same operation in an idempotent manner then you must include
    -- this value in the @clientToken@ request parameter of that later call.
    -- All other parameters must also have the same values that you used in the
    -- first call.
    UpdateResourceShareResponse -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Information about the resource share.
    UpdateResourceShareResponse -> Maybe ResourceShare
resourceShare :: Prelude.Maybe ResourceShare,
    -- | The response's http status code.
    UpdateResourceShareResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateResourceShareResponse -> UpdateResourceShareResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateResourceShareResponse -> UpdateResourceShareResponse -> Bool
$c/= :: UpdateResourceShareResponse -> UpdateResourceShareResponse -> Bool
== :: UpdateResourceShareResponse -> UpdateResourceShareResponse -> Bool
$c== :: UpdateResourceShareResponse -> UpdateResourceShareResponse -> Bool
Prelude.Eq, ReadPrec [UpdateResourceShareResponse]
ReadPrec UpdateResourceShareResponse
Int -> ReadS UpdateResourceShareResponse
ReadS [UpdateResourceShareResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateResourceShareResponse]
$creadListPrec :: ReadPrec [UpdateResourceShareResponse]
readPrec :: ReadPrec UpdateResourceShareResponse
$creadPrec :: ReadPrec UpdateResourceShareResponse
readList :: ReadS [UpdateResourceShareResponse]
$creadList :: ReadS [UpdateResourceShareResponse]
readsPrec :: Int -> ReadS UpdateResourceShareResponse
$creadsPrec :: Int -> ReadS UpdateResourceShareResponse
Prelude.Read, Int -> UpdateResourceShareResponse -> ShowS
[UpdateResourceShareResponse] -> ShowS
UpdateResourceShareResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateResourceShareResponse] -> ShowS
$cshowList :: [UpdateResourceShareResponse] -> ShowS
show :: UpdateResourceShareResponse -> String
$cshow :: UpdateResourceShareResponse -> String
showsPrec :: Int -> UpdateResourceShareResponse -> ShowS
$cshowsPrec :: Int -> UpdateResourceShareResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateResourceShareResponse x -> UpdateResourceShareResponse
forall x.
UpdateResourceShareResponse -> Rep UpdateResourceShareResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateResourceShareResponse x -> UpdateResourceShareResponse
$cfrom :: forall x.
UpdateResourceShareResponse -> Rep UpdateResourceShareResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateResourceShareResponse' 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:
--
-- 'clientToken', 'updateResourceShareResponse_clientToken' - The idempotency identifier associated with this request. If you want to
-- repeat the same operation in an idempotent manner then you must include
-- this value in the @clientToken@ request parameter of that later call.
-- All other parameters must also have the same values that you used in the
-- first call.
--
-- 'resourceShare', 'updateResourceShareResponse_resourceShare' - Information about the resource share.
--
-- 'httpStatus', 'updateResourceShareResponse_httpStatus' - The response's http status code.
newUpdateResourceShareResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateResourceShareResponse
newUpdateResourceShareResponse :: Int -> UpdateResourceShareResponse
newUpdateResourceShareResponse Int
pHttpStatus_ =
  UpdateResourceShareResponse'
    { $sel:clientToken:UpdateResourceShareResponse' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShare:UpdateResourceShareResponse' :: Maybe ResourceShare
resourceShare = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateResourceShareResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The idempotency identifier associated with this request. If you want to
-- repeat the same operation in an idempotent manner then you must include
-- this value in the @clientToken@ request parameter of that later call.
-- All other parameters must also have the same values that you used in the
-- first call.
updateResourceShareResponse_clientToken :: Lens.Lens' UpdateResourceShareResponse (Prelude.Maybe Prelude.Text)
updateResourceShareResponse_clientToken :: Lens' UpdateResourceShareResponse (Maybe Text)
updateResourceShareResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResourceShareResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateResourceShareResponse' :: UpdateResourceShareResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateResourceShareResponse
s@UpdateResourceShareResponse' {} Maybe Text
a -> UpdateResourceShareResponse
s {$sel:clientToken:UpdateResourceShareResponse' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateResourceShareResponse)

-- | Information about the resource share.
updateResourceShareResponse_resourceShare :: Lens.Lens' UpdateResourceShareResponse (Prelude.Maybe ResourceShare)
updateResourceShareResponse_resourceShare :: Lens' UpdateResourceShareResponse (Maybe ResourceShare)
updateResourceShareResponse_resourceShare = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateResourceShareResponse' {Maybe ResourceShare
resourceShare :: Maybe ResourceShare
$sel:resourceShare:UpdateResourceShareResponse' :: UpdateResourceShareResponse -> Maybe ResourceShare
resourceShare} -> Maybe ResourceShare
resourceShare) (\s :: UpdateResourceShareResponse
s@UpdateResourceShareResponse' {} Maybe ResourceShare
a -> UpdateResourceShareResponse
s {$sel:resourceShare:UpdateResourceShareResponse' :: Maybe ResourceShare
resourceShare = Maybe ResourceShare
a} :: UpdateResourceShareResponse)

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

instance Prelude.NFData UpdateResourceShareResponse where
  rnf :: UpdateResourceShareResponse -> ()
rnf UpdateResourceShareResponse' {Int
Maybe Text
Maybe ResourceShare
httpStatus :: Int
resourceShare :: Maybe ResourceShare
clientToken :: Maybe Text
$sel:httpStatus:UpdateResourceShareResponse' :: UpdateResourceShareResponse -> Int
$sel:resourceShare:UpdateResourceShareResponse' :: UpdateResourceShareResponse -> Maybe ResourceShare
$sel:clientToken:UpdateResourceShareResponse' :: UpdateResourceShareResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceShare
resourceShare
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus