{-# 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.RDS.CreateEventSubscription
-- 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 an RDS event notification subscription. This operation requires
-- a topic Amazon Resource Name (ARN) created by either the RDS console,
-- the SNS console, or the SNS API. To obtain an ARN with SNS, you must
-- create a topic in Amazon SNS and subscribe to the topic. The ARN is
-- displayed in the SNS console.
--
-- You can specify the type of source (@SourceType@) that you want to be
-- notified of and provide a list of RDS sources (@SourceIds@) that
-- triggers the events. You can also provide a list of event categories
-- (@EventCategories@) for events that you want to be notified of. For
-- example, you can specify @SourceType@ = @db-instance@, @SourceIds@ =
-- @mydbinstance1@, @mydbinstance2@ and @EventCategories@ = @Availability@,
-- @Backup@.
--
-- If you specify both the @SourceType@ and @SourceIds@, such as
-- @SourceType@ = @db-instance@ and @SourceIds@ = @myDBInstance1@, you are
-- notified of all the @db-instance@ events for the specified source. If
-- you specify a @SourceType@ but do not specify @SourceIds@, you receive
-- notice of the events for that source type for all your RDS sources. If
-- you don\'t specify either the SourceType or the @SourceIds@, you are
-- notified of events generated from all RDS sources belonging to your
-- customer account.
--
-- For more information about subscribing to an event for RDS DB engines,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Events.Subscribing.html Subscribing to Amazon RDS event notification>
-- in the /Amazon RDS User Guide/.
--
-- For more information about subscribing to an event for Aurora DB
-- engines, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_Events.Subscribing.html Subscribing to Amazon RDS event notification>
-- in the /Amazon Aurora User Guide/.
module Amazonka.RDS.CreateEventSubscription
  ( -- * Creating a Request
    CreateEventSubscription (..),
    newCreateEventSubscription,

    -- * Request Lenses
    createEventSubscription_enabled,
    createEventSubscription_eventCategories,
    createEventSubscription_sourceIds,
    createEventSubscription_sourceType,
    createEventSubscription_tags,
    createEventSubscription_subscriptionName,
    createEventSubscription_snsTopicArn,

    -- * Destructuring the Response
    CreateEventSubscriptionResponse (..),
    newCreateEventSubscriptionResponse,

    -- * Response Lenses
    createEventSubscriptionResponse_eventSubscription,
    createEventSubscriptionResponse_httpStatus,
  )
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.RDS.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newCreateEventSubscription' smart constructor.
data CreateEventSubscription = CreateEventSubscription'
  { -- | A value that indicates whether to activate the subscription. If the
    -- event notification subscription isn\'t activated, the subscription is
    -- created but not active.
    CreateEventSubscription -> Maybe Bool
enabled :: Prelude.Maybe Prelude.Bool,
    -- | A list of event categories for a particular source type (@SourceType@)
    -- that you want to subscribe to. You can see a list of the categories for
    -- a given source type in the \"Amazon RDS event categories and event
    -- messages\" section of the
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Events.Messages.html Amazon RDS User Guide>
    -- or the
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_Events.Messages.html Amazon Aurora User Guide>
    -- . You can also see this list by using the @DescribeEventCategories@
    -- operation.
    CreateEventSubscription -> Maybe [Text]
eventCategories :: Prelude.Maybe [Prelude.Text],
    -- | The list of identifiers of the event sources for which events are
    -- returned. If not specified, then all sources are included in the
    -- response. An identifier must begin with a letter and must contain only
    -- ASCII letters, digits, and hyphens. It can\'t end with a hyphen or
    -- contain two consecutive hyphens.
    --
    -- Constraints:
    --
    -- -   If @SourceIds@ are supplied, @SourceType@ must also be provided.
    --
    -- -   If the source type is a DB instance, a @DBInstanceIdentifier@ value
    --     must be supplied.
    --
    -- -   If the source type is a DB cluster, a @DBClusterIdentifier@ value
    --     must be supplied.
    --
    -- -   If the source type is a DB parameter group, a @DBParameterGroupName@
    --     value must be supplied.
    --
    -- -   If the source type is a DB security group, a @DBSecurityGroupName@
    --     value must be supplied.
    --
    -- -   If the source type is a DB snapshot, a @DBSnapshotIdentifier@ value
    --     must be supplied.
    --
    -- -   If the source type is a DB cluster snapshot, a
    --     @DBClusterSnapshotIdentifier@ value must be supplied.
    --
    -- -   If the source type is an RDS Proxy, a @DBProxyName@ value must be
    --     supplied.
    CreateEventSubscription -> Maybe [Text]
sourceIds :: Prelude.Maybe [Prelude.Text],
    -- | The type of source that is generating the events. For example, if you
    -- want to be notified of events generated by a DB instance, you set this
    -- parameter to @db-instance@. For RDS Proxy events, specify @db-proxy@. If
    -- this value isn\'t specified, all events are returned.
    --
    -- Valid values: @db-instance@ | @db-cluster@ | @db-parameter-group@ |
    -- @db-security-group@ | @db-snapshot@ | @db-cluster-snapshot@ | @db-proxy@
    CreateEventSubscription -> Maybe Text
sourceType :: Prelude.Maybe Prelude.Text,
    CreateEventSubscription -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the subscription.
    --
    -- Constraints: The name must be less than 255 characters.
    CreateEventSubscription -> Text
subscriptionName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the SNS topic created for event
    -- notification. The ARN is created by Amazon SNS when you create a topic
    -- and subscribe to it.
    CreateEventSubscription -> Text
snsTopicArn :: Prelude.Text
  }
  deriving (CreateEventSubscription -> CreateEventSubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEventSubscription -> CreateEventSubscription -> Bool
$c/= :: CreateEventSubscription -> CreateEventSubscription -> Bool
== :: CreateEventSubscription -> CreateEventSubscription -> Bool
$c== :: CreateEventSubscription -> CreateEventSubscription -> Bool
Prelude.Eq, ReadPrec [CreateEventSubscription]
ReadPrec CreateEventSubscription
Int -> ReadS CreateEventSubscription
ReadS [CreateEventSubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEventSubscription]
$creadListPrec :: ReadPrec [CreateEventSubscription]
readPrec :: ReadPrec CreateEventSubscription
$creadPrec :: ReadPrec CreateEventSubscription
readList :: ReadS [CreateEventSubscription]
$creadList :: ReadS [CreateEventSubscription]
readsPrec :: Int -> ReadS CreateEventSubscription
$creadsPrec :: Int -> ReadS CreateEventSubscription
Prelude.Read, Int -> CreateEventSubscription -> ShowS
[CreateEventSubscription] -> ShowS
CreateEventSubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEventSubscription] -> ShowS
$cshowList :: [CreateEventSubscription] -> ShowS
show :: CreateEventSubscription -> String
$cshow :: CreateEventSubscription -> String
showsPrec :: Int -> CreateEventSubscription -> ShowS
$cshowsPrec :: Int -> CreateEventSubscription -> ShowS
Prelude.Show, forall x. Rep CreateEventSubscription x -> CreateEventSubscription
forall x. CreateEventSubscription -> Rep CreateEventSubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateEventSubscription x -> CreateEventSubscription
$cfrom :: forall x. CreateEventSubscription -> Rep CreateEventSubscription x
Prelude.Generic)

-- |
-- Create a value of 'CreateEventSubscription' 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:
--
-- 'enabled', 'createEventSubscription_enabled' - A value that indicates whether to activate the subscription. If the
-- event notification subscription isn\'t activated, the subscription is
-- created but not active.
--
-- 'eventCategories', 'createEventSubscription_eventCategories' - A list of event categories for a particular source type (@SourceType@)
-- that you want to subscribe to. You can see a list of the categories for
-- a given source type in the \"Amazon RDS event categories and event
-- messages\" section of the
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Events.Messages.html Amazon RDS User Guide>
-- or the
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_Events.Messages.html Amazon Aurora User Guide>
-- . You can also see this list by using the @DescribeEventCategories@
-- operation.
--
-- 'sourceIds', 'createEventSubscription_sourceIds' - The list of identifiers of the event sources for which events are
-- returned. If not specified, then all sources are included in the
-- response. An identifier must begin with a letter and must contain only
-- ASCII letters, digits, and hyphens. It can\'t end with a hyphen or
-- contain two consecutive hyphens.
--
-- Constraints:
--
-- -   If @SourceIds@ are supplied, @SourceType@ must also be provided.
--
-- -   If the source type is a DB instance, a @DBInstanceIdentifier@ value
--     must be supplied.
--
-- -   If the source type is a DB cluster, a @DBClusterIdentifier@ value
--     must be supplied.
--
-- -   If the source type is a DB parameter group, a @DBParameterGroupName@
--     value must be supplied.
--
-- -   If the source type is a DB security group, a @DBSecurityGroupName@
--     value must be supplied.
--
-- -   If the source type is a DB snapshot, a @DBSnapshotIdentifier@ value
--     must be supplied.
--
-- -   If the source type is a DB cluster snapshot, a
--     @DBClusterSnapshotIdentifier@ value must be supplied.
--
-- -   If the source type is an RDS Proxy, a @DBProxyName@ value must be
--     supplied.
--
-- 'sourceType', 'createEventSubscription_sourceType' - The type of source that is generating the events. For example, if you
-- want to be notified of events generated by a DB instance, you set this
-- parameter to @db-instance@. For RDS Proxy events, specify @db-proxy@. If
-- this value isn\'t specified, all events are returned.
--
-- Valid values: @db-instance@ | @db-cluster@ | @db-parameter-group@ |
-- @db-security-group@ | @db-snapshot@ | @db-cluster-snapshot@ | @db-proxy@
--
-- 'tags', 'createEventSubscription_tags' - Undocumented member.
--
-- 'subscriptionName', 'createEventSubscription_subscriptionName' - The name of the subscription.
--
-- Constraints: The name must be less than 255 characters.
--
-- 'snsTopicArn', 'createEventSubscription_snsTopicArn' - The Amazon Resource Name (ARN) of the SNS topic created for event
-- notification. The ARN is created by Amazon SNS when you create a topic
-- and subscribe to it.
newCreateEventSubscription ::
  -- | 'subscriptionName'
  Prelude.Text ->
  -- | 'snsTopicArn'
  Prelude.Text ->
  CreateEventSubscription
newCreateEventSubscription :: Text -> Text -> CreateEventSubscription
newCreateEventSubscription
  Text
pSubscriptionName_
  Text
pSnsTopicArn_ =
    CreateEventSubscription'
      { $sel:enabled:CreateEventSubscription' :: Maybe Bool
enabled = forall a. Maybe a
Prelude.Nothing,
        $sel:eventCategories:CreateEventSubscription' :: Maybe [Text]
eventCategories = forall a. Maybe a
Prelude.Nothing,
        $sel:sourceIds:CreateEventSubscription' :: Maybe [Text]
sourceIds = forall a. Maybe a
Prelude.Nothing,
        $sel:sourceType:CreateEventSubscription' :: Maybe Text
sourceType = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateEventSubscription' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:subscriptionName:CreateEventSubscription' :: Text
subscriptionName = Text
pSubscriptionName_,
        $sel:snsTopicArn:CreateEventSubscription' :: Text
snsTopicArn = Text
pSnsTopicArn_
      }

-- | A value that indicates whether to activate the subscription. If the
-- event notification subscription isn\'t activated, the subscription is
-- created but not active.
createEventSubscription_enabled :: Lens.Lens' CreateEventSubscription (Prelude.Maybe Prelude.Bool)
createEventSubscription_enabled :: Lens' CreateEventSubscription (Maybe Bool)
createEventSubscription_enabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Maybe Bool
enabled :: Maybe Bool
$sel:enabled:CreateEventSubscription' :: CreateEventSubscription -> Maybe Bool
enabled} -> Maybe Bool
enabled) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Maybe Bool
a -> CreateEventSubscription
s {$sel:enabled:CreateEventSubscription' :: Maybe Bool
enabled = Maybe Bool
a} :: CreateEventSubscription)

-- | A list of event categories for a particular source type (@SourceType@)
-- that you want to subscribe to. You can see a list of the categories for
-- a given source type in the \"Amazon RDS event categories and event
-- messages\" section of the
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Events.Messages.html Amazon RDS User Guide>
-- or the
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_Events.Messages.html Amazon Aurora User Guide>
-- . You can also see this list by using the @DescribeEventCategories@
-- operation.
createEventSubscription_eventCategories :: Lens.Lens' CreateEventSubscription (Prelude.Maybe [Prelude.Text])
createEventSubscription_eventCategories :: Lens' CreateEventSubscription (Maybe [Text])
createEventSubscription_eventCategories = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Maybe [Text]
eventCategories :: Maybe [Text]
$sel:eventCategories:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
eventCategories} -> Maybe [Text]
eventCategories) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Maybe [Text]
a -> CreateEventSubscription
s {$sel:eventCategories:CreateEventSubscription' :: Maybe [Text]
eventCategories = Maybe [Text]
a} :: CreateEventSubscription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The list of identifiers of the event sources for which events are
-- returned. If not specified, then all sources are included in the
-- response. An identifier must begin with a letter and must contain only
-- ASCII letters, digits, and hyphens. It can\'t end with a hyphen or
-- contain two consecutive hyphens.
--
-- Constraints:
--
-- -   If @SourceIds@ are supplied, @SourceType@ must also be provided.
--
-- -   If the source type is a DB instance, a @DBInstanceIdentifier@ value
--     must be supplied.
--
-- -   If the source type is a DB cluster, a @DBClusterIdentifier@ value
--     must be supplied.
--
-- -   If the source type is a DB parameter group, a @DBParameterGroupName@
--     value must be supplied.
--
-- -   If the source type is a DB security group, a @DBSecurityGroupName@
--     value must be supplied.
--
-- -   If the source type is a DB snapshot, a @DBSnapshotIdentifier@ value
--     must be supplied.
--
-- -   If the source type is a DB cluster snapshot, a
--     @DBClusterSnapshotIdentifier@ value must be supplied.
--
-- -   If the source type is an RDS Proxy, a @DBProxyName@ value must be
--     supplied.
createEventSubscription_sourceIds :: Lens.Lens' CreateEventSubscription (Prelude.Maybe [Prelude.Text])
createEventSubscription_sourceIds :: Lens' CreateEventSubscription (Maybe [Text])
createEventSubscription_sourceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Maybe [Text]
sourceIds :: Maybe [Text]
$sel:sourceIds:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
sourceIds} -> Maybe [Text]
sourceIds) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Maybe [Text]
a -> CreateEventSubscription
s {$sel:sourceIds:CreateEventSubscription' :: Maybe [Text]
sourceIds = Maybe [Text]
a} :: CreateEventSubscription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The type of source that is generating the events. For example, if you
-- want to be notified of events generated by a DB instance, you set this
-- parameter to @db-instance@. For RDS Proxy events, specify @db-proxy@. If
-- this value isn\'t specified, all events are returned.
--
-- Valid values: @db-instance@ | @db-cluster@ | @db-parameter-group@ |
-- @db-security-group@ | @db-snapshot@ | @db-cluster-snapshot@ | @db-proxy@
createEventSubscription_sourceType :: Lens.Lens' CreateEventSubscription (Prelude.Maybe Prelude.Text)
createEventSubscription_sourceType :: Lens' CreateEventSubscription (Maybe Text)
createEventSubscription_sourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Maybe Text
sourceType :: Maybe Text
$sel:sourceType:CreateEventSubscription' :: CreateEventSubscription -> Maybe Text
sourceType} -> Maybe Text
sourceType) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Maybe Text
a -> CreateEventSubscription
s {$sel:sourceType:CreateEventSubscription' :: Maybe Text
sourceType = Maybe Text
a} :: CreateEventSubscription)

-- | Undocumented member.
createEventSubscription_tags :: Lens.Lens' CreateEventSubscription (Prelude.Maybe [Tag])
createEventSubscription_tags :: Lens' CreateEventSubscription (Maybe [Tag])
createEventSubscription_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Maybe [Tag]
a -> CreateEventSubscription
s {$sel:tags:CreateEventSubscription' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateEventSubscription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the subscription.
--
-- Constraints: The name must be less than 255 characters.
createEventSubscription_subscriptionName :: Lens.Lens' CreateEventSubscription Prelude.Text
createEventSubscription_subscriptionName :: Lens' CreateEventSubscription Text
createEventSubscription_subscriptionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Text
subscriptionName :: Text
$sel:subscriptionName:CreateEventSubscription' :: CreateEventSubscription -> Text
subscriptionName} -> Text
subscriptionName) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Text
a -> CreateEventSubscription
s {$sel:subscriptionName:CreateEventSubscription' :: Text
subscriptionName = Text
a} :: CreateEventSubscription)

