{-# 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.AssociateResourceShare
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds the specified list of principals and list of resources to a
-- resource share. Principals that already have access to this resource
-- share immediately receive access to the added resources. Newly added
-- principals immediately receive access to the resources shared in this
-- resource share.
module Amazonka.RAM.AssociateResourceShare
  ( -- * Creating a Request
    AssociateResourceShare (..),
    newAssociateResourceShare,

    -- * Request Lenses
    associateResourceShare_clientToken,
    associateResourceShare_principals,
    associateResourceShare_resourceArns,
    associateResourceShare_resourceShareArn,

    -- * Destructuring the Response
    AssociateResourceShareResponse (..),
    newAssociateResourceShareResponse,

    -- * Response Lenses
    associateResourceShareResponse_clientToken,
    associateResourceShareResponse_resourceShareAssociations,
    associateResourceShareResponse_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:/ 'newAssociateResourceShare' smart constructor.
data AssociateResourceShare = AssociateResourceShare'
  { -- | 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.
    AssociateResourceShare -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | Specifies a list of principals to whom you want to the resource share.
    -- This can be @null@ if you want to add only resources.
    --
    -- What the principals can do with the resources in the share is determined
    -- by the RAM permissions that you associate with the resource share. See
    -- AssociateResourceSharePermission.
    --
    -- 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/.
    AssociateResourceShare -> 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)>
    -- of the resources that you want to share. This can be @null@ if you want
    -- to add only principals.
    AssociateResourceShare -> Maybe [Text]
resourceArns :: 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 add principals or resources to.
    AssociateResourceShare -> Text
resourceShareArn :: Prelude.Text
  }
  deriving (AssociateResourceShare -> AssociateResourceShare -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateResourceShare -> AssociateResourceShare -> Bool
$c/= :: AssociateResourceShare -> AssociateResourceShare -> Bool
== :: AssociateResourceShare -> AssociateResourceShare -> Bool
$c== :: AssociateResourceShare -> AssociateResourceShare -> Bool
Prelude.Eq, ReadPrec [AssociateResourceShare]
ReadPrec AssociateResourceShare
Int -> ReadS AssociateResourceShare
ReadS [AssociateResourceShare]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateResourceShare]
$creadListPrec :: ReadPrec [AssociateResourceShare]
readPrec :: ReadPrec AssociateResourceShare
$creadPrec :: ReadPrec AssociateResourceShare
readList :: ReadS [AssociateResourceShare]
$creadList :: ReadS [AssociateResourceShare]
readsPrec :: Int -> ReadS AssociateResourceShare
$creadsPrec :: Int -> ReadS AssociateResourceShare
Prelude.Read, Int -> AssociateResourceShare -> ShowS
[AssociateResourceShare] -> ShowS
AssociateResourceShare -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateResourceShare] -> ShowS
$cshowList :: [AssociateResourceShare] -> ShowS
show :: AssociateResourceShare -> String
$cshow :: AssociateResourceShare -> String
showsPrec :: Int -> AssociateResourceShare -> ShowS
$cshowsPrec :: Int -> AssociateResourceShare -> ShowS
Prelude.Show, forall x. Rep AssociateResourceShare x -> AssociateResourceShare
forall x. AssociateResourceShare -> Rep AssociateResourceShare x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateResourceShare x -> AssociateResourceShare
$cfrom :: forall x. AssociateResourceShare -> Rep AssociateResourceShare x
Prelude.Generic)

-- |
-- Create a value of 'AssociateResourceShare' 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', 'associateResourceShare_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', 'associateResourceShare_principals' - Specifies a list of principals to whom you want to the resource share.
-- This can be @null@ if you want to add only resources.
--
-- What the principals can do with the resources in the share is determined
-- by the RAM permissions that you associate with the resource share. See
-- AssociateResourceSharePermission.
--
-- 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', 'associateResourceShare_resourceArns' - Specifies a list of
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- of the resources that you want to share. This can be @null@ if you want
-- to add only principals.
--
-- 'resourceShareArn', 'associateResourceShare_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 add principals or resources to.
newAssociateResourceShare ::
  -- | 'resourceShareArn'
  Prelude.Text ->
  AssociateResourceShare
