{-# 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.Comprehend.PutResourcePolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches a resource-based policy to a custom model. You can use this
-- policy to authorize an entity in another AWS account to import the
-- custom model, which replicates it in Amazon Comprehend in their account.
module Amazonka.Comprehend.PutResourcePolicy
  ( -- * Creating a Request
    PutResourcePolicy (..),
    newPutResourcePolicy,

    -- * Request Lenses
    putResourcePolicy_policyRevisionId,
    putResourcePolicy_resourceArn,
    putResourcePolicy_resourcePolicy,

    -- * Destructuring the Response
    PutResourcePolicyResponse (..),
    newPutResourcePolicyResponse,

    -- * Response Lenses
    putResourcePolicyResponse_policyRevisionId,
    putResourcePolicyResponse_httpStatus,
  )
where

import Amazonka.Comprehend.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newPutResourcePolicy' smart constructor.
data PutResourcePolicy = PutResourcePolicy'
  { -- | The revision ID that Amazon Comprehend assigned to the policy that you
    -- are updating. If you are creating a new policy that has no prior
    -- version, don\'t use this parameter. Amazon Comprehend creates the
    -- revision ID for you.
    PutResourcePolicy -> Maybe Text
policyRevisionId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the custom model to attach the policy
    -- to.
    PutResourcePolicy -> Text
resourceArn :: Prelude.Text,
    -- | The JSON resource-based policy to attach to your custom model. Provide
    -- your JSON as a UTF-8 encoded string without line breaks. To provide
    -- valid JSON for your policy, enclose the attribute names and values in
    -- double quotes. If the JSON body is also enclosed in double quotes, then
    -- you must escape the double quotes that are inside the policy:
    --
    -- @\"{\\\"attribute\\\": \\\"value\\\", \\\"attribute\\\": [\\\"value\\\"]}\"@
    --
    -- To avoid escaping quotes, you can use single quotes to enclose the
    -- policy and double quotes to enclose the JSON names and values:
    --
    -- @\'{\"attribute\": \"value\", \"attribute\": [\"value\"]}\'@
    PutResourcePolicy -> Text
resourcePolicy :: Prelude.Text
  }
  deriving (PutResourcePolicy -> PutResourcePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutResourcePolicy -> PutResourcePolicy -> Bool
$c/= :: PutResourcePolicy -> PutResourcePolicy -> Bool
== :: PutResourcePolicy -> PutResourcePolicy -> Bool
$c== :: PutResourcePolicy -> PutResourcePolicy -> Bool
Prelude.Eq, ReadPrec [PutResourcePolicy]
ReadPrec PutResourcePolicy
Int -> ReadS PutResourcePolicy
ReadS [PutResourcePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutResourcePolicy]
$creadListPrec :: ReadPrec [PutResourcePolicy]
readPrec :: ReadPrec PutResourcePolicy
$creadPrec :: ReadPrec PutResourcePolicy
readList :: ReadS [PutResourcePolicy]
$creadList :: ReadS [PutResourcePolicy]
readsPrec :: Int -> ReadS PutResourcePolicy
$creadsPrec :: Int -> ReadS PutResourcePolicy
Prelude.Read, Int -> PutResourcePolicy -> ShowS
[PutResourcePolicy] -> ShowS
PutResourcePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutResourcePolicy] -> ShowS
$cshowList :: [PutResourcePolicy] -> ShowS
show :: PutResourcePolicy -> String
$cshow :: PutResourcePolicy -> String
showsPrec :: Int -> PutResourcePolicy -> ShowS
$cshowsPrec :: Int -> PutResourcePolicy -> ShowS
Prelude.Show, forall x. Rep PutResourcePolicy x -> PutResourcePolicy
forall x. PutResourcePolicy -> Rep PutResourcePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutResourcePolicy x -> PutResourcePolicy
$cfrom :: forall x. PutResourcePolicy -> Rep PutResourcePolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutResourcePolicy' 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:
--
-- 'policyRevisionId', 'putResourcePolicy_policyRevisionId' - The revision ID that Amazon Comprehend assigned to the policy that you
-- are updating. If you are creating a new policy that has no prior
-- version, don\'t use this parameter. Amazon Comprehend creates the
-- revision ID for you.
--
-- 'resourceArn', 'putResourcePolicy_resourceArn' - The Amazon Resource Name (ARN) of the custom model to attach the policy
-- to.
--
-- 'resourcePolicy', 'putResourcePolicy_resourcePolicy' - The JSON resource-based policy to attach to your custom model. Provide
-- your JSON as a UTF-8 encoded string without line breaks. To provide
-- valid JSON for your policy, enclose the attribute names and values in
-- double quotes. If the JSON body is also enclosed in double quotes, then
-- you must escape the double quotes that are inside the policy:
--
-- @\"{\\\"attribute\\\": \\\"value\\\", \\\"attribute\\\": [\\\"value\\\"]}\"@
--
-- To avoid escaping quotes, you can use single quotes to enclose the
-- policy and double quotes to enclose the JSON names and values:
--
-- @\'{\"attribute\": \"value\", \"attribute\": [\"value\"]}\'@
newPutResourcePolicy ::
  -- | 'resourceArn'
  Prelude.Text ->
  -- | 'resourcePolicy'
  Prelude.Text ->
  PutResourcePolicy
newPutResourcePolicy :: Text -> Text -> PutResourcePolicy
newPutResourcePolicy Text
pResourceArn_ Text
pResourcePolicy_ =
  PutResourcePolicy'
    { $sel:policyRevisionId:PutResourcePolicy' :: Maybe Text
policyRevisionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:PutResourcePolicy' :: Text
resourceArn = Text
pResourceArn_,
      $sel:resourcePolicy:PutResourcePolicy' :: Text
resourcePolicy = Text
pResourcePolicy_
    }

-- | The revision ID that Amazon Comprehend assigned to the policy that you
-- are updating. If you are creating a new policy that has no prior
-- version, don\'t use this parameter. Amazon Comprehend creates the
-- revision ID for you.
putResourcePolicy_policyRevisionId :: Lens.Lens' PutResourcePolicy (Prelude.Maybe Prelude.Text)
putResourcePolicy_policyRevisionId :: Lens' PutResourcePolicy (Maybe Text)
putResourcePolicy_policyRevisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Maybe Text
policyRevisionId :: Maybe Text
$sel:policyRevisionId:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
policyRevisionId} -> Maybe Text
policyRevisionId) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Maybe Text
a -> PutResourcePolicy
s {$sel:policyRevisionId:PutResourcePolicy' :: Maybe Text
policyRevisionId = Maybe Text
a} :: PutResourcePolicy)

-- | The Amazon Resource Name (ARN) of the custom model to attach the policy
-- to.
putResourcePolicy_resourceArn :: Lens.Lens' PutResourcePolicy Prelude.Text
putResourcePolicy_resourceArn :: Lens' PutResourcePolicy Text
putResourcePolicy_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Text
resourceArn :: Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Text
resourceArn} -> Text
resourceArn) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Text
a -> PutResourcePolicy
s {$sel:resourceArn:PutResourcePolicy' :: Text
resourceArn = Text
a} :: PutResourcePolicy)

-- | The JSON resource-based policy to attach to your custom model. Provide
-- your JSON as a UTF-8 encoded string without line breaks. To provide
-- valid JSON for your policy, enclose the attribute names and values in
-- double quotes. If the JSON body is also enclosed in double quotes, then
-- you must escape the double quotes that are inside the policy:
--
-- @\"{\\\"attribute\\\": \\\"value\\\", \\\"attribute\\\": [\\\"value\\\"]}\"@
--
-- To avoid escaping quotes, you can use single quotes to enclose the
-- policy and double quotes to enclose the JSON names and values:
--
-- @\'{\"attribute\": \"value\", \"attribute\": [\"value\"]}\'@
putResourcePolicy_resourcePolicy :: Lens.Lens' PutResourcePolicy Prelude.Text
putResourcePolicy_resourcePolicy :: Lens' PutResourcePolicy Text
putResourcePolicy_resourcePolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Text
resourcePolicy :: Text
$sel:resourcePolicy:PutResourcePolicy' :: PutResourcePolicy -> Text
resourcePolicy} -> Text
resourcePolicy) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Text
a -> PutResourcePolicy
s {$sel:resourcePolicy:PutResourcePolicy' :: Text
resourcePolicy = Text
a} :: PutResourcePolicy)

instance Core.AWSRequest PutResourcePolicy where
  type
    AWSResponse PutResourcePolicy =
      PutResourcePolicyResponse
  request :: (Service -> Service)
-> PutResourcePolicy -> Request PutResourcePolicy
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 PutResourcePolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutResourcePolicy)))
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 -> Int -> PutResourcePolicyResponse
PutResourcePolicyResponse'
            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
"PolicyRevisionId")
            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 PutResourcePolicy where
  hashWithSalt :: Int -> PutResourcePolicy -> Int
hashWithSalt Int
_salt PutResourcePolicy' {Maybe Text
Text
resourcePolicy :: Text
resourceArn :: Text
policyRevisionId :: Maybe Text
$sel:resourcePolicy:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:policyRevisionId:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyRevisionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourcePolicy

instance Prelude.NFData PutResourcePolicy where
  rnf :: PutResourcePolicy -> ()
rnf PutResourcePolicy' {Maybe Text
Text
resourcePolicy :: Text
resourceArn :: Text
policyRevisionId :: Maybe Text
$sel:resourcePolicy:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:policyRevisionId:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyRevisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourcePolicy

instance Data.ToHeaders PutResourcePolicy where
  toHeaders :: PutResourcePolicy -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"Comprehend_20171127.PutResourcePolicy" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON PutResourcePolicy where
  toJSON :: PutResourcePolicy -> Value
toJSON PutResourcePolicy' {Maybe Text
Text
resourcePolicy :: Text
resourceArn :: Text
policyRevisionId :: Maybe Text
$sel:resourcePolicy:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:policyRevisionId:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"PolicyRevisionId" 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
policyRevisionId,
            forall a. a -> Maybe a
Prelude.Just (Key
"ResourceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceArn),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ResourcePolicy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourcePolicy)
          ]
      )

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

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

-- | /See:/ 'newPutResourcePolicyResponse' smart constructor.
data PutResourcePolicyResponse = PutResourcePolicyResponse'
  { -- | The revision ID of the policy. Each time you modify a policy, Amazon
    -- Comprehend assigns a new revision ID, and it deletes the prior version
    -- of the policy.
    PutResourcePolicyResponse -> Maybe Text
policyRevisionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PutResourcePolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutResourcePolicyResponse -> PutResourcePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutResourcePolicyResponse -> PutResourcePolicyResponse -> Bool
$c/= :: PutResourcePolicyResponse -> PutResourcePolicyResponse -> Bool
== :: PutResourcePolicyResponse -> PutResourcePolicyResponse -> Bool
$c== :: PutResourcePolicyResponse -> PutResourcePolicyResponse -> Bool
Prelude.Eq, ReadPrec [PutResourcePolicyResponse]
ReadPrec PutResourcePolicyResponse
Int -> ReadS PutResourcePolicyResponse
ReadS [PutResourcePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutResourcePolicyResponse]
$creadListPrec :: ReadPrec [PutResourcePolicyResponse]
readPrec :: ReadPrec PutResourcePolicyResponse
$creadPrec :: ReadPrec PutResourcePolicyResponse
readList :: ReadS [PutResourcePolicyResponse]
$creadList :: ReadS [PutResourcePolicyResponse]
readsPrec :: Int -> ReadS PutResourcePolicyResponse
$creadsPrec :: Int -> ReadS PutResourcePolicyResponse
Prelude.Read, Int -> PutResourcePolicyResponse -> ShowS
[PutResourcePolicyResponse] -> ShowS
PutResourcePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutResourcePolicyResponse] -> ShowS
$cshowList :: [PutResourcePolicyResponse] -> ShowS
show :: PutResourcePolicyResponse -> String
$cshow :: PutResourcePolicyResponse -> String
showsPrec :: Int -> PutResourcePolicyResponse -> ShowS
$cshowsPrec :: Int -> PutResourcePolicyResponse -> ShowS
Prelude.Show, forall x.
Rep PutResourcePolicyResponse x -> PutResourcePolicyResponse
forall x.
PutResourcePolicyResponse -> Rep PutResourcePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutResourcePolicyResponse x -> PutResourcePolicyResponse
$cfrom :: forall x.
PutResourcePolicyResponse -> Rep PutResourcePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutResourcePolicyResponse' 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:
--
-- 'policyRevisionId', 'putResourcePolicyResponse_policyRevisionId' - The revision ID of the policy. Each time you modify a policy, Amazon
-- Comprehend assigns a new revision ID, and it deletes the prior version
-- of the policy.
--
-- 'httpStatus', 'putResourcePolicyResponse_httpStatus' - The response's http status code.
newPutResourcePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutResourcePolicyResponse
newPutResourcePolicyResponse :: Int -> PutResourcePolicyResponse
newPutResourcePolicyResponse Int
pHttpStatus_ =
  PutResourcePolicyResponse'
    { $sel:policyRevisionId:PutResourcePolicyResponse' :: Maybe Text
policyRevisionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutResourcePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The revision ID of the policy. Each time you modify a policy, Amazon
-- Comprehend assigns a new revision ID, and it deletes the prior version
-- of the policy.
putResourcePolicyResponse_policyRevisionId :: Lens.Lens' PutResourcePolicyResponse (Prelude.Maybe Prelude.Text)
putResourcePolicyResponse_policyRevisionId :: Lens' PutResourcePolicyResponse (Maybe Text)
putResourcePolicyResponse_policyRevisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicyResponse' {Maybe Text
policyRevisionId :: Maybe Text
$sel:policyRevisionId:PutResourcePolicyResponse' :: PutResourcePolicyResponse -> Maybe Text
policyRevisionId} -> Maybe Text
policyRevisionId) (\s :: PutResourcePolicyResponse
s@PutResourcePolicyResponse' {} Maybe Text
a -> PutResourcePolicyResponse
s {$sel:policyRevisionId:PutResourcePolicyResponse' :: Maybe Text
policyRevisionId = Maybe Text
a} :: PutResourcePolicyResponse)

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

instance Prelude.NFData PutResourcePolicyResponse where
  rnf :: PutResourcePolicyResponse -> ()
rnf PutResourcePolicyResponse' {Int
Maybe Text
httpStatus :: Int
policyRevisionId :: Maybe Text
$sel:httpStatus:PutResourcePolicyResponse' :: PutResourcePolicyResponse -> Int
$sel:policyRevisionId:PutResourcePolicyResponse' :: PutResourcePolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyRevisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus