{-# 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.DisassociateResourceShare
-- 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 the specified principals or resources from the specified
-- resource share.
module Amazonka.RAM.DisassociateResourceShare
  ( -- * Creating a Request
    DisassociateResourceShare (..),
    newDisassociateResourceShare,

    -- * Request Lenses
    disassociateResourceShare_clientToken,
    disassociateResourceShare_principals,
    disassociateResourceShare_resourceArns,
    disassociateResourceShare_resourceShareArn,

    -- * Destructuring the Response
    DisassociateResourceShareResponse (..),
    newDisassociateResourceShareResponse,

    -- * Response Lenses
    disassociateResourceShareResponse_clientToken,
    disassociateResourceShareResponse_resourceShareAssociations,
    disassociateResourceShareResponse_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:/ 'newDisassociateResourceShare' smart constructor.
data DisassociateResourceShare = DisassociateResourceShare'
  { -- | 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.
    DisassociateResourceShare -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies a list of one or more principals that no longer are to have
    -- access to the resources in this resource share.
    --
    -- You can include the following values:
    --
    -- -   An Amazon Web Services account ID, for example: @123456789012@
    --
    -- -   An
    --     <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
    --     of an organization in Organizations, for example:
    --     @organizations::123456789012:organization\/o-exampleorgid@
    --
    -- -   An ARN of an organizational unit (OU) in Organizations, for example:
    --     @organizations::123456789012:ou\/o-exampleorgid\/ou-examplerootid-exampleouid123@
    --
    -- -   An ARN of an IAM role, for example:
    --     @iam::123456789012:role\/rolename@
    --
    -- -   An ARN of an IAM user, for example:
    --     @iam::123456789012user\/username@
    --
    -- Not all resource types can be shared with IAM roles and users. For more
    -- information, see
    -- <https://docs.aws.amazon.com/ram/latest/userguide/permissions.html#permissions-rbp-supported-resource-types Sharing with IAM roles and users>
    -- in the /Resource Access Manager User Guide/.
    DisassociateResourceShare -> Maybe [Text]
principals :: Prelude.Maybe [Prelude.Text],
    -- | Specifies a list of
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- for one or more resources that you want to remove from the resource
    -- share. After the operation runs, these resources are no longer shared
    -- with principals outside of the Amazon Web Services account that created
    -- the resources.
    DisassociateResourceShare -> Maybe [Text]
resourceArns :: Prelude.Maybe [Prelude.Text],
    -- | Specifies
    -- <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 remove resources from.
    DisassociateResourceShare -> Text
resourceShareArn :: Prelude.Text
  }
  deriving (DisassociateResourceShare -> DisassociateResourceShare -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateResourceShare -> DisassociateResourceShare -> Bool
$c/= :: DisassociateResourceShare -> DisassociateResourceShare -> Bool
== :: DisassociateResourceShare -> DisassociateResourceShare -> Bool
$c== :: DisassociateResourceShare -> DisassociateResourceShare -> Bool
Prelude.Eq, ReadPrec [DisassociateResourceShare]
ReadPrec DisassociateResourceShare
Int -> ReadS DisassociateResourceShare
ReadS [DisassociateResourceShare]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateResourceShare]
$creadListPrec :: ReadPrec [DisassociateResourceShare]
readPrec :: ReadPrec DisassociateResourceShare
$creadPrec :: ReadPrec DisassociateResourceShare
readList :: ReadS [DisassociateResourceShare]
$creadList :: ReadS [DisassociateResourceShare]
readsPrec :: Int -> ReadS DisassociateResourceShare
$creadsPrec :: Int -> ReadS DisassociateResourceShare
Prelude.Read, Int -> DisassociateResourceShare -> ShowS
[DisassociateResourceShare] -> ShowS
DisassociateResourceShare -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateResourceShare] -> ShowS
$cshowList :: [DisassociateResourceShare] -> ShowS
show :: DisassociateResourceShare -> String
$cshow :: DisassociateResourceShare -> String
showsPrec :: Int -> DisassociateResourceShare -> ShowS
$cshowsPrec :: Int -> DisassociateResourceShare -> ShowS
Prelude.Show, forall x.
Rep DisassociateResourceShare x -> DisassociateResourceShare
forall x.
DisassociateResourceShare -> Rep DisassociateResourceShare x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateResourceShare x -> DisassociateResourceShare
$cfrom :: forall x.
DisassociateResourceShare -> Rep DisassociateResourceShare x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateResourceShare' 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', 'disassociateResourceShare_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.
--
-- 'principals', 'disassociateResourceShare_principals' - Specifies a list of one or more principals that no longer are to have
-- access to the resources in this resource share.
--
-- You can include the following values:
--
-- -   An Amazon Web Services account ID, for example: @123456789012@
--
-- -   An
--     <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
--     of an organization in Organizations, for example:
--     @organizations::123456789012:organization\/o-exampleorgid@
--
-- -   An ARN of an organizational unit (OU) in Organizations, for example:
--     @organizations::123456789012:ou\/o-exampleorgid\/ou-examplerootid-exampleouid123@
--
-- -   An ARN of an IAM role, for example:
--     @iam::123456789012:role\/rolename@
--
-- -   An ARN of an IAM user, for example:
--     @iam::123456789012user\/username@
--
-- Not all resource types can be shared with IAM roles and users. For more
-- information, see
-- <https://docs.aws.amazon.com/ram/latest/userguide/permissions.html#permissions-rbp-supported-resource-types Sharing with IAM roles and users>
-- in the /Resource Access Manager User Guide/.
--
-- 'resourceArns', 'disassociateResourceShare_resourceArns' - Specifies a list of
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- for one or more resources that you want to remove from the resource
-- share. After the operation runs, these resources are no longer shared
-- with principals outside of the Amazon Web Services account that created
-- the resources.
--
-- 'resourceShareArn', 'disassociateResourceShare_resourceShareArn' - Specifies
-- <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 remove resources from.
newDisassociateResourceShare ::
  -- | 'resourceShareArn'
  Prelude.Text ->
  DisassociateResourceShare
newDisassociateResourceShare :: Text -> DisassociateResourceShare
newDisassociateResourceShare Text
pResourceShareArn_ =
  DisassociateResourceShare'
    { $sel:clientToken:DisassociateResourceShare' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:principals:DisassociateResourceShare' :: Maybe [Text]
principals = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArns:DisassociateResourceShare' :: Maybe [Text]
resourceArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArn:DisassociateResourceShare' :: Text
resourceShareArn = Text
pResourceShareArn_
    }

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

-- | Specifies a list of one or more principals that no longer are to have
-- access to the resources in this resource share.
--
-- You can include the following values:
--
-- -   An Amazon Web Services account ID, for example: @123456789012@
--
-- -   An
--     <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
--     of an organization in Organizations, for example:
--     @organizations::123456789012:organization\/o-exampleorgid@
--
-- -   An ARN of an organizational unit (OU) in Organizations, for example:
--     @organizations::123456789012:ou\/o-exampleorgid\/ou-examplerootid-exampleouid123@
--
-- -   An ARN of an IAM role, for example:
--     @iam::123456789012:role\/rolename@
--
-- -   An ARN of an IAM user, for example:
--     @iam::123456789012user\/username@
--
-- Not all resource types can be shared with IAM roles and users. For more
-- information, see
-- <https://docs.aws.amazon.com/ram/latest/userguide/permissions.html#permissions-rbp-supported-resource-types Sharing with IAM roles and users>
-- in the /Resource Access Manager User Guide/.
disassociateResourceShare_principals :: Lens.Lens' DisassociateResourceShare (Prelude.Maybe [Prelude.Text])
disassociateResourceShare_principals :: Lens' DisassociateResourceShare (Maybe [Text])
disassociateResourceShare_principals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceShare' {Maybe [Text]
principals :: Maybe [Text]
$sel:principals:DisassociateResourceShare' :: DisassociateResourceShare -> Maybe [Text]
principals} -> Maybe [Text]
principals) (\s :: DisassociateResourceShare
s@DisassociateResourceShare' {} Maybe [Text]
a -> DisassociateResourceShare
s {$sel:principals:DisassociateResourceShare' :: Maybe [Text]
principals = Maybe [Text]
a} :: DisassociateResourceShare) 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

