{-# 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.StopActivityStream
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops a database activity stream that was started using the Amazon Web
-- Services console, the @start-activity-stream@ CLI command, or the
-- @StartActivityStream@ action.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/DBActivityStreams.html Database Activity Streams>
-- in the /Amazon Aurora User Guide/.
module Amazonka.RDS.StopActivityStream
  ( -- * Creating a Request
    StopActivityStream (..),
    newStopActivityStream,

    -- * Request Lenses
    stopActivityStream_applyImmediately,
    stopActivityStream_resourceArn,

    -- * Destructuring the Response
    StopActivityStreamResponse (..),
    newStopActivityStreamResponse,

    -- * Response Lenses
    stopActivityStreamResponse_kinesisStreamName,
    stopActivityStreamResponse_kmsKeyId,
    stopActivityStreamResponse_status,
    stopActivityStreamResponse_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:/ 'newStopActivityStream' smart constructor.
data StopActivityStream = StopActivityStream'
  { -- | Specifies whether or not the database activity stream is to stop as soon
    -- as possible, regardless of the maintenance window for the database.
    StopActivityStream -> Maybe Bool
applyImmediately :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the DB cluster for the database
    -- activity stream. For example,
    -- @arn:aws:rds:us-east-1:12345667890:cluster:das-cluster@.
    StopActivityStream -> Text
resourceArn :: Prelude.Text
  }
  deriving (StopActivityStream -> StopActivityStream -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopActivityStream -> StopActivityStream -> Bool
$c/= :: StopActivityStream -> StopActivityStream -> Bool
== :: StopActivityStream -> StopActivityStream -> Bool
$c== :: StopActivityStream -> StopActivityStream -> Bool
Prelude.Eq, ReadPrec [StopActivityStream]
ReadPrec StopActivityStream
Int -> ReadS StopActivityStream
ReadS [StopActivityStream]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopActivityStream]
$creadListPrec :: ReadPrec [StopActivityStream]
readPrec :: ReadPrec StopActivityStream
$creadPrec :: ReadPrec StopActivityStream
readList :: ReadS [StopActivityStream]
$creadList :: ReadS [StopActivityStream]
readsPrec :: Int -> ReadS StopActivityStream
$creadsPrec :: Int -> ReadS StopActivityStream
Prelude.Read, Int -> StopActivityStream -> ShowS
[StopActivityStream] -> ShowS
StopActivityStream -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopActivityStream] -> ShowS
$cshowList :: [StopActivityStream] -> ShowS
show :: StopActivityStream -> String
$cshow :: StopActivityStream -> String
showsPrec :: Int -> StopActivityStream -> ShowS
$cshowsPrec :: Int -> StopActivityStream -> ShowS
Prelude.Show, forall x. Rep StopActivityStream x -> StopActivityStream
forall x. StopActivityStream -> Rep StopActivityStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopActivityStream x -> StopActivityStream
$cfrom :: forall x. StopActivityStream -> Rep StopActivityStream x
Prelude.Generic)

-- |
-- Create a value of 'StopActivityStream' 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:
--
-- 'applyImmediately', 'stopActivityStream_applyImmediately' - Specifies whether or not the database activity stream is to stop as soon
-- as possible, regardless of the maintenance window for the database.
--
-- 'resourceArn', 'stopActivityStream_resourceArn' - The Amazon Resource Name (ARN) of the DB cluster for the database
-- activity stream. For example,
-- @arn:aws:rds:us-east-1:12345667890:cluster:das-cluster@.
newStopActivityStream ::
  -- | 'resourceArn'
  Prelude.Text ->
  StopActivityStream
newStopActivityStream :: Text -> StopActivityStream
newStopActivityStream Text
pResourceArn_ =
  StopActivityStream'
    { $sel:applyImmediately:StopActivityStream' :: Maybe Bool
applyImmediately =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:StopActivityStream' :: Text
resourceArn = Text
pResourceArn_
    }

-- | Specifies whether or not the database activity stream is to stop as soon
-- as possible, regardless of the maintenance window for the database.
stopActivityStream_applyImmediately :: Lens.Lens' StopActivityStream (Prelude.Maybe Prelude.Bool)
stopActivityStream_applyImmediately :: Lens' StopActivityStream (Maybe Bool)
stopActivityStream_applyImmediately = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopActivityStream' {Maybe Bool
applyImmediately :: Maybe Bool
$sel:applyImmediately:StopActivityStream' :: StopActivityStream -> Maybe Bool
applyImmediately} -> Maybe Bool
applyImmediately) (\s :: StopActivityStream
s@StopActivityStream' {} Maybe Bool
a -> StopActivityStream
s {$sel:applyImmediately:StopActivityStream' :: Maybe Bool
applyImmediately = Maybe Bool
a} :: StopActivityStream)

-- | The Amazon Resource Name (ARN) of the DB cluster for the database
-- activity stream. For example,
-- @arn:aws:rds:us-east-1:12345667890:cluster:das-cluster@.
stopActivityStream_resourceArn :: Lens.Lens' StopActivityStream Prelude.Text
stopActivityStream_resourceArn :: Lens' StopActivityStream Text
stopActivityStream_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopActivityStream' {Text
resourceArn :: Text
$sel:resourceArn:StopActivityStream' :: StopActivityStream -> Text
resourceArn} -> Text
resourceArn) (\s :: StopActivityStream
s@StopActivityStream' {} Text
a -> StopActivityStream
s {$sel:resourceArn:StopActivityStream' :: Text
resourceArn = Text
a} :: StopActivityStream)

instance Core.AWSRequest StopActivityStream where
  type
    AWSResponse StopActivityStream =
      StopActivityStreamResponse
  request :: (Service -> Service)
-> StopActivityStream -> Request StopActivityStream
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 StopActivityStream
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StopActivityStream)))
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
"StopActivityStreamResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe Text
-> Maybe ActivityStreamStatus
-> Int
-> StopActivityStreamResponse
StopActivityStreamResponse'
            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
"KinesisStreamName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"KmsKeyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Status")
            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 StopActivityStream where
  hashWithSalt :: Int -> StopActivityStream -> Int
hashWithSalt Int
_salt StopActivityStream' {Maybe Bool
Text
resourceArn :: Text
applyImmediately :: Maybe Bool
$sel:resourceArn:StopActivityStream' :: StopActivityStream -> Text
$sel:applyImmediately:StopActivityStream' :: StopActivityStream -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
applyImmediately
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance Prelude.NFData StopActivityStream where
  rnf :: StopActivityStream -> ()
rnf StopActivityStream' {Maybe Bool
Text
resourceArn :: Text
applyImmediately :: Maybe Bool
$sel:resourceArn:StopActivityStream' :: StopActivityStream -> Text
$sel:applyImmediately:StopActivityStream' :: StopActivityStream -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
applyImmediately
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

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

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

instance Data.ToQuery StopActivityStream where
  toQuery :: StopActivityStream -> QueryString
toQuery StopActivityStream' {Maybe Bool
Text
resourceArn :: Text
applyImmediately :: Maybe Bool
$sel:resourceArn:StopActivityStream' :: StopActivityStream -> Text
$sel:applyImmediately:StopActivityStream' :: StopActivityStream -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"StopActivityStream" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"ApplyImmediately" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
applyImmediately,
        ByteString
"ResourceArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
resourceArn
      ]

-- | /See:/ 'newStopActivityStreamResponse' smart constructor.
data StopActivityStreamResponse = StopActivityStreamResponse'
  { -- | The name of the Amazon Kinesis data stream used for the database
    -- activity stream.
    StopActivityStreamResponse -> Maybe Text
kinesisStreamName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services KMS key identifier used for encrypting messages
    -- in the database activity stream.
    --
    -- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
    -- ARN, or alias name for the KMS key.
    StopActivityStreamResponse -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The status of the database activity stream.
    StopActivityStreamResponse -> Maybe ActivityStreamStatus
status :: Prelude.Maybe ActivityStreamStatus,
    -- | The response's http status code.
    StopActivityStreamResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopActivityStreamResponse -> StopActivityStreamResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopActivityStreamResponse -> StopActivityStreamResponse -> Bool
$c/= :: StopActivityStreamResponse -> StopActivityStreamResponse -> Bool
== :: StopActivityStreamResponse -> StopActivityStreamResponse -> Bool
$c== :: StopActivityStreamResponse -> StopActivityStreamResponse -> Bool
Prelude.Eq, ReadPrec [StopActivityStreamResponse]
ReadPrec StopActivityStreamResponse
Int -> ReadS StopActivityStreamResponse
ReadS [StopActivityStreamResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopActivityStreamResponse]
$creadListPrec :: ReadPrec [StopActivityStreamResponse]
readPrec :: ReadPrec StopActivityStreamResponse
$creadPrec :: ReadPrec StopActivityStreamResponse
readList :: ReadS [StopActivityStreamResponse]
$creadList :: ReadS [StopActivityStreamResponse]
readsPrec :: Int -> ReadS StopActivityStreamResponse
$creadsPrec :: Int -> ReadS StopActivityStreamResponse
Prelude.Read, Int -> StopActivityStreamResponse -> ShowS
[StopActivityStreamResponse] -> ShowS
StopActivityStreamResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopActivityStreamResponse] -> ShowS
$cshowList :: [StopActivityStreamResponse] -> ShowS
show :: StopActivityStreamResponse -> String
$cshow :: StopActivityStreamResponse -> String
showsPrec :: Int -> StopActivityStreamResponse -> ShowS
$cshowsPrec :: Int -> StopActivityStreamResponse -> ShowS
Prelude.Show, forall x.
Rep StopActivityStreamResponse x -> StopActivityStreamResponse
forall x.
StopActivityStreamResponse -> Rep StopActivityStreamResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopActivityStreamResponse x -> StopActivityStreamResponse
$cfrom :: forall x.
StopActivityStreamResponse -> Rep StopActivityStreamResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopActivityStreamResponse' 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:
--
-- 'kinesisStreamName', 'stopActivityStreamResponse_kinesisStreamName' - The name of the Amazon Kinesis data stream used for the database
-- activity stream.
--
-- 'kmsKeyId', 'stopActivityStreamResponse_kmsKeyId' - The Amazon Web Services KMS key identifier used for encrypting messages
-- in the database activity stream.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key.
--
-- 'status', 'stopActivityStreamResponse_status' - The status of the database activity stream.
--
-- 'httpStatus', 'stopActivityStreamResponse_httpStatus' - The response's http status code.
newStopActivityStreamResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopActivityStreamResponse
newStopActivityStreamResponse :: Int -> StopActivityStreamResponse
newStopActivityStreamResponse Int
pHttpStatus_ =
  StopActivityStreamResponse'
    { $sel:kinesisStreamName:StopActivityStreamResponse' :: Maybe Text
kinesisStreamName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:StopActivityStreamResponse' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:StopActivityStreamResponse' :: Maybe ActivityStreamStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopActivityStreamResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the Amazon Kinesis data stream used for the database
-- activity stream.
stopActivityStreamResponse_kinesisStreamName :: Lens.Lens' StopActivityStreamResponse (Prelude.Maybe Prelude.Text)
stopActivityStreamResponse_kinesisStreamName :: Lens' StopActivityStreamResponse (Maybe Text)
stopActivityStreamResponse_kinesisStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopActivityStreamResponse' {Maybe Text
kinesisStreamName :: Maybe Text
$sel:kinesisStreamName:StopActivityStreamResponse' :: StopActivityStreamResponse -> Maybe Text
kinesisStreamName} -> Maybe Text
kinesisStreamName) (\s :: StopActivityStreamResponse
s@StopActivityStreamResponse' {} Maybe Text
a -> StopActivityStreamResponse
s {$sel:kinesisStreamName:StopActivityStreamResponse' :: Maybe Text
kinesisStreamName = Maybe Text
a} :: StopActivityStreamResponse)

