{-# 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.SNS.PutDataProtectionPolicy
-- 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 or updates an inline policy document that is stored in the
-- specified Amazon SNS topic.
module Amazonka.SNS.PutDataProtectionPolicy
  ( -- * Creating a Request
    PutDataProtectionPolicy (..),
    newPutDataProtectionPolicy,

    -- * Request Lenses
    putDataProtectionPolicy_resourceArn,
    putDataProtectionPolicy_dataProtectionPolicy,

    -- * Destructuring the Response
    PutDataProtectionPolicyResponse (..),
    newPutDataProtectionPolicyResponse,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SNS.Types

-- | /See:/ 'newPutDataProtectionPolicy' smart constructor.
data PutDataProtectionPolicy = PutDataProtectionPolicy'
  { -- | The ARN of the topic whose @DataProtectionPolicy@ you want to add or
    -- update.
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the Amazon Web Services General Reference.
    PutDataProtectionPolicy -> Text
resourceArn :: Prelude.Text,
    -- | The JSON serialization of the topic\'s @DataProtectionPolicy@.
    --
    -- The @DataProtectionPolicy@ must be in JSON string format.
    --
    -- Length Constraints: Maximum length of 30,720.
    PutDataProtectionPolicy -> Text
dataProtectionPolicy :: Prelude.Text
  }
  deriving (PutDataProtectionPolicy -> PutDataProtectionPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutDataProtectionPolicy -> PutDataProtectionPolicy -> Bool
$c/= :: PutDataProtectionPolicy -> PutDataProtectionPolicy -> Bool
== :: PutDataProtectionPolicy -> PutDataProtectionPolicy -> Bool
$c== :: PutDataProtectionPolicy -> PutDataProtectionPolicy -> Bool
Prelude.Eq, ReadPrec [PutDataProtectionPolicy]
ReadPrec PutDataProtectionPolicy
Int -> ReadS PutDataProtectionPolicy
ReadS [PutDataProtectionPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutDataProtectionPolicy]
$creadListPrec :: ReadPrec [PutDataProtectionPolicy]
readPrec :: ReadPrec PutDataProtectionPolicy
$creadPrec :: ReadPrec PutDataProtectionPolicy
readList :: ReadS [PutDataProtectionPolicy]
$creadList :: ReadS [PutDataProtectionPolicy]
readsPrec :: Int -> ReadS PutDataProtectionPolicy
$creadsPrec :: Int -> ReadS PutDataProtectionPolicy
Prelude.Read, Int -> PutDataProtectionPolicy -> ShowS
[PutDataProtectionPolicy] -> ShowS
PutDataProtectionPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutDataProtectionPolicy] -> ShowS
$cshowList :: [PutDataProtectionPolicy] -> ShowS
show :: PutDataProtectionPolicy -> String
$cshow :: PutDataProtectionPolicy -> String
showsPrec :: Int -> PutDataProtectionPolicy -> ShowS
$cshowsPrec :: Int -> PutDataProtectionPolicy -> ShowS
Prelude.Show, forall x. Rep PutDataProtectionPolicy x -> PutDataProtectionPolicy
forall x. PutDataProtectionPolicy -> Rep PutDataProtectionPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutDataProtectionPolicy x -> PutDataProtectionPolicy
$cfrom :: forall x. PutDataProtectionPolicy -> Rep PutDataProtectionPolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutDataProtectionPolicy' 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:
--
-- 'resourceArn', 'putDataProtectionPolicy_resourceArn' - The ARN of the topic whose @DataProtectionPolicy@ you want to add or
-- update.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the Amazon Web Services General Reference.
--
-- 'dataProtectionPolicy', 'putDataProtectionPolicy_dataProtectionPolicy' - The JSON serialization of the topic\'s @DataProtectionPolicy@.
--
-- The @DataProtectionPolicy@ must be in JSON string format.
--
-- Length Constraints: Maximum length of 30,720.
newPutDataProtectionPolicy ::
  -- | 'resourceArn'
  Prelude.Text ->
  -- | 'dataProtectionPolicy'
  Prelude.Text ->
  PutDataProtectionPolicy
newPutDataProtectionPolicy :: Text -> Text -> PutDataProtectionPolicy
newPutDataProtectionPolicy
  Text
pResourceArn_
  Text
pDataProtectionPolicy_ =
    PutDataProtectionPolicy'
      { $sel:resourceArn:PutDataProtectionPolicy' :: Text
resourceArn =
          Text
pResourceArn_,
        $sel:dataProtectionPolicy:PutDataProtectionPolicy' :: Text
dataProtectionPolicy = Text
pDataProtectionPolicy_
      }

-- | The ARN of the topic whose @DataProtectionPolicy@ you want to add or
-- update.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the Amazon Web Services General Reference.
putDataProtectionPolicy_resourceArn :: Lens.Lens' PutDataProtectionPolicy Prelude.Text
putDataProtectionPolicy_resourceArn :: Lens' PutDataProtectionPolicy Text
putDataProtectionPolicy_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutDataProtectionPolicy' {Text
resourceArn :: Text
$sel:resourceArn:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
resourceArn} -> Text
resourceArn) (\s :: PutDataProtectionPolicy
s@PutDataProtectionPolicy' {} Text
a -> PutDataProtectionPolicy
s {$sel:resourceArn:PutDataProtectionPolicy' :: Text
resourceArn = Text
a} :: PutDataProtectionPolicy)

-- | The JSON serialization of the topic\'s @DataProtectionPolicy@.
--
-- The @DataProtectionPolicy@ must be in JSON string format.
--
-- Length Constraints: Maximum length of 30,720.
putDataProtectionPolicy_dataProtectionPolicy :: Lens.Lens' PutDataProtectionPolicy Prelude.Text
putDataProtectionPolicy_dataProtectionPolicy :: Lens' PutDataProtectionPolicy Text
putDataProtectionPolicy_dataProtectionPolicy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutDataProtectionPolicy' {Text
dataProtectionPolicy :: Text
$sel:dataProtectionPolicy:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
dataProtectionPolicy} -> Text
dataProtectionPolicy) (\s :: PutDataProtectionPolicy
s@PutDataProtectionPolicy' {} Text
a -> PutDataProtectionPolicy
s {$sel:dataProtectionPolicy:PutDataProtectionPolicy' :: Text
dataProtectionPolicy = Text
a} :: PutDataProtectionPolicy)

instance Core.AWSRequest PutDataProtectionPolicy where
  type
    AWSResponse PutDataProtectionPolicy =
      PutDataProtectionPolicyResponse
  request :: (Service -> Service)
-> PutDataProtectionPolicy -> Request PutDataProtectionPolicy
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 PutDataProtectionPolicy
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutDataProtectionPolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      PutDataProtectionPolicyResponse
PutDataProtectionPolicyResponse'

instance Prelude.Hashable PutDataProtectionPolicy where
  hashWithSalt :: Int -> PutDataProtectionPolicy -> Int
hashWithSalt Int
_salt PutDataProtectionPolicy' {Text
dataProtectionPolicy :: Text
resourceArn :: Text
$sel:dataProtectionPolicy:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
$sel:resourceArn:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dataProtectionPolicy

instance Prelude.NFData PutDataProtectionPolicy where
  rnf :: PutDataProtectionPolicy -> ()
rnf PutDataProtectionPolicy' {Text
dataProtectionPolicy :: Text
resourceArn :: Text
$sel:dataProtectionPolicy:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
$sel:resourceArn:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
..} =
    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
dataProtectionPolicy

instance Data.ToHeaders PutDataProtectionPolicy where
  toHeaders :: PutDataProtectionPolicy -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery PutDataProtectionPolicy where
  toQuery :: PutDataProtectionPolicy -> QueryString
toQuery PutDataProtectionPolicy' {Text
dataProtectionPolicy :: Text
resourceArn :: Text
$sel:dataProtectionPolicy:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
$sel:resourceArn:PutDataProtectionPolicy' :: PutDataProtectionPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"PutDataProtectionPolicy" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"ResourceArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
resourceArn,
        ByteString
"DataProtectionPolicy" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dataProtectionPolicy
      ]

-- | /See:/ 'newPutDataProtectionPolicyResponse' smart constructor.
data PutDataProtectionPolicyResponse = PutDataProtectionPolicyResponse'
  {
  }
  deriving (PutDataProtectionPolicyResponse
-> PutDataProtectionPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutDataProtectionPolicyResponse
-> PutDataProtectionPolicyResponse -> Bool
$c/= :: PutDataProtectionPolicyResponse
-> PutDataProtectionPolicyResponse -> Bool
== :: PutDataProtectionPolicyResponse
-> PutDataProtectionPolicyResponse -> Bool
$c== :: PutDataProtectionPolicyResponse
-> PutDataProtectionPolicyResponse -> Bool
Prelude.Eq, ReadPrec [PutDataProtectionPolicyResponse]
ReadPrec PutDataProtectionPolicyResponse
Int -> ReadS PutDataProtectionPolicyResponse
ReadS [PutDataProtectionPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutDataProtectionPolicyResponse]
$creadListPrec :: ReadPrec [PutDataProtectionPolicyResponse]
readPrec :: ReadPrec PutDataProtectionPolicyResponse
$creadPrec :: ReadPrec PutDataProtectionPolicyResponse
readList :: ReadS [PutDataProtectionPolicyResponse]
$creadList :: ReadS [PutDataProtectionPolicyResponse]
readsPrec :: Int -> ReadS PutDataProtectionPolicyResponse
$creadsPrec :: Int -> ReadS PutDataProtectionPolicyResponse
Prelude.Read, Int -> PutDataProtectionPolicyResponse -> ShowS
[PutDataProtectionPolicyResponse] -> ShowS
PutDataProtectionPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutDataProtectionPolicyResponse] -> ShowS
$cshowList :: [PutDataProtectionPolicyResponse] -> ShowS
show :: PutDataProtectionPolicyResponse -> String
$cshow :: PutDataProtectionPolicyResponse -> String
showsPrec :: Int -> PutDataProtectionPolicyResponse -> ShowS
$cshowsPrec :: Int -> PutDataProtectionPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep PutDataProtectionPolicyResponse x
-> PutDataProtectionPolicyResponse
forall x.
PutDataProtectionPolicyResponse
-> Rep PutDataProtectionPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutDataProtectionPolicyResponse x
-> PutDataProtectionPolicyResponse
$cfrom :: forall x.
PutDataProtectionPolicyResponse
-> Rep PutDataProtectionPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutDataProtectionPolicyResponse' 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.
newPutDataProtectionPolicyResponse ::
  PutDataProtectionPolicyResponse
newPutDataProtectionPolicyResponse :: PutDataProtectionPolicyResponse
newPutDataProtectionPolicyResponse =
  PutDataProtectionPolicyResponse
PutDataProtectionPolicyResponse'

instance
  Prelude.NFData
    PutDataProtectionPolicyResponse
  where
  rnf :: PutDataProtectionPolicyResponse -> ()
rnf PutDataProtectionPolicyResponse
_ = ()