{-# 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.CommitTransaction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Ends a SQL transaction started with the @BeginTransaction@ operation and
-- commits the changes.
module Amazonka.RDSData.CommitTransaction
  ( -- * Creating a Request
    CommitTransaction (..),
    newCommitTransaction,

    -- * Request Lenses
    commitTransaction_resourceArn,
    commitTransaction_secretArn,
    commitTransaction_transactionId,

    -- * Destructuring the Response
    CommitTransactionResponse (..),
    newCommitTransactionResponse,

    -- * Response Lenses
    commitTransactionResponse_transactionStatus,
    commitTransactionResponse_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 commit transaction
-- request.
--
-- /See:/ 'newCommitTransaction' smart constructor.
data CommitTransaction = CommitTransaction'
  { -- | The Amazon Resource Name (ARN) of the Aurora Serverless DB cluster.
    CommitTransaction -> Text
resourceArn :: Prelude.Text,
    -- | The name or ARN of the secret that enables access to the DB cluster.
    CommitTransaction -> Text
secretArn :: Prelude.Text,
    -- | The identifier of the transaction to end and commit.
    CommitTransaction -> Text
transactionId :: Prelude.Text
  }
  deriving (CommitTransaction -> CommitTransaction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommitTransaction -> CommitTransaction -> Bool
$c/= :: CommitTransaction -> CommitTransaction -> Bool
== :: CommitTransaction -> CommitTransaction -> Bool
$c== :: CommitTransaction -> CommitTransaction -> Bool
Prelude.Eq, ReadPrec [CommitTransaction]
ReadPrec CommitTransaction
Int -> ReadS CommitTransaction
ReadS [CommitTransaction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommitTransaction]
$creadListPrec :: ReadPrec [CommitTransaction]
readPrec :: ReadPrec CommitTransaction
$creadPrec :: ReadPrec CommitTransaction
readList :: ReadS [CommitTransaction]
$creadList :: ReadS [CommitTransaction]
readsPrec :: Int -> ReadS CommitTransaction
$creadsPrec :: Int -> ReadS CommitTransaction
Prelude.Read, Int -> CommitTransaction -> ShowS
[CommitTransaction] -> ShowS
CommitTransaction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommitTransaction] -> ShowS
$cshowList :: [CommitTransaction] -> ShowS
show :: CommitTransaction -> String
$cshow :: CommitTransaction -> String
showsPrec :: Int -> CommitTransaction -> ShowS
$cshowsPrec :: Int -> CommitTransaction -> ShowS
Prelude.Show, forall x. Rep CommitTransaction x -> CommitTransaction
forall x. CommitTransaction -> Rep CommitTransaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CommitTransaction x -> CommitTransaction
$cfrom :: forall x. CommitTransaction -> Rep CommitTransaction x
Prelude.Generic)

-- |
-- Create a value of 'CommitTransaction' 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', 'commitTransaction_resourceArn' - The Amazon Resource Name (ARN) of the Aurora Serverless DB cluster.
--
-- 'secretArn', 'commitTransaction_secretArn' - The name or ARN of the secret that enables access to the DB cluster.
--
-- 'transactionId', 'commitTransaction_transactionId' - The identifier of the transaction to end and commit.
newCommitTransaction ::
  -- | 'resourceArn'
  Prelude.Text ->
  -- | 'secretArn'
  Prelude.Text ->
  -- | 'transactionId'
  Prelude.Text ->
  CommitTransaction
newCommitTransaction :: Text -> Text -> Text -> CommitTransaction
newCommitTransaction
  Text
pResourceArn_
  Text
pSecretArn_
  Text
pTransactionId_ =
    CommitTransaction'
      { $sel:resourceArn:CommitTransaction' :: Text
resourceArn = Text
pResourceArn_,
        $sel:secretArn:CommitTransaction' :: Text
secretArn = Text
pSecretArn_,
        $sel:transactionId:CommitTransaction' :: Text
transactionId = Text
pTransactionId_
      }

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

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

-- | The identifier of the transaction to end and commit.
commitTransaction_transactionId :: Lens.Lens' CommitTransaction Prelude.Text
commitTransaction_transactionId :: Lens' CommitTransaction Text
commitTransaction_transactionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CommitTransaction' {Text
transactionId :: Text
$sel:transactionId:CommitTransaction' :: CommitTransaction -> Text
transactionId} -> Text
transactionId) (\s :: CommitTransaction
s@CommitTransaction' {} Text
a -> CommitTransaction
s {$sel:transactionId:CommitTransaction' :: Text
transactionId = Text
a} :: CommitTransaction)

instance Core.AWSRequest CommitTransaction where
  type
    AWSResponse CommitTransaction =
      CommitTransactionResponse
  request :: (Service -> Service)