-- | The Amazon Web Services KMS key identifier used for encrypting messages
-- in the database activity stream.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key.
stopActivityStreamResponse_kmsKeyId :: Lens.Lens' StopActivityStreamResponse (Prelude.Maybe Prelude.Text)
stopActivityStreamResponse_kmsKeyId :: Lens' StopActivityStreamResponse (Maybe Text)
stopActivityStreamResponse_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopActivityStreamResponse' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:StopActivityStreamResponse' :: StopActivityStreamResponse -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: StopActivityStreamResponse
s@StopActivityStreamResponse' {} Maybe Text
a -> StopActivityStreamResponse
s {$sel:kmsKeyId:StopActivityStreamResponse' :: Maybe Text
kmsKeyId = Maybe Text
a} :: StopActivityStreamResponse)

-- | The status of the database activity stream.
stopActivityStreamResponse_status :: Lens.Lens' StopActivityStreamResponse (Prelude.Maybe ActivityStreamStatus)
stopActivityStreamResponse_status :: Lens' StopActivityStreamResponse (Maybe ActivityStreamStatus)
stopActivityStreamResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopActivityStreamResponse' {Maybe ActivityStreamStatus
status :: Maybe ActivityStreamStatus
$sel:status:StopActivityStreamResponse' :: StopActivityStreamResponse -> Maybe ActivityStreamStatus
status} -> Maybe ActivityStreamStatus
status) (\s :: StopActivityStreamResponse
s@StopActivityStreamResponse' {} Maybe ActivityStreamStatus
a -> StopActivityStreamResponse
s {$sel:status:StopActivityStreamResponse' :: Maybe ActivityStreamStatus
status = Maybe ActivityStreamStatus
a} :: StopActivityStreamResponse)

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

instance Prelude.NFData StopActivityStreamResponse where
  rnf :: StopActivityStreamResponse -> ()
rnf StopActivityStreamResponse' {Int
Maybe Text
Maybe ActivityStreamStatus
httpStatus :: Int
status :: Maybe ActivityStreamStatus
kmsKeyId :: Maybe Text
kinesisStreamName :: Maybe Text
$sel:httpStatus:StopActivityStreamResponse' :: StopActivityStreamResponse -> Int
$sel:status:StopActivityStreamResponse' :: StopActivityStreamResponse -> Maybe ActivityStreamStatus
$sel:kmsKeyId:StopActivityStreamResponse' :: StopActivityStreamResponse -> Maybe Text
$sel:kinesisStreamName:StopActivityStreamResponse' :: StopActivityStreamResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kinesisStreamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityStreamStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus