{-# 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.Glue.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)
--
-- Sets the Data Catalog resource policy for access control.
module Amazonka.Glue.PutResourcePolicy
  ( -- * Creating a Request
    PutResourcePolicy (..),
    newPutResourcePolicy,

    -- * Request Lenses
    putResourcePolicy_enableHybrid,
    putResourcePolicy_policyExistsCondition,
    putResourcePolicy_policyHashCondition,
    putResourcePolicy_resourceArn,
    putResourcePolicy_policyInJson,

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

    -- * Response Lenses
    putResourcePolicyResponse_policyHash,
    putResourcePolicyResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
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'
  { -- | If @\'TRUE\'@, indicates that you are using both methods to grant
    -- cross-account access to Data Catalog resources:
    --
    -- -   By directly updating the resource policy with @PutResourePolicy@
    --
    -- -   By using the __Grant permissions__ command on the Amazon Web
    --     Services Management Console.
    --
    -- Must be set to @\'TRUE\'@ if you have already used the Management
    -- Console to grant cross-account access, otherwise the call fails. Default
    -- is \'FALSE\'.
    PutResourcePolicy -> Maybe EnableHybridValues
enableHybrid :: Prelude.Maybe EnableHybridValues,
    -- | A value of @MUST_EXIST@ is used to update a policy. A value of
    -- @NOT_EXIST@ is used to create a new policy. If a value of @NONE@ or a
    -- null value is used, the call does not depend on the existence of a
    -- policy.
    PutResourcePolicy -> Maybe ExistCondition
policyExistsCondition :: Prelude.Maybe ExistCondition,
    -- | The hash value returned when the previous policy was set using
    -- @PutResourcePolicy@. Its purpose is to prevent concurrent modifications
    -- of a policy. Do not use this parameter if no previous policy has been
    -- set.
    PutResourcePolicy -> Maybe Text
policyHashCondition :: Prelude.Maybe Prelude.Text,
    -- | Do not use. For internal use only.
    PutResourcePolicy -> Maybe Text
resourceArn :: Prelude.Maybe Prelude.Text,
    -- | Contains the policy document to set, in JSON format.
    PutResourcePolicy -> Text
policyInJson :: 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:
--
-- 'enableHybrid', 'putResourcePolicy_enableHybrid' - If @\'TRUE\'@, indicates that you are using both methods to grant
-- cross-account access to Data Catalog resources:
--
-- -   By directly updating the resource policy with @PutResourePolicy@
--
-- -   By using the __Grant permissions__ command on the Amazon Web
--     Services Management Console.
--
-- Must be set to @\'TRUE\'@ if you have already used the Management
-- Console to grant cross-account access, otherwise the call fails. Default
-- is \'FALSE\'.
--
-- 'policyExistsCondition', 'putResourcePolicy_policyExistsCondition' - A value of @MUST_EXIST@ is used to update a policy. A value of
-- @NOT_EXIST@ is used to create a new policy. If a value of @NONE@ or a
-- null value is used, the call does not depend on the existence of a
-- policy.
--
-- 'policyHashCondition', 'putResourcePolicy_policyHashCondition' - The hash value returned when the previous policy was set using
-- @PutResourcePolicy@. Its purpose is to prevent concurrent modifications
-- of a policy. Do not use this parameter if no previous policy has been
-- set.
--
-- 'resourceArn', 'putResourcePolicy_resourceArn' - Do not use. For internal use only.
--
-- 'policyInJson', 'putResourcePolicy_policyInJson' - Contains the policy document to set, in JSON format.
newPutResourcePolicy ::
  -- | 'policyInJson'
  Prelude.Text ->
  PutResourcePolicy
newPutResourcePolicy :: Text -> PutResourcePolicy
newPutResourcePolicy Text
pPolicyInJson_ =
  PutResourcePolicy'
    { $sel:enableHybrid:PutResourcePolicy' :: Maybe EnableHybridValues
enableHybrid = forall a. Maybe a
Prelude.Nothing,
      $sel:policyExistsCondition:PutResourcePolicy' :: Maybe ExistCondition
policyExistsCondition = forall a. Maybe a
Prelude.Nothing,
      $sel:policyHashCondition:PutResourcePolicy' :: Maybe Text
policyHashCondition = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:PutResourcePolicy' :: Maybe Text
resourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:policyInJson:PutResourcePolicy' :: Text
policyInJson = Text
pPolicyInJson_
    }

-- | If @\'TRUE\'@, indicates that you are using both methods to grant
-- cross-account access to Data Catalog resources:
--
-- -   By directly updating the resource policy with @PutResourePolicy@
--
-- -   By using the __Grant permissions__ command on the Amazon Web
--     Services Management Console.
--
-- Must be set to @\'TRUE\'@ if you have already used the Management
-- Console to grant cross-account access, otherwise the call fails. Default
-- is \'FALSE\'.
putResourcePolicy_enableHybrid :: Lens.Lens' PutResourcePolicy (Prelude.Maybe EnableHybridValues)
putResourcePolicy_enableHybrid :: Lens' PutResourcePolicy (Maybe EnableHybridValues)
putResourcePolicy_enableHybrid = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Maybe EnableHybridValues
enableHybrid :: Maybe EnableHybridValues
$sel:enableHybrid:PutResourcePolicy' :: PutResourcePolicy -> Maybe EnableHybridValues
enableHybrid} -> Maybe EnableHybridValues
enableHybrid) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Maybe EnableHybridValues
a -> PutResourcePolicy
s {$sel:enableHybrid:PutResourcePolicy' :: Maybe EnableHybridValues
enableHybrid = Maybe EnableHybridValues
a} :: PutResourcePolicy)

-- | A value of @MUST_EXIST@ is used to update a policy. A value of
-- @NOT_EXIST@ is used to create a new policy. If a value of @NONE@ or a
-- null value is used, the call does not depend on the existence of a
-- policy.
putResourcePolicy_policyExistsCondition :: Lens.Lens' PutResourcePolicy (Prelude.Maybe ExistCondition)
putResourcePolicy_policyExistsCondition :: Lens' PutResourcePolicy (Maybe ExistCondition)
putResourcePolicy_policyExistsCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Maybe ExistCondition
policyExistsCondition :: Maybe ExistCondition
$sel:policyExistsCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe ExistCondition
policyExistsCondition} -> Maybe ExistCondition
policyExistsCondition) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Maybe ExistCondition
a -> PutResourcePolicy
s {$sel:policyExistsCondition:PutResourcePolicy' :: Maybe ExistCondition
policyExistsCondition = Maybe ExistCondition
a} :: PutResourcePolicy)

-- | The hash value returned when the previous policy was set using
-- @PutResourcePolicy@. Its purpose is to prevent concurrent modifications
-- of a policy. Do not use this parameter if no previous policy has been
-- set.
putResourcePolicy_policyHashCondition :: Lens.Lens' PutResourcePolicy (Prelude.Maybe Prelude.Text)
putResourcePolicy_policyHashCondition :: Lens' PutResourcePolicy (Maybe Text)
putResourcePolicy_policyHashCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Maybe Text
policyHashCondition :: Maybe Text
$sel:policyHashCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
policyHashCondition} -> Maybe Text
policyHashCondition) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Maybe Text
a -> PutResourcePolicy
s {$sel:policyHashCondition:PutResourcePolicy' :: Maybe Text
policyHashCondition = Maybe Text
a} :: PutResourcePolicy)

-- | Do not use. For internal use only.
putResourcePolicy_resourceArn :: Lens.Lens' PutResourcePolicy (Prelude.Maybe Prelude.Text)
putResourcePolicy_resourceArn :: Lens' PutResourcePolicy (Maybe Text)
putResourcePolicy_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Maybe Text
resourceArn :: Maybe Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
resourceArn} -> Maybe Text
resourceArn) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Maybe Text
a -> PutResourcePolicy
s {$sel:resourceArn:PutResourcePolicy' :: Maybe Text
resourceArn = Maybe Text
a} :: PutResourcePolicy)

