{-# 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.OAM.PutSinkPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates or updates the resource policy that grants permissions to source
-- accounts to link to the monitoring account sink. When you create a sink
-- policy, you can grant permissions to all accounts in an organization or
-- to individual accounts.
--
-- You can also use a sink policy to limit the types of data that is
-- shared. The three types that you can allow or deny are:
--
-- -   __Metrics__ - Specify with @AWS::CloudWatch::Metric@
--
-- -   __Log groups__ - Specify with @AWS::Logs::LogGroup@
--
-- -   __Traces__ - Specify with @AWS::XRay::Trace@
--
-- See the examples in this section to see how to specify permitted source
-- accounts and data types.
module Amazonka.OAM.PutSinkPolicy
  ( -- * Creating a Request
    PutSinkPolicy (..),
    newPutSinkPolicy,

    -- * Request Lenses
    putSinkPolicy_sinkIdentifier,
    putSinkPolicy_policy,

    -- * Destructuring the Response
    PutSinkPolicyResponse (..),
    newPutSinkPolicyResponse,

    -- * Response Lenses
    putSinkPolicyResponse_policy,
    putSinkPolicyResponse_sinkArn,
    putSinkPolicyResponse_sinkId,
    putSinkPolicyResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.OAM.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newPutSinkPolicy' smart constructor.
data PutSinkPolicy = PutSinkPolicy'
  { -- | The ARN of the sink to attach this policy to.
    PutSinkPolicy -> Text
sinkIdentifier :: Prelude.Text,
    -- | The JSON policy to use. If you are updating an existing policy, the
    -- entire existing policy is replaced by what you specify here.
    --
    -- The policy must be in JSON string format with quotation marks escaped
    -- and no newlines.
    --
    -- For examples of different types of policies, see the __Examples__
    -- section on this page.
    PutSinkPolicy -> Text
policy :: Prelude.Text
  }
  deriving (PutSinkPolicy -> PutSinkPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutSinkPolicy -> PutSinkPolicy -> Bool
$c/= :: PutSinkPolicy -> PutSinkPolicy -> Bool
== :: PutSinkPolicy -> PutSinkPolicy -> Bool
$c== :: PutSinkPolicy -> PutSinkPolicy -> Bool
Prelude.Eq, ReadPrec [PutSinkPolicy]
ReadPrec PutSinkPolicy
Int -> ReadS PutSinkPolicy
ReadS [PutSinkPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutSinkPolicy]
$creadListPrec :: ReadPrec [PutSinkPolicy]
readPrec :: ReadPrec PutSinkPolicy
$creadPrec :: ReadPrec PutSinkPolicy
readList :: ReadS [PutSinkPolicy]
$creadList :: ReadS [PutSinkPolicy]
readsPrec :: Int -> ReadS PutSinkPolicy
$creadsPrec :: Int -> ReadS PutSinkPolicy
Prelude.Read, Int -> PutSinkPolicy -> ShowS
[PutSinkPolicy] -> ShowS
PutSinkPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutSinkPolicy] -> ShowS
$cshowList :: [PutSinkPolicy] -> ShowS
show :: PutSinkPolicy -> String
$cshow :: PutSinkPolicy -> String
showsPrec :: Int -> PutSinkPolicy -> ShowS
$cshowsPrec :: Int -> PutSinkPolicy -> ShowS
Prelude.Show, forall x. Rep PutSinkPolicy x -> PutSinkPolicy
forall x. PutSinkPolicy -> Rep PutSinkPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutSinkPolicy x -> PutSinkPolicy
$cfrom :: forall x. PutSinkPolicy -> Rep PutSinkPolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutSinkPolicy' 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:
--
-- 'sinkIdentifier', 'putSinkPolicy_sinkIdentifier' - The ARN of the sink to attach this policy to.
--
-- 'policy', 'putSinkPolicy_policy' - The JSON policy to use. If you are updating an existing policy, the
-- entire existing policy is replaced by what you specify here.
--
-- The policy must be in JSON string format with quotation marks escaped
-- and no newlines.
--
-- For examples of different types of policies, see the __Examples__
-- section on this page.
newPutSinkPolicy ::
  -- | 'sinkIdentifier'
  Prelude.Text ->
  -- | 'policy'
  Prelude.Text ->
  PutSinkPolicy
newPutSinkPolicy :: Text -> Text -> PutSinkPolicy
newPutSinkPolicy Text
pSinkIdentifier_ Text
pPolicy_ =
  PutSinkPolicy'
    { $sel:sinkIdentifier:PutSinkPolicy' :: Text
sinkIdentifier = Text
pSinkIdentifier_,
      $sel:policy:PutSinkPolicy' :: Text
policy = Text
pPolicy_
    }

-- | The ARN of the sink to attach this policy to.
putSinkPolicy_sinkIdentifier :: Lens.Lens' PutSinkPolicy Prelude.Text
putSinkPolicy_sinkIdentifier :: Lens' PutSinkPolicy Text
putSinkPolicy_sinkIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutSinkPolicy' {Text
sinkIdentifier :: Text
$sel:sinkIdentifier:PutSinkPolicy' :: PutSinkPolicy -> Text
sinkIdentifier} -> Text
sinkIdentifier) (\s :: PutSinkPolicy
s@PutSinkPolicy' {} Text
a -> PutSinkPolicy
s {$sel:sinkIdentifier:PutSinkPolicy' :: Text
sinkIdentifier = Text
a} :: PutSinkPolicy)

-- | The JSON policy to use. If you are updating an existing policy, the
-- entire existing policy is replaced by what you specify here.
--
-- The policy must be in JSON string format with quotation marks escaped
-- and no newlines.
--
-- For examples of different types of policies, see the __Examples__
-- section on this page.
putSinkPolicy_policy :: Lens.Lens' PutSinkPolicy Prelude.Text
putSinkPolicy_policy :: Lens' PutSinkPolicy Text
putSinkPolicy_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutSinkPolicy' {Text
policy :: Text
$sel:policy:PutSinkPolicy' :: PutSinkPolicy -> Text
policy} -> Text
policy) (\s :: PutSinkPolicy
s@PutSinkPolicy' {} Text
a -> PutSinkPolicy
s {$sel:policy:PutSinkPolicy' :: Text
policy = Text
a} :: PutSinkPolicy)

instance Core.AWSRequest PutSinkPolicy where
  type
    AWSResponse PutSinkPolicy =
      PutSinkPolicyResponse
  request :: (Service -> Service) -> PutSinkPolicy -> Request PutSinkPolicy
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 PutSinkPolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutSinkPolicy)))
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 Text -> Maybe Text -> Int -> PutSinkPolicyResponse
PutSinkPolicyResponse'
            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
"Policy")
            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
"SinkArn")
            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
"SinkId")
            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 PutSinkPolicy where
  hashWithSalt :: Int -> PutSinkPolicy -> Int
hashWithSalt Int
_salt PutSinkPolicy' {Text
policy :: Text
sinkIdentifier :: Text
$sel:policy:PutSinkPolicy' :: PutSinkPolicy -> Text
$sel:sinkIdentifier:PutSinkPolicy' :: PutSinkPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sinkIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policy

instance Prelude.NFData PutSinkPolicy where
  rnf :: PutSinkPolicy -> ()
rnf PutSinkPolicy' {Text
policy :: Text
sinkIdentifier :: Text
$sel:policy:PutSinkPolicy' :: PutSinkPolicy -> Text
$sel:sinkIdentifier:PutSinkPolicy' :: PutSinkPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
sinkIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policy

instance Data.ToHeaders PutSinkPolicy where
  toHeaders :: PutSinkPolicy -> 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 PutSinkPolicy where
  toJSON :: PutSinkPolicy -> Value
toJSON PutSinkPolicy' {Text
policy :: Text
sinkIdentifier :: Text
$sel:policy:PutSinkPolicy' :: PutSinkPolicy -> Text
$sel:sinkIdentifier:PutSinkPolicy' :: PutSinkPolicy -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"SinkIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sinkIdentifier),
            forall a. a -> Maybe a
Prelude.Just (Key
"Policy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policy)
          ]
      )

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

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

-- | /See:/ 'newPutSinkPolicyResponse' smart constructor.
data PutSinkPolicyResponse = PutSinkPolicyResponse'
  { -- | The policy that you specified.
    PutSinkPolicyResponse -> Maybe Text
policy :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the sink.
    PutSinkPolicyResponse -> Maybe Text
sinkArn :: Prelude.Maybe Prelude.Text,
    -- | The random ID string that Amazon Web Services generated as part of the
    -- sink ARN.
    PutSinkPolicyResponse -> Maybe Text
sinkId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    PutSinkPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutSinkPolicyResponse -> PutSinkPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutSinkPolicyResponse -> PutSinkPolicyResponse -> Bool
$c/= :: PutSinkPolicyResponse -> PutSinkPolicyResponse -> Bool
== :: PutSinkPolicyResponse -> PutSinkPolicyResponse -> Bool
$c== :: PutSinkPolicyResponse -> PutSinkPolicyResponse -> Bool
Prelude.Eq, ReadPrec [PutSinkPolicyResponse]
ReadPrec PutSinkPolicyResponse
Int -> ReadS PutSinkPolicyResponse
ReadS [PutSinkPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutSinkPolicyResponse]
$creadListPrec :: ReadPrec [PutSinkPolicyResponse]
readPrec :: ReadPrec PutSinkPolicyResponse
$creadPrec :: ReadPrec PutSinkPolicyResponse
readList :: ReadS [PutSinkPolicyResponse]
$creadList :: ReadS [PutSinkPolicyResponse]
readsPrec :: Int -> ReadS PutSinkPolicyResponse
$creadsPrec :: Int -> ReadS PutSinkPolicyResponse
Prelude.Read, Int -> PutSinkPolicyResponse -> ShowS
[PutSinkPolicyResponse] -> ShowS
PutSinkPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutSinkPolicyResponse] -> ShowS
$cshowList :: [PutSinkPolicyResponse] -> ShowS
show :: PutSinkPolicyResponse -> String
$cshow :: PutSinkPolicyResponse -> String
showsPrec :: Int -> PutSinkPolicyResponse -> ShowS
$cshowsPrec :: Int -> PutSinkPolicyResponse -> ShowS
Prelude.Show, forall x. Rep PutSinkPolicyResponse x -> PutSinkPolicyResponse
forall x. PutSinkPolicyResponse -> Rep PutSinkPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutSinkPolicyResponse x -> PutSinkPolicyResponse
$cfrom :: forall x. PutSinkPolicyResponse -> Rep PutSinkPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutSinkPolicyResponse' 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:
--
-- 'policy', 'putSinkPolicyResponse_policy' - The policy that you specified.
--
-- 'sinkArn', 'putSinkPolicyResponse_sinkArn' - The ARN of the sink.
--
-- 'sinkId', 'putSinkPolicyResponse_sinkId' - The random ID string that Amazon Web Services generated as part of the
-- sink ARN.
--
-- 'httpStatus', 'putSinkPolicyResponse_httpStatus' - The response's http status code.
newPutSinkPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutSinkPolicyResponse
newPutSinkPolicyResponse :: Int -> PutSinkPolicyResponse
newPutSinkPolicyResponse Int
pHttpStatus_ =
  PutSinkPolicyResponse'
    { $sel:policy:PutSinkPolicyResponse' :: Maybe Text
policy = forall a. Maybe a
Prelude.Nothing,
      $sel:sinkArn:PutSinkPolicyResponse' :: Maybe Text
sinkArn = forall a. Maybe a
Prelude.Nothing,
      $sel:sinkId:PutSinkPolicyResponse' :: Maybe Text
sinkId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutSinkPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The policy that you specified.
putSinkPolicyResponse_policy :: Lens.Lens' PutSinkPolicyResponse (Prelude.Maybe Prelude.Text)
putSinkPolicyResponse_policy :: Lens' PutSinkPolicyResponse (Maybe Text)
putSinkPolicyResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutSinkPolicyResponse' {Maybe Text
policy :: Maybe Text
$sel:policy:PutSinkPolicyResponse' :: PutSinkPolicyResponse -> Maybe Text
policy} -> Maybe Text
policy) (\s :: PutSinkPolicyResponse
s@PutSinkPolicyResponse' {} Maybe Text
a -> PutSinkPolicyResponse
s {$sel:policy:PutSinkPolicyResponse' :: Maybe Text
policy = Maybe Text
a} :: PutSinkPolicyResponse)

-- | The ARN of the sink.
putSinkPolicyResponse_sinkArn :: Lens.Lens' PutSinkPolicyResponse (Prelude.Maybe Prelude.Text)
putSinkPolicyResponse_sinkArn :: Lens' PutSinkPolicyResponse (Maybe Text)
putSinkPolicyResponse_sinkArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutSinkPolicyResponse' {Maybe Text
sinkArn :: Maybe Text
$sel:sinkArn:PutSinkPolicyResponse' :: PutSinkPolicyResponse -> Maybe Text
sinkArn} -> Maybe Text
sinkArn) (\s :: PutSinkPolicyResponse
s@PutSinkPolicyResponse' {} Maybe Text
a -> PutSinkPolicyResponse
s {$sel:sinkArn:PutSinkPolicyResponse' :: Maybe Text
sinkArn = Maybe Text
a} :: PutSinkPolicyResponse)

-- | The random ID string that Amazon Web Services generated as part of the
-- sink ARN.
putSinkPolicyResponse_sinkId :: Lens.Lens' PutSinkPolicyResponse (Prelude.Maybe Prelude.Text)
putSinkPolicyResponse_sinkId :: Lens' PutSinkPolicyResponse (Maybe Text)
putSinkPolicyResponse_sinkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutSinkPolicyResponse' {Maybe Text
sinkId :: Maybe Text
$sel:sinkId:PutSinkPolicyResponse' :: PutSinkPolicyResponse -> Maybe Text
sinkId} -> Maybe Text
sinkId) (\s :: PutSinkPolicyResponse
s@PutSinkPolicyResponse' {} Maybe Text
a -> PutSinkPolicyResponse
s {$sel:sinkId:PutSinkPolicyResponse' :: Maybe Text
sinkId = Maybe Text
a} :: PutSinkPolicyResponse)

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

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