{-# 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.RDSData.RollbackTransaction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Performs a rollback of a transaction. Rolling back a transaction cancels
-- its changes.
module Amazonka.RDSData.RollbackTransaction
  ( -- * Creating a Request
    RollbackTransaction (..),
    newRollbackTransaction,

    -- * Request Lenses
    rollbackTransaction_resourceArn,
    rollbackTransaction_secretArn,
    rollbackTransaction_transactionId,

    -- * Destructuring the Response
    RollbackTransactionResponse (..),
    newRollbackTransactionResponse,

    -- * Response Lenses
    rollbackTransactionResponse_transactionStatus,
    rollbackTransactionResponse_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.RDSData.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The request parameters represent the input of a request to perform a
-- rollback of a transaction.
--
-- /See:/ 'newRollbackTransaction' smart constructor.
data RollbackTransaction = RollbackTransaction'
  { -- | The Amazon Resource Name (ARN) of the Aurora Serverless DB cluster.
    RollbackTransaction -> Text
resourceArn :: Prelude.Text,
    -- | The name or ARN of the secret that enables access to the DB cluster.
    RollbackTransaction -> Text
secretArn :: Prelude.Text,
    -- | The identifier of the transaction to roll back.
    RollbackTransaction -> Text
transactionId :: Prelude.Text
  }
  deriving (RollbackTransaction -> RollbackTransaction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RollbackTransaction -> RollbackTransaction -> Bool
$c/= :: RollbackTransaction -> RollbackTransaction -> Bool
== :: RollbackTransaction -> RollbackTransaction -> Bool
$c== :: RollbackTransaction -> RollbackTransaction -> Bool
Prelude.Eq, ReadPrec [RollbackTransaction]
ReadPrec RollbackTransaction
Int -> ReadS RollbackTransaction
ReadS [RollbackTransaction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RollbackTransaction]
$creadListPrec :: ReadPrec [RollbackTransaction]
readPrec :: ReadPrec RollbackTransaction
$creadPrec :: ReadPrec RollbackTransaction
readList :: ReadS [RollbackTransaction]
$creadList :: ReadS [RollbackTransaction]
readsPrec :: Int -> ReadS RollbackTransaction
$creadsPrec :: Int -> ReadS RollbackTransaction
Prelude.Read, Int -> RollbackTransaction -> ShowS
[RollbackTransaction] -> ShowS
RollbackTransaction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RollbackTransaction] -> ShowS
$cshowList :: [RollbackTransaction] -> ShowS
show :: RollbackTransaction -> String
$cshow :: RollbackTransaction -> String
showsPrec :: Int -> RollbackTransaction -> ShowS
$cshowsPrec :: Int -> RollbackTransaction -> ShowS
Prelude.Show, forall x. Rep RollbackTransaction x -> RollbackTransaction
forall x. RollbackTransaction -> Rep RollbackTransaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RollbackTransaction x -> RollbackTransaction
$cfrom :: forall x. RollbackTransaction -> Rep RollbackTransaction x
Prelude.Generic)

-- |
-- Create a value of 'RollbackTransaction' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'resourceArn', 'rollbackTransaction_resourceArn' - The Amazon Resource Name (ARN) of the Aurora Serverless DB cluster.
--
-- 'secretArn', 'rollbackTransaction_secretArn' - The name or ARN of the secret that enables access to the DB cluster.
--
-- 'transactionId', 'rollbackTransaction_transactionId' - The identifier of the transaction to roll back.
newRollbackTransaction ::
  -- | 'resourceArn'
  Prelude.Text ->
  -- | 'secretArn'
  Prelude.Text ->
  -- | 'transactionId'
  Prelude.Text ->
  RollbackTransaction
newRollbackTransaction :: Text -> Text -> Text -> RollbackTransaction
newRollbackTransaction
  Text
pResourceArn_
  Text
pSecretArn_
  Text
pTransactionId_ =
    RollbackTransaction'
      { $sel:resourceArn:RollbackTransaction' :: Text
resourceArn = Text
pResourceArn_,
        $sel:secretArn:RollbackTransaction' :: Text
secretArn = Text
pSecretArn_,
        $sel:transactionId:RollbackTransaction' :: Text
transactionId = Text
pTransactionId_
      }

-- | The Amazon Resource Name (ARN) of the Aurora Serverless DB cluster.
rollbackTransaction_resourceArn :: Lens.Lens' RollbackTransaction Prelude.Text
rollbackTransaction_resourceArn :: Lens' RollbackTransaction Text
rollbackTransaction_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RollbackTransaction' {Text
resourceArn :: Text
$sel:resourceArn:RollbackTransaction' :: RollbackTransaction -> Text
resourceArn} -> Text
resourceArn) (\s :: RollbackTransaction
s@RollbackTransaction' {} Text
a -> RollbackTransaction
s {$sel:resourceArn:RollbackTransaction' :: Text
resourceArn = Text
a} :: RollbackTransaction)

-- | The name or ARN of the secret that enables access to the DB cluster.
rollbackTransaction_secretArn :: Lens.Lens' RollbackTransaction Prelude.Text
rollbackTransaction_secretArn :: Lens' RollbackTransaction Text
rollbackTransaction_secretArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RollbackTransaction' {Text
secretArn :: Text
$sel:secretArn:RollbackTransaction' :: RollbackTransaction -> Text
secretArn} -> Text
secretArn) (\s :: RollbackTransaction
s@RollbackTransaction' {} Text
a -> RollbackTransaction
s {$sel:secretArn:RollbackTransaction' :: Text
secretArn = Text
a} :: RollbackTransaction)

