{-# 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.DisassociateResourceSharePermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disassociates an RAM permission from a resource share. Permission
-- changes take effect immediately. You can remove a RAM permission from a
-- resource share only if there are currently no resources of the relevant
-- resource type currently attached to the resource share.
module Amazonka.RAM.DisassociateResourceSharePermission
  ( -- * Creating a Request
    DisassociateResourceSharePermission (..),
    newDisassociateResourceSharePermission,

    -- * Request Lenses
    disassociateResourceSharePermission_clientToken,
    disassociateResourceSharePermission_resourceShareArn,
    disassociateResourceSharePermission_permissionArn,

    -- * Destructuring the Response
    DisassociateResourceSharePermissionResponse (..),
    newDisassociateResourceSharePermissionResponse,

    -- * Response Lenses
    disassociateResourceSharePermissionResponse_clientToken,
    disassociateResourceSharePermissionResponse_returnValue,
    disassociateResourceSharePermissionResponse_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:/ 'newDisassociateResourceSharePermission' smart constructor.
data DisassociateResourceSharePermission = DisassociateResourceSharePermission'
  { -- | 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.
    DisassociateResourceSharePermission -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the resource share from which you want to disassociate a permission.
    DisassociateResourceSharePermission -> Text
resourceShareArn :: Prelude.Text,
    -- | The
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    -- of the permission to disassociate from the resource share. Changes to
    -- permissions take effect immediately.
    DisassociateResourceSharePermission -> Text
permissionArn :: Prelude.Text
  }
  deriving (DisassociateResourceSharePermission
-> DisassociateResourceSharePermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateResourceSharePermission
-> DisassociateResourceSharePermission -> Bool
$c/= :: DisassociateResourceSharePermission
-> DisassociateResourceSharePermission -> Bool
== :: DisassociateResourceSharePermission
-> DisassociateResourceSharePermission -> Bool
$c== :: DisassociateResourceSharePermission
-> DisassociateResourceSharePermission -> Bool
Prelude.Eq, ReadPrec [DisassociateResourceSharePermission]
ReadPrec DisassociateResourceSharePermission
Int -> ReadS DisassociateResourceSharePermission
ReadS [DisassociateResourceSharePermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateResourceSharePermission]
$creadListPrec :: ReadPrec [DisassociateResourceSharePermission]
readPrec :: ReadPrec DisassociateResourceSharePermission
$creadPrec :: ReadPrec DisassociateResourceSharePermission
readList :: ReadS [DisassociateResourceSharePermission]
$creadList :: ReadS [DisassociateResourceSharePermission]
readsPrec :: Int -> ReadS DisassociateResourceSharePermission
$creadsPrec :: Int -> ReadS DisassociateResourceSharePermission
Prelude.Read, Int -> DisassociateResourceSharePermission -> ShowS
[DisassociateResourceSharePermission] -> ShowS
DisassociateResourceSharePermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateResourceSharePermission] -> ShowS
$cshowList :: [DisassociateResourceSharePermission] -> ShowS
show :: DisassociateResourceSharePermission -> String
$cshow :: DisassociateResourceSharePermission -> String
showsPrec :: Int -> DisassociateResourceSharePermission -> ShowS
$cshowsPrec :: Int -> DisassociateResourceSharePermission -> ShowS
Prelude.Show, forall x.
Rep DisassociateResourceSharePermission x
-> DisassociateResourceSharePermission
forall x.
DisassociateResourceSharePermission
-> Rep DisassociateResourceSharePermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateResourceSharePermission x
-> DisassociateResourceSharePermission
$cfrom :: forall x.
DisassociateResourceSharePermission
-> Rep DisassociateResourceSharePermission x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateResourceSharePermission' 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', 'disassociateResourceSharePermission_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.
--
-- 'resourceShareArn', 'disassociateResourceSharePermission_resourceShareArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the resource share from which you want to disassociate a permission.
--
-- 'permissionArn', 'disassociateResourceSharePermission_permissionArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the permission to disassociate from the resource share. Changes to
-- permissions take effect immediately.
newDisassociateResourceSharePermission ::
  -- | 'resourceShareArn'
  Prelude.Text ->
  -- | 'permissionArn'
  Prelude.Text ->
  DisassociateResourceSharePermission
newDisassociateResourceSharePermission :: Text -> Text -> DisassociateResourceSharePermission
newDisassociateResourceSharePermission
  Text
pResourceShareArn_
  Text
pPermissionArn_ =
    DisassociateResourceSharePermission'
      { $sel:clientToken:DisassociateResourceSharePermission' :: Maybe Text
clientToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:resourceShareArn:DisassociateResourceSharePermission' :: Text
resourceShareArn = Text
pResourceShareArn_,
        $sel:permissionArn:DisassociateResourceSharePermission' :: Text
permissionArn = Text
pPermissionArn_
      }

-- | 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.
disassociateResourceSharePermission_clientToken :: Lens.Lens' DisassociateResourceSharePermission (Prelude.Maybe Prelude.Text)
disassociateResourceSharePermission_clientToken :: Lens' DisassociateResourceSharePermission (Maybe Text)
disassociateResourceSharePermission_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceSharePermission' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DisassociateResourceSharePermission' :: DisassociateResourceSharePermission -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DisassociateResourceSharePermission
s@DisassociateResourceSharePermission' {} Maybe Text
a -> DisassociateResourceSharePermission
s {$sel:clientToken:DisassociateResourceSharePermission' :: Maybe Text
clientToken = Maybe Text
a} :: DisassociateResourceSharePermission)

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

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the permission to disassociate from the resource share. Changes to
-- permissions take effect immediately.
disassociateResourceSharePermission_permissionArn :: Lens.Lens' DisassociateResourceSharePermission Prelude.Text
disassociateResourceSharePermission_permissionArn :: Lens' DisassociateResourceSharePermission Text
disassociateResourceSharePermission_permissionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceSharePermission' {Text
permissionArn :: Text
$sel:permissionArn:DisassociateResourceSharePermission' :: DisassociateResourceSharePermission -> Text
permissionArn} -> Text
permissionArn) (\s :: DisassociateResourceSharePermission
s@DisassociateResourceSharePermission' {} Text
a -> DisassociateResourceSharePermission
s {$sel:permissionArn:DisassociateResourceSharePermission' :: Text
permissionArn = Text
a} :: DisassociateResourceSharePermission)

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

instance
  Prelude.NFData
    DisassociateResourceSharePermission
  where
  rnf :: DisassociateResourceSharePermission -> ()
rnf DisassociateResourceSharePermission' {Maybe Text
Text
permissionArn :: Text
resourceShareArn :: Text
clientToken :: Maybe Text
$sel:permissionArn:DisassociateResourceSharePermission' :: DisassociateResourceSharePermission -> Text
$sel:resourceShareArn:DisassociateResourceSharePermission' :: DisassociateResourceSharePermission -> Text
$sel:clientToken:DisassociateResourceSharePermission' :: DisassociateResourceSharePermission -> 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 Text
resourceShareArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
permissionArn

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

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

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

-- | /See:/ 'newDisassociateResourceSharePermissionResponse' smart constructor.
data DisassociateResourceSharePermissionResponse = DisassociateResourceSharePermissionResponse'
  { -- | 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.
    DisassociateResourceSharePermissionResponse -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A return value of @true@ indicates that the request succeeded. A value
    -- of @false@ indicates that the request failed.
    DisassociateResourceSharePermissionResponse -> Maybe Bool
returnValue :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DisassociateResourceSharePermissionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateResourceSharePermissionResponse
-> DisassociateResourceSharePermissionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateResourceSharePermissionResponse
-> DisassociateResourceSharePermissionResponse -> Bool
$c/= :: DisassociateResourceSharePermissionResponse
-> DisassociateResourceSharePermissionResponse -> Bool
== :: DisassociateResourceSharePermissionResponse
-> DisassociateResourceSharePermissionResponse -> Bool
$c== :: DisassociateResourceSharePermissionResponse
-> DisassociateResourceSharePermissionResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateResourceSharePermissionResponse]
ReadPrec DisassociateResourceSharePermissionResponse
Int -> ReadS DisassociateResourceSharePermissionResponse
ReadS [DisassociateResourceSharePermissionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateResourceSharePermissionResponse]
$creadListPrec :: ReadPrec [DisassociateResourceSharePermissionResponse]
readPrec :: ReadPrec DisassociateResourceSharePermissionResponse
$creadPrec :: ReadPrec DisassociateResourceSharePermissionResponse
readList :: ReadS [DisassociateResourceSharePermissionResponse]
$creadList :: ReadS [DisassociateResourceSharePermissionResponse]
readsPrec :: Int -> ReadS DisassociateResourceSharePermissionResponse
$creadsPrec :: Int -> ReadS DisassociateResourceSharePermissionResponse
Prelude.Read, Int -> DisassociateResourceSharePermissionResponse -> ShowS
[DisassociateResourceSharePermissionResponse] -> ShowS
DisassociateResourceSharePermissionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateResourceSharePermissionResponse] -> ShowS
$cshowList :: [DisassociateResourceSharePermissionResponse] -> ShowS
show :: DisassociateResourceSharePermissionResponse -> String
$cshow :: DisassociateResourceSharePermissionResponse -> String
showsPrec :: Int -> DisassociateResourceSharePermissionResponse -> ShowS
$cshowsPrec :: Int -> DisassociateResourceSharePermissionResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateResourceSharePermissionResponse x
-> DisassociateResourceSharePermissionResponse
forall x.
DisassociateResourceSharePermissionResponse
-> Rep DisassociateResourceSharePermissionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateResourceSharePermissionResponse x
-> DisassociateResourceSharePermissionResponse
$cfrom :: forall x.
DisassociateResourceSharePermissionResponse
-> Rep DisassociateResourceSharePermissionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateResourceSharePermissionResponse' 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', 'disassociateResourceSharePermissionResponse_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.
--
-- 'returnValue', 'disassociateResourceSharePermissionResponse_returnValue' - A return value of @true@ indicates that the request succeeded. A value
-- of @false@ indicates that the request failed.
--
-- 'httpStatus', 'disassociateResourceSharePermissionResponse_httpStatus' - The response's http status code.
newDisassociateResourceSharePermissionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateResourceSharePermissionResponse
newDisassociateResourceSharePermissionResponse :: Int -> DisassociateResourceSharePermissionResponse
newDisassociateResourceSharePermissionResponse
  Int
pHttpStatus_ =
    DisassociateResourceSharePermissionResponse'
      { $sel:clientToken:DisassociateResourceSharePermissionResponse' :: Maybe Text
clientToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:returnValue:DisassociateResourceSharePermissionResponse' :: Maybe Bool
returnValue = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DisassociateResourceSharePermissionResponse' :: 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.
disassociateResourceSharePermissionResponse_clientToken :: Lens.Lens' DisassociateResourceSharePermissionResponse (Prelude.Maybe Prelude.Text)
disassociateResourceSharePermissionResponse_clientToken :: Lens' DisassociateResourceSharePermissionResponse (Maybe Text)
disassociateResourceSharePermissionResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceSharePermissionResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DisassociateResourceSharePermissionResponse' :: DisassociateResourceSharePermissionResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DisassociateResourceSharePermissionResponse
s@DisassociateResourceSharePermissionResponse' {} Maybe Text
a -> DisassociateResourceSharePermissionResponse
s {$sel:clientToken:DisassociateResourceSharePermissionResponse' :: Maybe Text
clientToken = Maybe Text
a} :: DisassociateResourceSharePermissionResponse)

-- | A return value of @true@ indicates that the request succeeded. A value
-- of @false@ indicates that the request failed.
disassociateResourceSharePermissionResponse_returnValue :: Lens.Lens' DisassociateResourceSharePermissionResponse (Prelude.Maybe Prelude.Bool)
disassociateResourceSharePermissionResponse_returnValue :: Lens' DisassociateResourceSharePermissionResponse (Maybe Bool)
disassociateResourceSharePermissionResponse_returnValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceSharePermissionResponse' {Maybe Bool
returnValue :: Maybe Bool
$sel:returnValue:DisassociateResourceSharePermissionResponse' :: DisassociateResourceSharePermissionResponse -> Maybe Bool
returnValue} -> Maybe Bool
returnValue) (\s :: DisassociateResourceSharePermissionResponse
s@DisassociateResourceSharePermissionResponse' {} Maybe Bool
a -> DisassociateResourceSharePermissionResponse
s {$sel:returnValue:DisassociateResourceSharePermissionResponse' :: Maybe Bool
returnValue = Maybe Bool
a} :: DisassociateResourceSharePermissionResponse)

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

instance
  Prelude.NFData
    DisassociateResourceSharePermissionResponse
  where
  rnf :: DisassociateResourceSharePermissionResponse -> ()
rnf DisassociateResourceSharePermissionResponse' {Int
Maybe Bool
Maybe Text
httpStatus :: Int
returnValue :: Maybe Bool
clientToken :: Maybe Text
$sel:httpStatus:DisassociateResourceSharePermissionResponse' :: DisassociateResourceSharePermissionResponse -> Int
$sel:returnValue:DisassociateResourceSharePermissionResponse' :: DisassociateResourceSharePermissionResponse -> Maybe Bool
$sel:clientToken:DisassociateResourceSharePermissionResponse' :: DisassociateResourceSharePermissionResponse -> 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 Bool
returnValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus