{-# 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.AcceptResourceShareInvitation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Accepts an invitation to a resource share from another Amazon Web
-- Services account. After you accept the invitation, the resources
-- included in the resource share are available to interact with in the
-- relevant Amazon Web Services Management Consoles and tools.
module Amazonka.RAM.AcceptResourceShareInvitation
  ( -- * Creating a Request
    AcceptResourceShareInvitation (..),
    newAcceptResourceShareInvitation,

    -- * Request Lenses
    acceptResourceShareInvitation_clientToken,
    acceptResourceShareInvitation_resourceShareInvitationArn,

    -- * Destructuring the Response
    AcceptResourceShareInvitationResponse (..),
    newAcceptResourceShareInvitationResponse,

    -- * Response Lenses
    acceptResourceShareInvitationResponse_clientToken,
    acceptResourceShareInvitationResponse_resourceShareInvitation,
    acceptResourceShareInvitationResponse_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:/ 'newAcceptResourceShareInvitation' smart constructor.
data AcceptResourceShareInvitation = AcceptResourceShareInvitation'
  { -- | 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.
    AcceptResourceShareInvitation -> 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 invitation that you want to accept.
    AcceptResourceShareInvitation -> Text
resourceShareInvitationArn :: Prelude.Text
  }
  deriving (AcceptResourceShareInvitation
-> AcceptResourceShareInvitation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptResourceShareInvitation
-> AcceptResourceShareInvitation -> Bool
$c/= :: AcceptResourceShareInvitation
-> AcceptResourceShareInvitation -> Bool
== :: AcceptResourceShareInvitation
-> AcceptResourceShareInvitation -> Bool
$c== :: AcceptResourceShareInvitation
-> AcceptResourceShareInvitation -> Bool
Prelude.Eq, ReadPrec [AcceptResourceShareInvitation]
ReadPrec AcceptResourceShareInvitation
Int -> ReadS AcceptResourceShareInvitation
ReadS [AcceptResourceShareInvitation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AcceptResourceShareInvitation]
$creadListPrec :: ReadPrec [AcceptResourceShareInvitation]
readPrec :: ReadPrec AcceptResourceShareInvitation
$creadPrec :: ReadPrec AcceptResourceShareInvitation
readList :: ReadS [AcceptResourceShareInvitation]
$creadList :: ReadS [AcceptResourceShareInvitation]
readsPrec :: Int -> ReadS AcceptResourceShareInvitation
$creadsPrec :: Int -> ReadS AcceptResourceShareInvitation
Prelude.Read, Int -> AcceptResourceShareInvitation -> ShowS
[AcceptResourceShareInvitation] -> ShowS
AcceptResourceShareInvitation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptResourceShareInvitation] -> ShowS
$cshowList :: [AcceptResourceShareInvitation] -> ShowS
show :: AcceptResourceShareInvitation -> String
$cshow :: AcceptResourceShareInvitation -> String
showsPrec :: Int -> AcceptResourceShareInvitation -> ShowS
$cshowsPrec :: Int -> AcceptResourceShareInvitation -> ShowS
Prelude.Show, forall x.
Rep AcceptResourceShareInvitation x
-> AcceptResourceShareInvitation
forall x.
AcceptResourceShareInvitation
-> Rep AcceptResourceShareInvitation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AcceptResourceShareInvitation x
-> AcceptResourceShareInvitation
$cfrom :: forall x.
AcceptResourceShareInvitation
-> Rep AcceptResourceShareInvitation x
Prelude.Generic)

-- |
-- Create a value of 'AcceptResourceShareInvitation' 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', 'acceptResourceShareInvitation_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.
--
-- 'resourceShareInvitationArn', 'acceptResourceShareInvitation_resourceShareInvitationArn' - The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the invitation that you want to accept.
newAcceptResourceShareInvitation ::
  -- | 'resourceShareInvitationArn'
  Prelude.Text ->
  AcceptResourceShareInvitation
newAcceptResourceShareInvitation :: Text -> AcceptResourceShareInvitation
newAcceptResourceShareInvitation
  Text
pResourceShareInvitationArn_ =
    AcceptResourceShareInvitation'
      { $sel:clientToken:AcceptResourceShareInvitation' :: Maybe Text
clientToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:resourceShareInvitationArn:AcceptResourceShareInvitation' :: Text
resourceShareInvitationArn =
          Text
pResourceShareInvitationArn_
      }

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

-- | The
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resoure Name (ARN)>
-- of the invitation that you want to accept.
acceptResourceShareInvitation_resourceShareInvitationArn :: Lens.Lens' AcceptResourceShareInvitation Prelude.Text
acceptResourceShareInvitation_resourceShareInvitationArn :: Lens' AcceptResourceShareInvitation Text
acceptResourceShareInvitation_resourceShareInvitationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptResourceShareInvitation' {Text
resourceShareInvitationArn :: Text
$sel:resourceShareInvitationArn:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> Text
resourceShareInvitationArn} -> Text
resourceShareInvitationArn) (\s :: AcceptResourceShareInvitation
s@AcceptResourceShareInvitation' {} Text
a -> AcceptResourceShareInvitation
s {$sel:resourceShareInvitationArn:AcceptResourceShareInvitation' :: Text
resourceShareInvitationArn = Text
a} :: AcceptResourceShareInvitation)

instance
  Core.AWSRequest
    AcceptResourceShareInvitation
  where
  type
    AWSResponse AcceptResourceShareInvitation =
      AcceptResourceShareInvitationResponse
  request :: (Service -> Service)
-> AcceptResourceShareInvitation
-> Request AcceptResourceShareInvitation
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 AcceptResourceShareInvitation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AcceptResourceShareInvitation)))
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 ResourceShareInvitation
-> Int
-> AcceptResourceShareInvitationResponse
AcceptResourceShareInvitationResponse'
            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
"resourceShareInvitation")
            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
    AcceptResourceShareInvitation
  where
  hashWithSalt :: Int -> AcceptResourceShareInvitation -> Int
hashWithSalt Int
_salt AcceptResourceShareInvitation' {Maybe Text
Text
resourceShareInvitationArn :: Text
clientToken :: Maybe Text
$sel:resourceShareInvitationArn:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> Text
$sel:clientToken:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> 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
resourceShareInvitationArn

instance Prelude.NFData AcceptResourceShareInvitation where
  rnf :: AcceptResourceShareInvitation -> ()
rnf AcceptResourceShareInvitation' {Maybe Text
Text
resourceShareInvitationArn :: Text
clientToken :: Maybe Text
$sel:resourceShareInvitationArn:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> Text
$sel:clientToken:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> 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
resourceShareInvitationArn

instance Data.ToHeaders AcceptResourceShareInvitation where
  toHeaders :: AcceptResourceShareInvitation -> 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 AcceptResourceShareInvitation where
  toJSON :: AcceptResourceShareInvitation -> Value
toJSON AcceptResourceShareInvitation' {Maybe Text
Text
resourceShareInvitationArn :: Text
clientToken :: Maybe Text
$sel:resourceShareInvitationArn:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> Text
$sel:clientToken:AcceptResourceShareInvitation' :: AcceptResourceShareInvitation -> 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
"resourceShareInvitationArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceShareInvitationArn
              )
          ]
      )

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

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

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

-- |
-- Create a value of 'AcceptResourceShareInvitationResponse' 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', 'acceptResourceShareInvitationResponse_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.
--
-- 'resourceShareInvitation', 'acceptResourceShareInvitationResponse_resourceShareInvitation' - An object that contains information about the specified invitation.
--
-- 'httpStatus', 'acceptResourceShareInvitationResponse_httpStatus' - The response's http status code.
newAcceptResourceShareInvitationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AcceptResourceShareInvitationResponse
newAcceptResourceShareInvitationResponse :: Int -> AcceptResourceShareInvitationResponse
newAcceptResourceShareInvitationResponse Int
pHttpStatus_ =
  AcceptResourceShareInvitationResponse'
    { $sel:clientToken:AcceptResourceShareInvitationResponse' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareInvitation:AcceptResourceShareInvitationResponse' :: Maybe ResourceShareInvitation
resourceShareInvitation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AcceptResourceShareInvitationResponse' :: 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.
acceptResourceShareInvitationResponse_clientToken :: Lens.Lens' AcceptResourceShareInvitationResponse (Prelude.Maybe Prelude.Text)
acceptResourceShareInvitationResponse_clientToken :: Lens' AcceptResourceShareInvitationResponse (Maybe Text)
acceptResourceShareInvitationResponse_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptResourceShareInvitationResponse' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:AcceptResourceShareInvitationResponse' :: AcceptResourceShareInvitationResponse -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: AcceptResourceShareInvitationResponse
s@AcceptResourceShareInvitationResponse' {} Maybe Text
a -> AcceptResourceShareInvitationResponse
s {$sel:clientToken:AcceptResourceShareInvitationResponse' :: Maybe Text
clientToken = Maybe Text
a} :: AcceptResourceShareInvitationResponse)

-- | An object that contains information about the specified invitation.
acceptResourceShareInvitationResponse_resourceShareInvitation :: Lens.Lens' AcceptResourceShareInvitationResponse (Prelude.Maybe ResourceShareInvitation)
acceptResourceShareInvitationResponse_resourceShareInvitation :: Lens'
  AcceptResourceShareInvitationResponse
  (Maybe ResourceShareInvitation)
acceptResourceShareInvitationResponse_resourceShareInvitation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AcceptResourceShareInvitationResponse' {Maybe ResourceShareInvitation
resourceShareInvitation :: Maybe ResourceShareInvitation
$sel:resourceShareInvitation:AcceptResourceShareInvitationResponse' :: AcceptResourceShareInvitationResponse
-> Maybe ResourceShareInvitation
resourceShareInvitation} -> Maybe ResourceShareInvitation
resourceShareInvitation) (\s :: AcceptResourceShareInvitationResponse
s@AcceptResourceShareInvitationResponse' {} Maybe ResourceShareInvitation
a -> AcceptResourceShareInvitationResponse
s {$sel:resourceShareInvitation:AcceptResourceShareInvitationResponse' :: Maybe ResourceShareInvitation
resourceShareInvitation = Maybe ResourceShareInvitation
a} :: AcceptResourceShareInvitationResponse)

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

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