-> CommitTransaction -> Request CommitTransaction
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 CommitTransaction
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CommitTransaction)))
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 -> CommitTransactionResponse
CommitTransactionResponse'
            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 CommitTransaction where
  hashWithSalt :: Int -> CommitTransaction -> Int
hashWithSalt Int
_salt CommitTransaction' {Text
transactionId :: Text
secretArn :: Text
resourceArn :: Text
$sel:transactionId:CommitTransaction' :: CommitTransaction -> Text
$sel:secretArn:CommitTransaction' :: CommitTransaction -> Text
$sel:resourceArn:CommitTransaction' :: CommitTransaction -> 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 CommitTransaction where
  rnf :: CommitTransaction -> ()
rnf CommitTransaction' {Text
transactionId :: Text
secretArn :: Text
resourceArn :: Text
$sel:transactionId:CommitTransaction' :: CommitTransaction -> Text
$sel:secretArn:CommitTransaction' :: CommitTransaction -> Text
$sel:resourceArn:CommitTransaction' :: CommitTransaction -> 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 CommitTransaction where
  toHeaders :: CommitTransaction -> 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 CommitTransaction where
  toJSON :: CommitTransaction -> Value
toJSON CommitTransaction' {Text
transactionId :: Text
secretArn :: Text
resourceArn :: Text
$sel:transactionId:CommitTransaction' :: CommitTransaction -> Text
$sel:secretArn:CommitTransaction' :: CommitTransaction -> Text
$sel:resourceArn:CommitTransaction' :: CommitTransaction -> 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 CommitTransaction where
  toPath :: CommitTransaction -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/CommitTransaction"

instance Data.ToQuery CommitTransaction where
  toQuery :: CommitTransaction -> 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 commit transaction
-- request.
--
-- /See:/ 'newCommitTransactionResponse' smart constructor.
data CommitTransactionResponse = CommitTransactionResponse'
  { -- | The status of the commit operation.
    CommitTransactionResponse -> Maybe Text
transactionStatus :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CommitTransactionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CommitTransactionResponse -> CommitTransactionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommitTransactionResponse -> CommitTransactionResponse -> Bool
$c/= :: CommitTransactionResponse -> CommitTransactionResponse -> Bool
== :: CommitTransactionResponse -> CommitTransactionResponse -> Bool
$c== :: CommitTransactionResponse -> CommitTransactionResponse -> Bool
Prelude.Eq, ReadPrec [CommitTransactionResponse]
ReadPrec CommitTransactionResponse
Int -> ReadS CommitTransactionResponse
ReadS [CommitTransactionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommitTransactionResponse]
$creadListPrec :: ReadPrec [CommitTransactionResponse]
readPrec :: ReadPrec CommitTransactionResponse
$creadPrec :: ReadPrec CommitTransactionResponse
readList :: ReadS [CommitTransactionResponse]
$creadList :: ReadS [CommitTransactionResponse]
readsPrec :: Int -> ReadS CommitTransactionResponse
$creadsPrec :: Int -> ReadS CommitTransactionResponse
Prelude.Read, Int -> CommitTransactionResponse -> ShowS
[CommitTransactionResponse] -> ShowS
CommitTransactionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommitTransactionResponse] -> ShowS
$cshowList :: [CommitTransactionResponse] -> ShowS
show :: CommitTransactionResponse -> String
$cshow :: CommitTransactionResponse -> String
showsPrec :: Int -> CommitTransactionResponse -> ShowS
$cshowsPrec :: Int -> CommitTransactionResponse -> ShowS
Prelude.Show, forall x.
Rep CommitTransactionResponse x -> CommitTransactionResponse
forall x.
CommitTransactionResponse -> Rep CommitTransactionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CommitTransactionResponse x -> CommitTransactionResponse
$cfrom :: forall x.
CommitTransactionResponse -> Rep CommitTransactionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CommitTransactionResponse' 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', 'commitTransactionResponse_transactionStatus' - The status of the commit operation.
--
-- 'httpStatus', 'commitTransactionResponse_httpStatus' - The response's http status code.
newCommitTransactionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CommitTransactionResponse
newCommitTransactionResponse :: Int -> CommitTransactionResponse
newCommitTransactionResponse Int
pHttpStatus_ =
  CommitTransactionResponse'
    { $sel:transactionStatus:CommitTransactionResponse' :: Maybe Text
transactionStatus =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CommitTransactionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData CommitTransactionResponse where
  rnf :: CommitTransactionResponse -> ()
rnf CommitTransactionResponse' {Int
Maybe Text
httpStatus :: Int
transactionStatus :: Maybe Text
$sel:httpStatus:CommitTransactionResponse' :: CommitTransactionResponse -> Int
$sel:transactionStatus:CommitTransactionResponse' :: CommitTransactionResponse -> 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