-- | Specifies a list of
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- for one or more resources that you want to remove from the resource
-- share. After the operation runs, these resources are no longer shared
-- with principals outside of the Amazon Web Services account that created
-- the resources.
disassociateResourceShare_resourceArns :: Lens.Lens' DisassociateResourceShare (Prelude.Maybe [Prelude.Text])
disassociateResourceShare_resourceArns :: Lens' DisassociateResourceShare (Maybe [Text])
disassociateResourceShare_resourceArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceShare' {Maybe [Text]
resourceArns :: Maybe [Text]
$sel:resourceArns:DisassociateResourceShare' :: DisassociateResourceShare -> Maybe [Text]
resourceArns} -> Maybe [Text]
resourceArns) (\s :: DisassociateResourceShare
s@DisassociateResourceShare' {} Maybe [Text]
a -> DisassociateResourceShare
s {$sel:resourceArns:DisassociateResourceShare' :: Maybe [Text]
resourceArns = Maybe [Text]
a} :: DisassociateResourceShare) 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

-- | Specifies
-- <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 remove resources from.
disassociateResourceShare_resourceShareArn :: Lens.Lens' DisassociateResourceShare Prelude.Text
disassociateResourceShare_resourceShareArn :: Lens' DisassociateResourceShare Text
disassociateResourceShare_resourceShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceShare' {Text
resourceShareArn :: Text
$sel:resourceShareArn:DisassociateResourceShare' :: DisassociateResourceShare -> Text
resourceShareArn} -> Text
resourceShareArn) (\s :: DisassociateResourceShare
s@DisassociateResourceShare' {} Text
a -> DisassociateResourceShare
s {$sel:resourceShareArn:DisassociateResourceShare' :: Text
resourceShareArn = Text
a} :: DisassociateResourceShare)

instance Core.AWSRequest DisassociateResourceShare where
  type
    AWSResponse DisassociateResourceShare =
      DisassociateResourceShareResponse
  request :: (Service -> Service)
-> DisassociateResourceShare -> Request DisassociateResourceShare
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 DisassociateResourceShare
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateResourceShare)))
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 [ResourceShareAssociation]
-> Int
-> DisassociateResourceShareResponse
DisassociateResourceShareResponse'
            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
"resourceShareAssociations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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 DisassociateResourceShare where
  hashWithSalt :: Int -> DisassociateResourceShare -> Int
hashWithSalt Int
_salt DisassociateResourceShare' {Maybe [Text]
Maybe Text
Text
resourceShareArn :: Text
resourceArns :: Maybe [Text]
principals :: Maybe [Text]
clientToken :: Maybe Text
$sel:resourceShareArn:DisassociateResourceShare' :: DisassociateResourceShare -> Text
$sel:resourceArns:DisassociateResourceShare' :: DisassociateResourceShare -> Maybe [Text]
$sel:principals:DisassociateResourceShare' :: DisassociateResourceShare -> Maybe [Text]
$sel:clientToken:DisassociateResourceShare' :: DisassociateResourceShare -> 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` Maybe [Text]
principals
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
resourceArns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceShareArn

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

instance Data.ToHeaders DisassociateResourceShare where
  toHeaders :: DisassociateResourceShare -> 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 DisassociateResourceShare where
  toJSON :: DisassociateResourceShare -> Value
toJSON DisassociateResourceShare' {Maybe [Text]
Maybe Text
Text
resourceShareArn :: Text
resourceArns :: Maybe [Text]
principals :: Maybe [Text]
clientToken :: Maybe Text
$sel:resourceShareArn:DisassociateResourceShare' :: DisassociateResourceShare -> Text
$sel:resourceArns:DisassociateResourceShare' :: DisassociateResourceShare -> Maybe [Text]
$sel:principals:DisassociateResourceShare' :: DisassociateResourceShare -> Maybe [Text]
$sel:clientToken:DisassociateResourceShare' :: DisassociateResourceShare -> 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,
            (Key
"principals" 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]
principals,
            (Key
"resourceArns" 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]
resourceArns,
            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 DisassociateResourceShare where
  toPath :: DisassociateResourceShare -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/disassociateresourceshare"

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

-- | /See:/ 'newDisassociateResourceShareResponse' smart constructor.
data DisassociateResourceShareResponse = DisassociateResourceShareResponse'
  { -- | 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.
    DisassociateResourceShareResponse -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | An array of objects that contain information about the updated
    -- associations for this resource share.
    DisassociateResourceShareResponse
-> Maybe [ResourceShareAssociation]
resourceShareAssociations :: Prelude.Maybe [ResourceShareAssociation],
    -- | The response's http status code.
    DisassociateResourceShareResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateResourceShareResponse
-> DisassociateResourceShareResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateResourceShareResponse
-> DisassociateResourceShareResponse -> Bool
$c/= :: DisassociateResourceShareResponse
-> DisassociateResourceShareResponse -> Bool
== :: DisassociateResourceShareResponse
-> DisassociateResourceShareResponse -> Bool
$c== :: DisassociateResourceShareResponse
-> DisassociateResourceShareResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateResourceShareResponse]
ReadPrec DisassociateResourceShareResponse
Int -> ReadS DisassociateResourceShareResponse
ReadS [DisassociateResourceShareResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateResourceShareResponse]
$creadListPrec :: ReadPrec [DisassociateResourceShareResponse]
readPrec :: ReadPrec DisassociateResourceShareResponse
$creadPrec :: ReadPrec DisassociateResourceShareResponse
readList :: ReadS [DisassociateResourceShareResponse]
$creadList :: ReadS [DisassociateResourceShareResponse]
readsPrec :: Int -> ReadS DisassociateResourceShareResponse
$creadsPrec :: Int -> ReadS DisassociateResourceShareResponse
Prelude.Read, Int -> DisassociateResourceShareResponse -> ShowS
[DisassociateResourceShareResponse] -> ShowS
DisassociateResourceShareResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateResourceShareResponse] -> ShowS
$cshowList :: [DisassociateResourceShareResponse] -> ShowS
show :: DisassociateResourceShareResponse -> String
$cshow :: DisassociateResourceShareResponse -> String
showsPrec :: Int -> DisassociateResourceShareResponse -> ShowS
$cshowsPrec :: Int -> DisassociateResourceShareResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateResourceShareResponse x
-> DisassociateResourceShareResponse
forall x.
DisassociateResourceShareResponse
-> Rep DisassociateResourceShareResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateResourceShareResponse x
-> DisassociateResourceShareResponse
$cfrom :: forall x.
DisassociateResourceShareResponse
-> Rep DisassociateResourceShareResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateResourceShareResponse' 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', 'disassociateResourceShareResponse_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.
--
-- 'resourceShareAssociations', 'disassociateResourceShareResponse_resourceShareAssociations' - An array of objects that contain information about the updated
-- associations for this resource share.
--
-- 'httpStatus', 'disassociateResourceShareResponse_httpStatus' - The response's http status code.
newDisassociateResourceShareResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateResourceShareResponse
newDisassociateResourceShareResponse :: Int -> DisassociateResourceShareResponse
newDisassociateResourceShareResponse Int
pHttpStatus_ =
  DisassociateResourceShareResponse'
    { $sel:clientToken:DisassociateResourceShareResponse' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareAssociations:DisassociateResourceShareResponse' :: Maybe [ResourceShareAssociation]
resourceShareAssociations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DisassociateResourceShareResponse' :: 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.
disassociateResourceShareResponse_clientToken :: Lens.Lens' DisassociateResourceShareResponse (Prelude.Maybe Prelude.Text)
disassociateResourceShareResponse_clientToken :: Lens' DisassociateResourceShareResponse (Maybe Text)
disassociateResourceShareResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceShareResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DisassociateResourceShareResponse' :: DisassociateResourceShareResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DisassociateResourceShareResponse
s@DisassociateResourceShareResponse' {} Maybe Text
a -> DisassociateResourceShareResponse
s {$sel:clientToken:DisassociateResourceShareResponse' :: Maybe Text
clientToken = Maybe Text
a} :: DisassociateResourceShareResponse)

-- | An array of objects that contain information about the updated
-- associations for this resource share.
disassociateResourceShareResponse_resourceShareAssociations :: Lens.Lens' DisassociateResourceShareResponse (Prelude.Maybe [ResourceShareAssociation])
disassociateResourceShareResponse_resourceShareAssociations :: Lens'
  DisassociateResourceShareResponse
  (Maybe [ResourceShareAssociation])
disassociateResourceShareResponse_resourceShareAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceShareResponse' {Maybe [ResourceShareAssociation]
resourceShareAssociations :: Maybe [ResourceShareAssociation]
$sel:resourceShareAssociations:DisassociateResourceShareResponse' :: DisassociateResourceShareResponse
-> Maybe [ResourceShareAssociation]
resourceShareAssociations} -> Maybe [ResourceShareAssociation]
resourceShareAssociations) (\s :: DisassociateResourceShareResponse
s@DisassociateResourceShareResponse' {} Maybe [ResourceShareAssociation]
a -> DisassociateResourceShareResponse
s {$sel:resourceShareAssociations:DisassociateResourceShareResponse' :: Maybe [ResourceShareAssociation]
resourceShareAssociations = Maybe [ResourceShareAssociation]
a} :: DisassociateResourceShareResponse) 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 response's http status code.
disassociateResourceShareResponse_httpStatus :: Lens.Lens' DisassociateResourceShareResponse Prelude.Int
disassociateResourceShareResponse_httpStatus :: Lens' DisassociateResourceShareResponse Int
disassociateResourceShareResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateResourceShareResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateResourceShareResponse' :: DisassociateResourceShareResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DisassociateResourceShareResponse
s@DisassociateResourceShareResponse' {} Int
a -> DisassociateResourceShareResponse
s {$sel:httpStatus:DisassociateResourceShareResponse' :: Int
httpStatus = Int
a} :: DisassociateResourceShareResponse)

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