-- | The identifier of the transaction to roll back.
rollbackTransaction_transactionId :: Lens.Lens' RollbackTransaction Prelude.Text
rollbackTransaction_transactionId :: Lens' RollbackTransaction Text
rollbackTransaction_transactionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RollbackTransaction' {Text
transactionId :: Text
$sel:transactionId:RollbackTransaction' :: RollbackTransaction -> Text
transactionId} -> Text
transactionId) (\s :: RollbackTransaction
s@RollbackTransaction' {} Text
a -> RollbackTransaction
s {$sel:transactionId:RollbackTransaction' :: Text
transactionId = Text
a} :: RollbackTransaction)

instance Core.AWSRequest RollbackTransaction where
  type
    AWSResponse RollbackTransaction =
      RollbackTransactionResponse
  request :: (Service -> Service)
-> RollbackTransaction -> Request RollbackTransaction
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 RollbackTransaction
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RollbackTransaction)))
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 -> Int -> RollbackTransactionResponse
RollbackTransactionResponse'
            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
"transactionStatus")
            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 RollbackTransaction where
  hashWithSalt :: Int -> RollbackTransaction -> Int
hashWithSalt Int
_salt RollbackTransaction' {Text
transactionId :: Text
secretArn :: Text
resourceArn :: Text
$sel:transactionId:RollbackTransaction' :: RollbackTransaction -> Text
$sel:secretArn:RollbackTransaction' :: RollbackTransaction -> Text
$sel:resourceArn:RollbackTransaction' :: RollbackTransaction -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
secretArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
transactionId

instance Prelude.NFData RollbackTransaction where
  rnf :: RollbackTransaction -> ()
rnf RollbackTransaction' {Text
transactionId :: Text
secretArn :: Text
resourceArn :: Text
$sel:transactionId:RollbackTransaction' :: RollbackTransaction -> Text
$sel:secretArn:RollbackTransaction' :: RollbackTransaction -> Text
$sel:resourceArn:RollbackTransaction' :: RollbackTransaction -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
secretArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
transactionId

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

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

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

-- | The response elements represent the output of a request to perform a
-- rollback of a transaction.
--
-- /See:/ 'newRollbackTransactionResponse' smart constructor.
data RollbackTransactionResponse = RollbackTransactionResponse'
  { -- | The status of the rollback operation.
    RollbackTransactionResponse -> Maybe Text
transactionStatus :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    RollbackTransactionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (RollbackTransactionResponse -> RollbackTransactionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RollbackTransactionResponse -> RollbackTransactionResponse -> Bool
$c/= :: RollbackTransactionResponse -> RollbackTransactionResponse -> Bool
== :: RollbackTransactionResponse -> RollbackTransactionResponse -> Bool
$c== :: RollbackTransactionResponse -> RollbackTransactionResponse -> Bool
Prelude.Eq, ReadPrec [RollbackTransactionResponse]
ReadPrec RollbackTransactionResponse
Int -> ReadS RollbackTransactionResponse
ReadS [RollbackTransactionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RollbackTransactionResponse]
$creadListPrec :: ReadPrec [RollbackTransactionResponse]
readPrec :: ReadPrec RollbackTransactionResponse
$creadPrec :: ReadPrec RollbackTransactionResponse
readList :: ReadS [RollbackTransactionResponse]
$creadList :: ReadS [RollbackTransactionResponse]
readsPrec :: Int -> ReadS RollbackTransactionResponse
$creadsPrec :: Int -> ReadS RollbackTransactionResponse
Prelude.Read, Int -> RollbackTransactionResponse -> ShowS
[RollbackTransactionResponse] -> ShowS
RollbackTransactionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RollbackTransactionResponse] -> ShowS
$cshowList :: [RollbackTransactionResponse] -> ShowS
show :: RollbackTransactionResponse -> String
$cshow :: RollbackTransactionResponse -> String
showsPrec :: Int -> RollbackTransactionResponse -> ShowS
$cshowsPrec :: Int -> RollbackTransactionResponse -> ShowS
Prelude.Show, forall x.
Rep RollbackTransactionResponse x -> RollbackTransactionResponse
forall x.
RollbackTransactionResponse -> Rep RollbackTransactionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RollbackTransactionResponse x -> RollbackTransactionResponse
$cfrom :: forall x.
RollbackTransactionResponse -> Rep RollbackTransactionResponse x
Prelude.Generic)

-- |
-- Create a value of 'RollbackTransactionResponse' 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:
--
-- 'transactionStatus', 'rollbackTransactionResponse_transactionStatus' - The status of the rollback operation.
--
-- 'httpStatus', 'rollbackTransactionResponse_httpStatus' - The response's http status code.
newRollbackTransactionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  RollbackTransactionResponse
newRollbackTransactionResponse :: Int -> RollbackTransactionResponse
newRollbackTransactionResponse Int
pHttpStatus_ =
  RollbackTransactionResponse'
    { $sel:transactionStatus:RollbackTransactionResponse' :: Maybe Text
transactionStatus =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RollbackTransactionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The status of the rollback operation.
rollbackTransactionResponse_transactionStatus :: Lens.Lens' RollbackTransactionResponse (Prelude.Maybe Prelude.Text)
rollbackTransactionResponse_transactionStatus :: Lens' RollbackTransactionResponse (Maybe Text)
rollbackTransactionResponse_transactionStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RollbackTransactionResponse' {Maybe Text
transactionStatus :: Maybe Text
$sel:transactionStatus:RollbackTransactionResponse' :: RollbackTransactionResponse -> Maybe Text
transactionStatus} -> Maybe Text
transactionStatus) (\s :: RollbackTransactionResponse
s@RollbackTransactionResponse' {} Maybe Text
a -> RollbackTransactionResponse
s {$sel:transactionStatus:RollbackTransactionResponse' :: Maybe Text
transactionStatus = Maybe Text
a} :: RollbackTransactionResponse)

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

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