-- | The Amazon Resource Name (ARN) of the SNS topic created for event
-- notification. The ARN is created by Amazon SNS when you create a topic
-- and subscribe to it.
createEventSubscription_snsTopicArn :: Lens.Lens' CreateEventSubscription Prelude.Text
createEventSubscription_snsTopicArn :: Lens' CreateEventSubscription Text
createEventSubscription_snsTopicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscription' {Text
snsTopicArn :: Text
$sel:snsTopicArn:CreateEventSubscription' :: CreateEventSubscription -> Text
snsTopicArn} -> Text
snsTopicArn) (\s :: CreateEventSubscription
s@CreateEventSubscription' {} Text
a -> CreateEventSubscription
s {$sel:snsTopicArn:CreateEventSubscription' :: Text
snsTopicArn = Text
a} :: CreateEventSubscription)

instance Core.AWSRequest CreateEventSubscription where
  type
    AWSResponse CreateEventSubscription =
      CreateEventSubscriptionResponse
  request :: (Service -> Service)
-> CreateEventSubscription -> Request CreateEventSubscription
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 CreateEventSubscription
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateEventSubscription)))
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
"CreateEventSubscriptionResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe EventSubscription -> Int -> CreateEventSubscriptionResponse
CreateEventSubscriptionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EventSubscription")
            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 CreateEventSubscription where
  hashWithSalt :: Int -> CreateEventSubscription -> Int
hashWithSalt Int
_salt CreateEventSubscription' {Maybe Bool
Maybe [Text]
Maybe [Tag]
Maybe Text
Text
snsTopicArn :: Text
subscriptionName :: Text
tags :: Maybe [Tag]
sourceType :: Maybe Text
sourceIds :: Maybe [Text]
eventCategories :: Maybe [Text]
enabled :: Maybe Bool
$sel:snsTopicArn:CreateEventSubscription' :: CreateEventSubscription -> Text
$sel:subscriptionName:CreateEventSubscription' :: CreateEventSubscription -> Text
$sel:tags:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Tag]
$sel:sourceType:CreateEventSubscription' :: CreateEventSubscription -> Maybe Text
$sel:sourceIds:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
$sel:eventCategories:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
$sel:enabled:CreateEventSubscription' :: CreateEventSubscription -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
eventCategories
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
sourceIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
subscriptionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snsTopicArn

instance Prelude.NFData CreateEventSubscription where
  rnf :: CreateEventSubscription -> ()
rnf CreateEventSubscription' {Maybe Bool
Maybe [Text]
Maybe [Tag]
Maybe Text
Text
snsTopicArn :: Text
subscriptionName :: Text
tags :: Maybe [Tag]
sourceType :: Maybe Text
sourceIds :: Maybe [Text]
eventCategories :: Maybe [Text]
enabled :: Maybe Bool
$sel:snsTopicArn:CreateEventSubscription' :: CreateEventSubscription -> Text
$sel:subscriptionName:CreateEventSubscription' :: CreateEventSubscription -> Text
$sel:tags:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Tag]
$sel:sourceType:CreateEventSubscription' :: CreateEventSubscription -> Maybe Text
$sel:sourceIds:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
$sel:eventCategories:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
$sel:enabled:CreateEventSubscription' :: CreateEventSubscription -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
eventCategories
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
sourceIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subscriptionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snsTopicArn

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

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

instance Data.ToQuery CreateEventSubscription where
  toQuery :: CreateEventSubscription -> QueryString
toQuery CreateEventSubscription' {Maybe Bool
Maybe [Text]
Maybe [Tag]
Maybe Text
Text
snsTopicArn :: Text
subscriptionName :: Text
tags :: Maybe [Tag]
sourceType :: Maybe Text
sourceIds :: Maybe [Text]
eventCategories :: Maybe [Text]
enabled :: Maybe Bool
$sel:snsTopicArn:CreateEventSubscription' :: CreateEventSubscription -> Text
$sel:subscriptionName:CreateEventSubscription' :: CreateEventSubscription -> Text
$sel:tags:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Tag]
$sel:sourceType:CreateEventSubscription' :: CreateEventSubscription -> Maybe Text
$sel:sourceIds:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
$sel:eventCategories:CreateEventSubscription' :: CreateEventSubscription -> Maybe [Text]
$sel:enabled:CreateEventSubscription' :: CreateEventSubscription -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateEventSubscription" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"Enabled" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
enabled,
        ByteString
"EventCategories"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"EventCategory"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
eventCategories
            ),
        ByteString
"SourceIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"SourceId" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
sourceIds),
        ByteString
"SourceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
sourceType,
        ByteString
"Tags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"SubscriptionName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
subscriptionName,
        ByteString
"SnsTopicArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snsTopicArn
      ]

-- | /See:/ 'newCreateEventSubscriptionResponse' smart constructor.
data CreateEventSubscriptionResponse = CreateEventSubscriptionResponse'
  { CreateEventSubscriptionResponse -> Maybe EventSubscription
eventSubscription :: Prelude.Maybe EventSubscription,
    -- | The response's http status code.
    CreateEventSubscriptionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateEventSubscriptionResponse
-> CreateEventSubscriptionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateEventSubscriptionResponse
-> CreateEventSubscriptionResponse -> Bool
$c/= :: CreateEventSubscriptionResponse
-> CreateEventSubscriptionResponse -> Bool
== :: CreateEventSubscriptionResponse
-> CreateEventSubscriptionResponse -> Bool
$c== :: CreateEventSubscriptionResponse
-> CreateEventSubscriptionResponse -> Bool
Prelude.Eq, ReadPrec [CreateEventSubscriptionResponse]
ReadPrec CreateEventSubscriptionResponse
Int -> ReadS CreateEventSubscriptionResponse
ReadS [CreateEventSubscriptionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateEventSubscriptionResponse]
$creadListPrec :: ReadPrec [CreateEventSubscriptionResponse]
readPrec :: ReadPrec CreateEventSubscriptionResponse
$creadPrec :: ReadPrec CreateEventSubscriptionResponse
readList :: ReadS [CreateEventSubscriptionResponse]
$creadList :: ReadS [CreateEventSubscriptionResponse]
readsPrec :: Int -> ReadS CreateEventSubscriptionResponse
$creadsPrec :: Int -> ReadS CreateEventSubscriptionResponse
Prelude.Read, Int -> CreateEventSubscriptionResponse -> ShowS
[CreateEventSubscriptionResponse] -> ShowS
CreateEventSubscriptionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateEventSubscriptionResponse] -> ShowS
$cshowList :: [CreateEventSubscriptionResponse] -> ShowS
show :: CreateEventSubscriptionResponse -> String
$cshow :: CreateEventSubscriptionResponse -> String
showsPrec :: Int -> CreateEventSubscriptionResponse -> ShowS
$cshowsPrec :: Int -> CreateEventSubscriptionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateEventSubscriptionResponse x
-> CreateEventSubscriptionResponse
forall x.
CreateEventSubscriptionResponse
-> Rep CreateEventSubscriptionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateEventSubscriptionResponse x
-> CreateEventSubscriptionResponse
$cfrom :: forall x.
CreateEventSubscriptionResponse
-> Rep CreateEventSubscriptionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateEventSubscriptionResponse' 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:
--
-- 'eventSubscription', 'createEventSubscriptionResponse_eventSubscription' - Undocumented member.
--
-- 'httpStatus', 'createEventSubscriptionResponse_httpStatus' - The response's http status code.
newCreateEventSubscriptionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateEventSubscriptionResponse
newCreateEventSubscriptionResponse :: Int -> CreateEventSubscriptionResponse
newCreateEventSubscriptionResponse Int
pHttpStatus_ =
  CreateEventSubscriptionResponse'
    { $sel:eventSubscription:CreateEventSubscriptionResponse' :: Maybe EventSubscription
eventSubscription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateEventSubscriptionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createEventSubscriptionResponse_eventSubscription :: Lens.Lens' CreateEventSubscriptionResponse (Prelude.Maybe EventSubscription)
createEventSubscriptionResponse_eventSubscription :: Lens' CreateEventSubscriptionResponse (Maybe EventSubscription)
createEventSubscriptionResponse_eventSubscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateEventSubscriptionResponse' {Maybe EventSubscription
eventSubscription :: Maybe EventSubscription
$sel:eventSubscription:CreateEventSubscriptionResponse' :: CreateEventSubscriptionResponse -> Maybe EventSubscription
eventSubscription} -> Maybe EventSubscription
eventSubscription) (\s :: CreateEventSubscriptionResponse
s@CreateEventSubscriptionResponse' {} Maybe EventSubscription
a -> CreateEventSubscriptionResponse
s {$sel:eventSubscription:CreateEventSubscriptionResponse' :: Maybe EventSubscription
eventSubscription = Maybe EventSubscription
a} :: CreateEventSubscriptionResponse)

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

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