newAssociateResourceShare :: Text -> AssociateResourceShare
newAssociateResourceShare Text
pResourceShareArn_ =
  AssociateResourceShare'
    { $sel:clientToken:AssociateResourceShare' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:principals:AssociateResourceShare' :: Maybe [Text]
principals = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArns:AssociateResourceShare' :: Maybe [Text]
resourceArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareArn:AssociateResourceShare' :: 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.
associateResourceShare_clientToken :: Lens.Lens' AssociateResourceShare (Prelude.Maybe Prelude.Text)
associateResourceShare_clientToken :: Lens' AssociateResourceShare (Maybe Text)
associateResourceShare_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShare' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:AssociateResourceShare' :: AssociateResourceShare -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: AssociateResourceShare
s@AssociateResourceShare' {} Maybe Text
a -> AssociateResourceShare
s {$sel:clientToken:AssociateResourceShare' :: Maybe Text
clientToken = Maybe Text
a} :: AssociateResourceShare)

-- | Specifies a list of principals to whom you want to the resource share.
-- This can be @null@ if you want to add only resources.
--
-- What the principals can do with the resources in the share is determined
-- by the RAM permissions that you associate with the resource share. See
-- AssociateResourceSharePermission.
--
-- 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/.
associateResourceShare_principals :: Lens.Lens' AssociateResourceShare (Prelude.Maybe [Prelude.Text])
associateResourceShare_principals :: Lens' AssociateResourceShare (Maybe [Text])
associateResourceShare_principals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShare' {Maybe [Text]
principals :: Maybe [Text]
$sel:principals:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
principals} -> Maybe [Text]
principals) (\s :: AssociateResourceShare
s@AssociateResourceShare' {} Maybe [Text]
a -> AssociateResourceShare
s {$sel:principals:AssociateResourceShare' :: Maybe [Text]
principals = Maybe [Text]
a} :: AssociateResourceShare) 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)>
-- of the resources that you want to share. This can be @null@ if you want
-- to add only principals.
associateResourceShare_resourceArns :: Lens.Lens' AssociateResourceShare (Prelude.Maybe [Prelude.Text])
associateResourceShare_resourceArns :: Lens' AssociateResourceShare (Maybe [Text])
associateResourceShare_resourceArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShare' {Maybe [Text]
resourceArns :: Maybe [Text]
$sel:resourceArns:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
resourceArns} -> Maybe [Text]
resourceArns) (\s :: AssociateResourceShare
s@AssociateResourceShare' {} Maybe [Text]
a -> AssociateResourceShare
s {$sel:resourceArns:AssociateResourceShare' :: Maybe [Text]
resourceArns = Maybe [Text]
a} :: AssociateResourceShare) 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 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 add principals or resources to.
associateResourceShare_resourceShareArn :: Lens.Lens' AssociateResourceShare Prelude.Text
associateResourceShare_resourceShareArn :: Lens' AssociateResourceShare Text
associateResourceShare_resourceShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShare' {Text
resourceShareArn :: Text
$sel:resourceShareArn:AssociateResourceShare' :: AssociateResourceShare -> Text
resourceShareArn} -> Text
resourceShareArn) (\s :: AssociateResourceShare
s@AssociateResourceShare' {} Text
a -> AssociateResourceShare
s {$sel:resourceShareArn:AssociateResourceShare' :: Text
resourceShareArn = Text
a} :: AssociateResourceShare)

instance Core.AWSRequest AssociateResourceShare where
  type
    AWSResponse AssociateResourceShare =
      AssociateResourceShareResponse
  request :: (Service -> Service)
-> AssociateResourceShare -> Request AssociateResourceShare
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 AssociateResourceShare
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AssociateResourceShare)))
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
-> AssociateResourceShareResponse
AssociateResourceShareResponse'
            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 AssociateResourceShare where
  hashWithSalt :: Int -> AssociateResourceShare -> Int
hashWithSalt Int
_salt AssociateResourceShare' {Maybe [Text]
Maybe Text
Text
resourceShareArn :: Text
resourceArns :: Maybe [Text]
principals :: Maybe [Text]
clientToken :: Maybe Text
$sel:resourceShareArn:AssociateResourceShare' :: AssociateResourceShare -> Text
$sel:resourceArns:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
$sel:principals:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
$sel:clientToken:AssociateResourceShare' :: AssociateResourceShare -> 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 AssociateResourceShare where
  rnf :: AssociateResourceShare -> ()
rnf AssociateResourceShare' {Maybe [Text]
Maybe Text
Text
resourceShareArn :: Text
resourceArns :: Maybe [Text]
principals :: Maybe [Text]
clientToken :: Maybe Text
$sel:resourceShareArn:AssociateResourceShare' :: AssociateResourceShare -> Text
$sel:resourceArns:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
$sel:principals:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
$sel:clientToken:AssociateResourceShare' :: AssociateResourceShare -> 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 AssociateResourceShare where
  toHeaders :: AssociateResourceShare -> 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 AssociateResourceShare where
  toJSON :: AssociateResourceShare -> Value
toJSON AssociateResourceShare' {Maybe [Text]
Maybe Text
Text
resourceShareArn :: Text
resourceArns :: Maybe [Text]
principals :: Maybe [Text]
clientToken :: Maybe Text
$sel:resourceShareArn:AssociateResourceShare' :: AssociateResourceShare -> Text
$sel:resourceArns:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
$sel:principals:AssociateResourceShare' :: AssociateResourceShare -> Maybe [Text]
$sel:clientToken:AssociateResourceShare' :: AssociateResourceShare -> 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 AssociateResourceShare where
  toPath :: AssociateResourceShare -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/associateresourceshare"

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

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

-- |
-- Create a value of 'AssociateResourceShareResponse' 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', 'associateResourceShareResponse_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', 'associateResourceShareResponse_resourceShareAssociations' - An array of objects that contain information about the associations.
--
-- 'httpStatus', 'associateResourceShareResponse_httpStatus' - The response's http status code.
newAssociateResourceShareResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AssociateResourceShareResponse
newAssociateResourceShareResponse :: Int -> AssociateResourceShareResponse
newAssociateResourceShareResponse Int
pHttpStatus_ =
  AssociateResourceShareResponse'
    { $sel:clientToken:AssociateResourceShareResponse' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareAssociations:AssociateResourceShareResponse' :: Maybe [ResourceShareAssociation]
resourceShareAssociations = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AssociateResourceShareResponse' :: 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.
associateResourceShareResponse_clientToken :: Lens.Lens' AssociateResourceShareResponse (Prelude.Maybe Prelude.Text)
associateResourceShareResponse_clientToken :: Lens' AssociateResourceShareResponse (Maybe Text)
associateResourceShareResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShareResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:AssociateResourceShareResponse' :: AssociateResourceShareResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: AssociateResourceShareResponse
s@AssociateResourceShareResponse' {} Maybe Text
a -> AssociateResourceShareResponse
s {$sel:clientToken:AssociateResourceShareResponse' :: Maybe Text
clientToken = Maybe Text
a} :: AssociateResourceShareResponse)

-- | An array of objects that contain information about the associations.
associateResourceShareResponse_resourceShareAssociations :: Lens.Lens' AssociateResourceShareResponse (Prelude.Maybe [ResourceShareAssociation])
associateResourceShareResponse_resourceShareAssociations :: Lens'
  AssociateResourceShareResponse (Maybe [ResourceShareAssociation])
associateResourceShareResponse_resourceShareAssociations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShareResponse' {Maybe [ResourceShareAssociation]
resourceShareAssociations :: Maybe [ResourceShareAssociation]
$sel:resourceShareAssociations:AssociateResourceShareResponse' :: AssociateResourceShareResponse -> Maybe [ResourceShareAssociation]
resourceShareAssociations} -> Maybe [ResourceShareAssociation]
resourceShareAssociations) (\s :: AssociateResourceShareResponse
s@AssociateResourceShareResponse' {} Maybe [ResourceShareAssociation]
a -> AssociateResourceShareResponse
s {$sel:resourceShareAssociations:AssociateResourceShareResponse' :: Maybe [ResourceShareAssociation]
resourceShareAssociations = Maybe [ResourceShareAssociation]
a} :: AssociateResourceShareResponse) 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.
associateResourceShareResponse_httpStatus :: Lens.Lens' AssociateResourceShareResponse Prelude.Int
associateResourceShareResponse_httpStatus :: Lens' AssociateResourceShareResponse Int
associateResourceShareResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateResourceShareResponse' {Int
httpStatus :: Int
$sel:httpStatus:AssociateResourceShareResponse' :: AssociateResourceShareResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: AssociateResourceShareResponse
s@AssociateResourceShareResponse' {} Int
a -> AssociateResourceShareResponse
s {$sel:httpStatus:AssociateResourceShareResponse' :: Int
httpStatus = Int
a} :: AssociateResourceShareResponse)

instance
  Prelude.NFData
    AssociateResourceShareResponse
  where
  rnf :: AssociateResourceShareResponse -> ()
rnf AssociateResourceShareResponse' {Int
Maybe [ResourceShareAssociation]
Maybe Text
httpStatus :: Int
resourceShareAssociations :: Maybe [ResourceShareAssociation]
clientToken :: Maybe Text
$sel:httpStatus:AssociateResourceShareResponse' :: AssociateResourceShareResponse -> Int
$sel:resourceShareAssociations:AssociateResourceShareResponse' :: AssociateResourceShareResponse -> Maybe [ResourceShareAssociation]
$sel:clientToken:AssociateResourceShareResponse' :: AssociateResourceShareResponse -> 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