{-# 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.CostExplorer.CreateAnomalySubscription
-- 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 an alert subscription to a cost anomaly detection monitor. You can
-- use each subscription to define subscribers with email or SNS
-- notifications. Email subscribers can set an absolute or percentage
-- threshold and a time frequency for receiving notifications.
module Amazonka.CostExplorer.CreateAnomalySubscription
  ( -- * Creating a Request
    CreateAnomalySubscription (..),
    newCreateAnomalySubscription,

    -- * Request Lenses
    createAnomalySubscription_resourceTags,
    createAnomalySubscription_anomalySubscription,

    -- * Destructuring the Response
    CreateAnomalySubscriptionResponse (..),
    newCreateAnomalySubscriptionResponse,

    -- * Response Lenses
    createAnomalySubscriptionResponse_httpStatus,
    createAnomalySubscriptionResponse_subscriptionArn,
  )
where

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

-- | /See:/ 'newCreateAnomalySubscription' smart constructor.
data CreateAnomalySubscription = CreateAnomalySubscription'
  { -- | An optional list of tags to associate with the specified
    -- <https://docs.aws.amazon.com/aws-cost-management/latest/APIReference/API_AnomalySubscription.html AnomalySubscription>
    -- . You can use resource tags to control access to your @subscription@
    -- using IAM policies.
    --
    -- Each tag consists of a key and a value, and each key must be unique for
    -- the resource. The following restrictions apply to resource tags:
    --
    -- -   Although the maximum number of array members is 200, you can assign
    --     a maximum of 50 user-tags to one resource. The remaining are
    --     reserved for Amazon Web Services use
    --
    -- -   The maximum length of a key is 128 characters
    --
    -- -   The maximum length of a value is 256 characters
    --
    -- -   Keys and values can only contain alphanumeric characters, spaces,
    --     and any of the following: @_.:\/=+\@-@
    --
    -- -   Keys and values are case sensitive
    --
    -- -   Keys and values are trimmed for any leading or trailing whitespaces
    --
    -- -   Don’t use @aws:@ as a prefix for your keys. This prefix is reserved
    --     for Amazon Web Services use
    CreateAnomalySubscription -> Maybe [ResourceTag]
resourceTags :: Prelude.Maybe [ResourceTag],
    -- | The cost anomaly subscription object that you want to create.
    CreateAnomalySubscription -> AnomalySubscription
anomalySubscription :: AnomalySubscription
  }
  deriving (CreateAnomalySubscription -> CreateAnomalySubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAnomalySubscription -> CreateAnomalySubscription -> Bool
$c/= :: CreateAnomalySubscription -> CreateAnomalySubscription -> Bool
== :: CreateAnomalySubscription -> CreateAnomalySubscription -> Bool
$c== :: CreateAnomalySubscription -> CreateAnomalySubscription -> Bool
Prelude.Eq, ReadPrec [CreateAnomalySubscription]
ReadPrec CreateAnomalySubscription
Int -> ReadS CreateAnomalySubscription
ReadS [CreateAnomalySubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAnomalySubscription]
$creadListPrec :: ReadPrec [CreateAnomalySubscription]
readPrec :: ReadPrec CreateAnomalySubscription
$creadPrec :: ReadPrec CreateAnomalySubscription
readList :: ReadS [CreateAnomalySubscription]
$creadList :: ReadS [CreateAnomalySubscription]
readsPrec :: Int -> ReadS CreateAnomalySubscription
$creadsPrec :: Int -> ReadS CreateAnomalySubscription
Prelude.Read, Int -> CreateAnomalySubscription -> ShowS
[CreateAnomalySubscription] -> ShowS
CreateAnomalySubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAnomalySubscription] -> ShowS
$cshowList :: [CreateAnomalySubscription] -> ShowS
show :: CreateAnomalySubscription -> String
$cshow :: CreateAnomalySubscription -> String
showsPrec :: Int -> CreateAnomalySubscription -> ShowS
$cshowsPrec :: Int -> CreateAnomalySubscription -> ShowS
Prelude.Show, forall x.
Rep CreateAnomalySubscription x -> CreateAnomalySubscription
forall x.
CreateAnomalySubscription -> Rep CreateAnomalySubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateAnomalySubscription x -> CreateAnomalySubscription
$cfrom :: forall x.
CreateAnomalySubscription -> Rep CreateAnomalySubscription x
Prelude.Generic)

-- |
-- Create a value of 'CreateAnomalySubscription' 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:
--
-- 'resourceTags', 'createAnomalySubscription_resourceTags' - An optional list of tags to associate with the specified
-- <https://docs.aws.amazon.com/aws-cost-management/latest/APIReference/API_AnomalySubscription.html AnomalySubscription>
-- . You can use resource tags to control access to your @subscription@
-- using IAM policies.
--
-- Each tag consists of a key and a value, and each key must be unique for
-- the resource. The following restrictions apply to resource tags:
--
-- -   Although the maximum number of array members is 200, you can assign
--     a maximum of 50 user-tags to one resource. The remaining are
--     reserved for Amazon Web Services use
--
-- -   The maximum length of a key is 128 characters
--
-- -   The maximum length of a value is 256 characters
--
-- -   Keys and values can only contain alphanumeric characters, spaces,
--     and any of the following: @_.:\/=+\@-@
--
-- -   Keys and values are case sensitive
--
-- -   Keys and values are trimmed for any leading or trailing whitespaces
--
-- -   Don’t use @aws:@ as a prefix for your keys. This prefix is reserved
--     for Amazon Web Services use
--
-- 'anomalySubscription', 'createAnomalySubscription_anomalySubscription' - The cost anomaly subscription object that you want to create.
newCreateAnomalySubscription ::
  -- | 'anomalySubscription'
  AnomalySubscription ->
  CreateAnomalySubscription
newCreateAnomalySubscription :: AnomalySubscription -> CreateAnomalySubscription
newCreateAnomalySubscription AnomalySubscription
pAnomalySubscription_ =
  CreateAnomalySubscription'
    { $sel:resourceTags:CreateAnomalySubscription' :: Maybe [ResourceTag]
resourceTags =
        forall a. Maybe a
Prelude.Nothing,
      $sel:anomalySubscription:CreateAnomalySubscription' :: AnomalySubscription
anomalySubscription = AnomalySubscription
pAnomalySubscription_
    }

-- | An optional list of tags to associate with the specified
-- <https://docs.aws.amazon.com/aws-cost-management/latest/APIReference/API_AnomalySubscription.html AnomalySubscription>
-- . You can use resource tags to control access to your @subscription@
-- using IAM policies.
--
-- Each tag consists of a key and a value, and each key must be unique for
-- the resource. The following restrictions apply to resource tags:
--
-- -   Although the maximum number of array members is 200, you can assign
--     a maximum of 50 user-tags to one resource. The remaining are
--     reserved for Amazon Web Services use
--
-- -   The maximum length of a key is 128 characters
--
-- -   The maximum length of a value is 256 characters
--
-- -   Keys and values can only contain alphanumeric characters, spaces,
--     and any of the following: @_.:\/=+\@-@
--
-- -   Keys and values are case sensitive
--
-- -   Keys and values are trimmed for any leading or trailing whitespaces
--
-- -   Don’t use @aws:@ as a prefix for your keys. This prefix is reserved
--     for Amazon Web Services use
createAnomalySubscription_resourceTags :: Lens.Lens' CreateAnomalySubscription (Prelude.Maybe [ResourceTag])
createAnomalySubscription_resourceTags :: Lens' CreateAnomalySubscription (Maybe [ResourceTag])
createAnomalySubscription_resourceTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAnomalySubscription' {Maybe [ResourceTag]
resourceTags :: Maybe [ResourceTag]
$sel:resourceTags:CreateAnomalySubscription' :: CreateAnomalySubscription -> Maybe [ResourceTag]
resourceTags} -> Maybe [ResourceTag]
resourceTags) (\s :: CreateAnomalySubscription
s@CreateAnomalySubscription' {} Maybe [ResourceTag]
a -> CreateAnomalySubscription
s {$sel:resourceTags:CreateAnomalySubscription' :: Maybe [ResourceTag]
resourceTags = Maybe [ResourceTag]
a} :: CreateAnomalySubscription) 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 cost anomaly subscription object that you want to create.
createAnomalySubscription_anomalySubscription :: Lens.Lens' CreateAnomalySubscription AnomalySubscription
createAnomalySubscription_anomalySubscription :: Lens' CreateAnomalySubscription AnomalySubscription
createAnomalySubscription_anomalySubscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAnomalySubscription' {AnomalySubscription
anomalySubscription :: AnomalySubscription
$sel:anomalySubscription:CreateAnomalySubscription' :: CreateAnomalySubscription -> AnomalySubscription
anomalySubscription} -> AnomalySubscription
anomalySubscription) (\s :: CreateAnomalySubscription
s@CreateAnomalySubscription' {} AnomalySubscription
a -> CreateAnomalySubscription
s {$sel:anomalySubscription:CreateAnomalySubscription' :: AnomalySubscription
anomalySubscription = AnomalySubscription
a} :: CreateAnomalySubscription)

instance Core.AWSRequest CreateAnomalySubscription where
  type
    AWSResponse CreateAnomalySubscription =
      CreateAnomalySubscriptionResponse
  request :: (Service -> Service)
-> CreateAnomalySubscription -> Request CreateAnomalySubscription
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 CreateAnomalySubscription
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateAnomalySubscription)))
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 ->
          Int -> Text -> CreateAnomalySubscriptionResponse
CreateAnomalySubscriptionResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"SubscriptionArn")
      )

instance Prelude.Hashable CreateAnomalySubscription where
  hashWithSalt :: Int -> CreateAnomalySubscription -> Int
hashWithSalt Int
_salt CreateAnomalySubscription' {Maybe [ResourceTag]
AnomalySubscription
anomalySubscription :: AnomalySubscription
resourceTags :: Maybe [ResourceTag]
$sel:anomalySubscription:CreateAnomalySubscription' :: CreateAnomalySubscription -> AnomalySubscription
$sel:resourceTags:CreateAnomalySubscription' :: CreateAnomalySubscription -> Maybe [ResourceTag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ResourceTag]
resourceTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AnomalySubscription
anomalySubscription

instance Prelude.NFData CreateAnomalySubscription where
  rnf :: CreateAnomalySubscription -> ()
rnf CreateAnomalySubscription' {Maybe [ResourceTag]
AnomalySubscription
anomalySubscription :: AnomalySubscription
resourceTags :: Maybe [ResourceTag]
$sel:anomalySubscription:CreateAnomalySubscription' :: CreateAnomalySubscription -> AnomalySubscription
$sel:resourceTags:CreateAnomalySubscription' :: CreateAnomalySubscription -> Maybe [ResourceTag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ResourceTag]
resourceTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AnomalySubscription
anomalySubscription

instance Data.ToHeaders CreateAnomalySubscription where
  toHeaders :: CreateAnomalySubscription -> 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
"AWSInsightsIndexService.CreateAnomalySubscription" ::
                          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 CreateAnomalySubscription where
  toJSON :: CreateAnomalySubscription -> Value
toJSON CreateAnomalySubscription' {Maybe [ResourceTag]
AnomalySubscription
anomalySubscription :: AnomalySubscription
resourceTags :: Maybe [ResourceTag]
$sel:anomalySubscription:CreateAnomalySubscription' :: CreateAnomalySubscription -> AnomalySubscription
$sel:resourceTags:CreateAnomalySubscription' :: CreateAnomalySubscription -> Maybe [ResourceTag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ResourceTags" 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 [ResourceTag]
resourceTags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AnomalySubscription" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AnomalySubscription
anomalySubscription)
          ]
      )

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

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

-- | /See:/ 'newCreateAnomalySubscriptionResponse' smart constructor.
data CreateAnomalySubscriptionResponse = CreateAnomalySubscriptionResponse'
  { -- | The response's http status code.
    CreateAnomalySubscriptionResponse -> Int
httpStatus :: Prelude.Int,
    -- | The unique identifier of your newly created cost anomaly subscription.
    CreateAnomalySubscriptionResponse -> Text
subscriptionArn :: Prelude.Text
  }
  deriving (CreateAnomalySubscriptionResponse
-> CreateAnomalySubscriptionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAnomalySubscriptionResponse
-> CreateAnomalySubscriptionResponse -> Bool
$c/= :: CreateAnomalySubscriptionResponse
-> CreateAnomalySubscriptionResponse -> Bool
== :: CreateAnomalySubscriptionResponse
-> CreateAnomalySubscriptionResponse -> Bool
$c== :: CreateAnomalySubscriptionResponse
-> CreateAnomalySubscriptionResponse -> Bool
Prelude.Eq, ReadPrec [CreateAnomalySubscriptionResponse]
ReadPrec CreateAnomalySubscriptionResponse
Int -> ReadS CreateAnomalySubscriptionResponse
ReadS [CreateAnomalySubscriptionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAnomalySubscriptionResponse]
$creadListPrec :: ReadPrec [CreateAnomalySubscriptionResponse]
readPrec :: ReadPrec CreateAnomalySubscriptionResponse
$creadPrec :: ReadPrec CreateAnomalySubscriptionResponse
readList :: ReadS [CreateAnomalySubscriptionResponse]
$creadList :: ReadS [CreateAnomalySubscriptionResponse]
readsPrec :: Int -> ReadS CreateAnomalySubscriptionResponse
$creadsPrec :: Int -> ReadS CreateAnomalySubscriptionResponse
Prelude.Read, Int -> CreateAnomalySubscriptionResponse -> ShowS
[CreateAnomalySubscriptionResponse] -> ShowS
CreateAnomalySubscriptionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAnomalySubscriptionResponse] -> ShowS
$cshowList :: [CreateAnomalySubscriptionResponse] -> ShowS
show :: CreateAnomalySubscriptionResponse -> String
$cshow :: CreateAnomalySubscriptionResponse -> String
showsPrec :: Int -> CreateAnomalySubscriptionResponse -> ShowS
$cshowsPrec :: Int -> CreateAnomalySubscriptionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateAnomalySubscriptionResponse x
-> CreateAnomalySubscriptionResponse
forall x.
CreateAnomalySubscriptionResponse
-> Rep CreateAnomalySubscriptionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateAnomalySubscriptionResponse x
-> CreateAnomalySubscriptionResponse
$cfrom :: forall x.
CreateAnomalySubscriptionResponse
-> Rep CreateAnomalySubscriptionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateAnomalySubscriptionResponse' 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:
--
-- 'httpStatus', 'createAnomalySubscriptionResponse_httpStatus' - The response's http status code.
--
-- 'subscriptionArn', 'createAnomalySubscriptionResponse_subscriptionArn' - The unique identifier of your newly created cost anomaly subscription.
newCreateAnomalySubscriptionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'subscriptionArn'
  Prelude.Text ->
  CreateAnomalySubscriptionResponse
newCreateAnomalySubscriptionResponse :: Int -> Text -> CreateAnomalySubscriptionResponse
newCreateAnomalySubscriptionResponse
  Int
pHttpStatus_
  Text
pSubscriptionArn_ =
    CreateAnomalySubscriptionResponse'
      { $sel:httpStatus:CreateAnomalySubscriptionResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:subscriptionArn:CreateAnomalySubscriptionResponse' :: Text
subscriptionArn = Text
pSubscriptionArn_
      }

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

-- | The unique identifier of your newly created cost anomaly subscription.
createAnomalySubscriptionResponse_subscriptionArn :: Lens.Lens' CreateAnomalySubscriptionResponse Prelude.Text
createAnomalySubscriptionResponse_subscriptionArn :: Lens' CreateAnomalySubscriptionResponse Text
createAnomalySubscriptionResponse_subscriptionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAnomalySubscriptionResponse' {Text
subscriptionArn :: Text
$sel:subscriptionArn:CreateAnomalySubscriptionResponse' :: CreateAnomalySubscriptionResponse -> Text
subscriptionArn} -> Text
subscriptionArn) (\s :: CreateAnomalySubscriptionResponse
s@CreateAnomalySubscriptionResponse' {} Text
a -> CreateAnomalySubscriptionResponse
s {$sel:subscriptionArn:CreateAnomalySubscriptionResponse' :: Text
subscriptionArn = Text
a} :: CreateAnomalySubscriptionResponse)

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