{-# 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.Redshift.AuthorizeDataShare
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- From a data producer account, authorizes the sharing of a datashare with
-- one or more consumer accounts or managing entities. To authorize a
-- datashare for a data consumer, the producer account must have the
-- correct access permissions.
module Amazonka.Redshift.AuthorizeDataShare
  ( -- * Creating a Request
    AuthorizeDataShare (..),
    newAuthorizeDataShare,

    -- * Request Lenses
    authorizeDataShare_dataShareArn,
    authorizeDataShare_consumerIdentifier,

    -- * Destructuring the Response
    DataShare (..),
    newDataShare,

    -- * Response Lenses
    dataShare_allowPubliclyAccessibleConsumers,
    dataShare_dataShareArn,
    dataShare_dataShareAssociations,
    dataShare_managedBy,
    dataShare_producerArn,
  )
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.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newAuthorizeDataShare' smart constructor.
data AuthorizeDataShare = AuthorizeDataShare'
  { -- | The Amazon Resource Name (ARN) of the datashare that producers are to
    -- authorize sharing for.
    AuthorizeDataShare -> Text
dataShareArn :: Prelude.Text,
    -- | The identifier of the data consumer that is authorized to access the
    -- datashare. This identifier is an Amazon Web Services account ID or a
    -- keyword, such as ADX.
    AuthorizeDataShare -> Text
consumerIdentifier :: Prelude.Text
  }
  deriving (AuthorizeDataShare -> AuthorizeDataShare -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthorizeDataShare -> AuthorizeDataShare -> Bool
$c/= :: AuthorizeDataShare -> AuthorizeDataShare -> Bool
== :: AuthorizeDataShare -> AuthorizeDataShare -> Bool
$c== :: AuthorizeDataShare -> AuthorizeDataShare -> Bool
Prelude.Eq, ReadPrec [AuthorizeDataShare]
ReadPrec AuthorizeDataShare
Int -> ReadS AuthorizeDataShare
ReadS [AuthorizeDataShare]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AuthorizeDataShare]
$creadListPrec :: ReadPrec [AuthorizeDataShare]
readPrec :: ReadPrec AuthorizeDataShare
$creadPrec :: ReadPrec AuthorizeDataShare
readList :: ReadS [AuthorizeDataShare]
$creadList :: ReadS [AuthorizeDataShare]
readsPrec :: Int -> ReadS AuthorizeDataShare
$creadsPrec :: Int -> ReadS AuthorizeDataShare
Prelude.Read, Int -> AuthorizeDataShare -> ShowS
[AuthorizeDataShare] -> ShowS
AuthorizeDataShare -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthorizeDataShare] -> ShowS
$cshowList :: [AuthorizeDataShare] -> ShowS
show :: AuthorizeDataShare -> String
$cshow :: AuthorizeDataShare -> String
showsPrec :: Int -> AuthorizeDataShare -> ShowS
$cshowsPrec :: Int -> AuthorizeDataShare -> ShowS
Prelude.Show, forall x. Rep AuthorizeDataShare x -> AuthorizeDataShare
forall x. AuthorizeDataShare -> Rep AuthorizeDataShare x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthorizeDataShare x -> AuthorizeDataShare
$cfrom :: forall x. AuthorizeDataShare -> Rep AuthorizeDataShare x
Prelude.Generic)

-- |
-- Create a value of 'AuthorizeDataShare' 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:
--
-- 'dataShareArn', 'authorizeDataShare_dataShareArn' - The Amazon Resource Name (ARN) of the datashare that producers are to
-- authorize sharing for.
--
-- 'consumerIdentifier', 'authorizeDataShare_consumerIdentifier' - The identifier of the data consumer that is authorized to access the
-- datashare. This identifier is an Amazon Web Services account ID or a
-- keyword, such as ADX.
newAuthorizeDataShare ::
  -- | 'dataShareArn'
  Prelude.Text ->
  -- | 'consumerIdentifier'
  Prelude.Text ->
  AuthorizeDataShare
newAuthorizeDataShare :: Text -> Text -> AuthorizeDataShare
newAuthorizeDataShare
  Text
pDataShareArn_
  Text
pConsumerIdentifier_ =
    AuthorizeDataShare'
      { $sel:dataShareArn:AuthorizeDataShare' :: Text
dataShareArn = Text
pDataShareArn_,
        $sel:consumerIdentifier:AuthorizeDataShare' :: Text
consumerIdentifier = Text
pConsumerIdentifier_
      }

-- | The Amazon Resource Name (ARN) of the datashare that producers are to
-- authorize sharing for.
authorizeDataShare_dataShareArn :: Lens.Lens' AuthorizeDataShare Prelude.Text
authorizeDataShare_dataShareArn :: Lens' AuthorizeDataShare Text
authorizeDataShare_dataShareArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeDataShare' {Text
dataShareArn :: Text
$sel:dataShareArn:AuthorizeDataShare' :: AuthorizeDataShare -> Text
dataShareArn} -> Text
dataShareArn) (\s :: AuthorizeDataShare
s@AuthorizeDataShare' {} Text
a -> AuthorizeDataShare
s {$sel:dataShareArn:AuthorizeDataShare' :: Text
dataShareArn = Text
a} :: AuthorizeDataShare)

-- | The identifier of the data consumer that is authorized to access the
-- datashare. This identifier is an Amazon Web Services account ID or a
-- keyword, such as ADX.
authorizeDataShare_consumerIdentifier :: Lens.Lens' AuthorizeDataShare Prelude.Text
authorizeDataShare_consumerIdentifier :: Lens' AuthorizeDataShare Text
authorizeDataShare_consumerIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthorizeDataShare' {Text
consumerIdentifier :: Text
$sel:consumerIdentifier:AuthorizeDataShare' :: AuthorizeDataShare -> Text
consumerIdentifier} -> Text
consumerIdentifier) (\s :: AuthorizeDataShare
s@AuthorizeDataShare' {} Text
a -> AuthorizeDataShare
s {$sel:consumerIdentifier:AuthorizeDataShare' :: Text
consumerIdentifier = Text
a} :: AuthorizeDataShare)

instance Core.AWSRequest AuthorizeDataShare where
  type AWSResponse AuthorizeDataShare = DataShare
  request :: (Service -> Service)
-> AuthorizeDataShare -> Request AuthorizeDataShare
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AuthorizeDataShare
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AuthorizeDataShare)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"AuthorizeDataShareResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable AuthorizeDataShare where
  hashWithSalt :: Int -> AuthorizeDataShare -> Int
hashWithSalt Int
_salt AuthorizeDataShare' {Text
consumerIdentifier :: Text
dataShareArn :: Text
$sel:consumerIdentifier:AuthorizeDataShare' :: AuthorizeDataShare -> Text
$sel:dataShareArn:AuthorizeDataShare' :: AuthorizeDataShare -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dataShareArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
consumerIdentifier

instance Prelude.NFData AuthorizeDataShare where
  rnf :: AuthorizeDataShare -> ()
rnf AuthorizeDataShare' {Text
consumerIdentifier :: Text
dataShareArn :: Text
$sel:consumerIdentifier:AuthorizeDataShare' :: AuthorizeDataShare -> Text
$sel:dataShareArn:AuthorizeDataShare' :: AuthorizeDataShare -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
dataShareArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
consumerIdentifier

instance Data.ToHeaders AuthorizeDataShare where
  toHeaders :: AuthorizeDataShare -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AuthorizeDataShare where
  toQuery :: AuthorizeDataShare -> QueryString
toQuery AuthorizeDataShare' {Text
consumerIdentifier :: Text
dataShareArn :: Text
$sel:consumerIdentifier:AuthorizeDataShare' :: AuthorizeDataShare -> Text
$sel:dataShareArn:AuthorizeDataShare' :: AuthorizeDataShare -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AuthorizeDataShare" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"DataShareArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dataShareArn,
        ByteString
"ConsumerIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
consumerIdentifier
      ]