-- | Contains the policy document to set, in JSON format.
putResourcePolicy_policyInJson :: Lens.Lens' PutResourcePolicy Prelude.Text
putResourcePolicy_policyInJson :: Lens' PutResourcePolicy Text
putResourcePolicy_policyInJson = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicy' {Text
policyInJson :: Text
$sel:policyInJson:PutResourcePolicy' :: PutResourcePolicy -> Text
policyInJson} -> Text
policyInJson) (\s :: PutResourcePolicy
s@PutResourcePolicy' {} Text
a -> PutResourcePolicy
s {$sel:policyInJson:PutResourcePolicy' :: Text
policyInJson = 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
"PolicyHash")
            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
Maybe EnableHybridValues
Maybe ExistCondition
Text
policyInJson :: Text
resourceArn :: Maybe Text
policyHashCondition :: Maybe Text
policyExistsCondition :: Maybe ExistCondition
enableHybrid :: Maybe EnableHybridValues
$sel:policyInJson:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
$sel:policyHashCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
$sel:policyExistsCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe ExistCondition
$sel:enableHybrid:PutResourcePolicy' :: PutResourcePolicy -> Maybe EnableHybridValues
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnableHybridValues
enableHybrid
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExistCondition
policyExistsCondition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyHashCondition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyInJson

instance Prelude.NFData PutResourcePolicy where
  rnf :: PutResourcePolicy -> ()
rnf PutResourcePolicy' {Maybe Text
Maybe EnableHybridValues
Maybe ExistCondition
Text
policyInJson :: Text
resourceArn :: Maybe Text
policyHashCondition :: Maybe Text
policyExistsCondition :: Maybe ExistCondition
enableHybrid :: Maybe EnableHybridValues
$sel:policyInJson:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
$sel:policyHashCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
$sel:policyExistsCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe ExistCondition
$sel:enableHybrid:PutResourcePolicy' :: PutResourcePolicy -> Maybe EnableHybridValues
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe EnableHybridValues
enableHybrid
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExistCondition
policyExistsCondition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyHashCondition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyInJson

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
"AWSGlue.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
Maybe EnableHybridValues
Maybe ExistCondition
Text
policyInJson :: Text
resourceArn :: Maybe Text
policyHashCondition :: Maybe Text
policyExistsCondition :: Maybe ExistCondition
enableHybrid :: Maybe EnableHybridValues
$sel:policyInJson:PutResourcePolicy' :: PutResourcePolicy -> Text
$sel:resourceArn:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
$sel:policyHashCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe Text
$sel:policyExistsCondition:PutResourcePolicy' :: PutResourcePolicy -> Maybe ExistCondition
$sel:enableHybrid:PutResourcePolicy' :: PutResourcePolicy -> Maybe EnableHybridValues
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EnableHybrid" 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 EnableHybridValues
enableHybrid,
            (Key
"PolicyExistsCondition" 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 ExistCondition
policyExistsCondition,
            (Key
"PolicyHashCondition" 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
policyHashCondition,
            (Key
"ResourceArn" 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
resourceArn,
            forall a. a -> Maybe a
Prelude.Just (Key
"PolicyInJson" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policyInJson)
          ]
      )

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'
  { -- | A hash of the policy that has just been set. This must be included in a
    -- subsequent call that overwrites or updates this policy.
    PutResourcePolicyResponse -> Maybe Text
policyHash :: 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:
--
-- 'policyHash', 'putResourcePolicyResponse_policyHash' - A hash of the policy that has just been set. This must be included in a
-- subsequent call that overwrites or updates this policy.
--
-- 'httpStatus', 'putResourcePolicyResponse_httpStatus' - The response's http status code.
newPutResourcePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutResourcePolicyResponse
newPutResourcePolicyResponse :: Int -> PutResourcePolicyResponse
newPutResourcePolicyResponse Int
pHttpStatus_ =
  PutResourcePolicyResponse'
    { $sel:policyHash:PutResourcePolicyResponse' :: Maybe Text
policyHash =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutResourcePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A hash of the policy that has just been set. This must be included in a
-- subsequent call that overwrites or updates this policy.
putResourcePolicyResponse_policyHash :: Lens.Lens' PutResourcePolicyResponse (Prelude.Maybe Prelude.Text)
putResourcePolicyResponse_policyHash :: Lens' PutResourcePolicyResponse (Maybe Text)
putResourcePolicyResponse_policyHash = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutResourcePolicyResponse' {Maybe Text
policyHash :: Maybe Text
$sel:policyHash:PutResourcePolicyResponse' :: PutResourcePolicyResponse -> Maybe Text
policyHash} -> Maybe Text
policyHash) (\s :: PutResourcePolicyResponse
s@PutResourcePolicyResponse' {} Maybe Text
a -> PutResourcePolicyResponse
s {$sel:policyHash:PutResourcePolicyResponse' :: Maybe Text
policyHash = 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
policyHash :: Maybe Text
$sel:httpStatus:PutResourcePolicyResponse' :: PutResourcePolicyResponse -> Int
$sel:policyHash:PutResourcePolicyResponse' :: PutResourcePolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyHash
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus