{-# 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.Glue.UpdateTable
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates a metadata table in the Data Catalog.
module Amazonka.Glue.UpdateTable
  ( -- * Creating a Request
    UpdateTable (..),
    newUpdateTable,

    -- * Request Lenses
    updateTable_catalogId,
    updateTable_skipArchive,
    updateTable_transactionId,
    updateTable_versionId,
    updateTable_databaseName,
    updateTable_tableInput,

    -- * Destructuring the Response
    UpdateTableResponse (..),
    newUpdateTableResponse,

    -- * Response Lenses
    updateTableResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateTable' smart constructor.
data UpdateTable = UpdateTable'
  { -- | The ID of the Data Catalog where the table resides. If none is provided,
    -- the Amazon Web Services account ID is used by default.
    UpdateTable -> Maybe Text
catalogId :: Prelude.Maybe Prelude.Text,
    -- | By default, @UpdateTable@ always creates an archived version of the
    -- table before updating it. However, if @skipArchive@ is set to true,
    -- @UpdateTable@ does not create the archived version.
    UpdateTable -> Maybe Bool
skipArchive :: Prelude.Maybe Prelude.Bool,
    -- | The transaction ID at which to update the table contents.
    UpdateTable -> Maybe Text
transactionId :: Prelude.Maybe Prelude.Text,
    -- | The version ID at which to update the table contents.
    UpdateTable -> Maybe Text
versionId :: Prelude.Maybe Prelude.Text,
    -- | The name of the catalog database in which the table resides. For Hive
    -- compatibility, this name is entirely lowercase.
    UpdateTable -> Text
databaseName :: Prelude.Text,
    -- | An updated @TableInput@ object to define the metadata table in the
    -- catalog.
    UpdateTable -> TableInput
tableInput :: TableInput
  }
  deriving (UpdateTable -> UpdateTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateTable -> UpdateTable -> Bool
$c/= :: UpdateTable -> UpdateTable -> Bool
== :: UpdateTable -> UpdateTable -> Bool
$c== :: UpdateTable -> UpdateTable -> Bool
Prelude.Eq, ReadPrec [UpdateTable]
ReadPrec UpdateTable
Int -> ReadS UpdateTable
ReadS [UpdateTable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateTable]
$creadListPrec :: ReadPrec [UpdateTable]
readPrec :: ReadPrec UpdateTable
$creadPrec :: ReadPrec UpdateTable
readList :: ReadS [UpdateTable]
$creadList :: ReadS [UpdateTable]
readsPrec :: Int -> ReadS UpdateTable
$creadsPrec :: Int -> ReadS UpdateTable
Prelude.Read, Int -> UpdateTable -> ShowS
[UpdateTable] -> ShowS
UpdateTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateTable] -> ShowS
$cshowList :: [UpdateTable] -> ShowS
show :: UpdateTable -> String
$cshow :: UpdateTable -> String
showsPrec :: Int -> UpdateTable -> ShowS
$cshowsPrec :: Int -> UpdateTable -> ShowS
Prelude.Show, forall x. Rep UpdateTable x -> UpdateTable
forall x. UpdateTable -> Rep UpdateTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateTable x -> UpdateTable
$cfrom :: forall x. UpdateTable -> Rep UpdateTable x
Prelude.Generic)

-- |
-- Create a value of 'UpdateTable' 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:
--
-- 'catalogId', 'updateTable_catalogId' - The ID of the Data Catalog where the table resides. If none is provided,
-- the Amazon Web Services account ID is used by default.
--
-- 'skipArchive', 'updateTable_skipArchive' - By default, @UpdateTable@ always creates an archived version of the
-- table before updating it. However, if @skipArchive@ is set to true,
-- @UpdateTable@ does not create the archived version.
--
-- 'transactionId', 'updateTable_transactionId' - The transaction ID at which to update the table contents.
--
-- 'versionId', 'updateTable_versionId' - The version ID at which to update the table contents.
--
-- 'databaseName', 'updateTable_databaseName' - The name of the catalog database in which the table resides. For Hive
-- compatibility, this name is entirely lowercase.
--
-- 'tableInput', 'updateTable_tableInput' - An updated @TableInput@ object to define the metadata table in the
-- catalog.
newUpdateTable ::
  -- | 'databaseName'
  Prelude.Text ->
  -- | 'tableInput'
  TableInput ->
  UpdateTable
newUpdateTable :: Text -> TableInput -> UpdateTable
newUpdateTable Text
pDatabaseName_ TableInput
pTableInput_ =
  UpdateTable'
    { $sel:catalogId:UpdateTable' :: Maybe Text
catalogId = forall a. Maybe a
Prelude.Nothing,
      $sel:skipArchive:UpdateTable' :: Maybe Bool
skipArchive = forall a. Maybe a
Prelude.Nothing,
      $sel:transactionId:UpdateTable' :: Maybe Text
transactionId = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:UpdateTable' :: Maybe Text
versionId = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseName:UpdateTable' :: Text
databaseName = Text
pDatabaseName_,
      $sel:tableInput:UpdateTable' :: TableInput
tableInput = TableInput
pTableInput_
    }

-- | The ID of the Data Catalog where the table resides. If none is provided,
-- the Amazon Web Services account ID is used by default.
updateTable_catalogId :: Lens.Lens' UpdateTable (Prelude.Maybe Prelude.Text)
updateTable_catalogId :: Lens' UpdateTable (Maybe Text)
updateTable_catalogId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateTable' {Maybe Text
catalogId :: Maybe Text
$sel:catalogId:UpdateTable' :: UpdateTable -> Maybe Text
catalogId} -> Maybe Text
catalogId) (\s :: UpdateTable
s@UpdateTable' {} Maybe Text
a -> UpdateTable
s {$sel:catalogId:UpdateTable' :: Maybe Text
catalogId = Maybe Text
a} :: UpdateTable)

-- | By default, @UpdateTable@ always creates an archived version of the
-- table before updating it. However, if @skipArchive@ is set to true,
-- @UpdateTable@ does not create the archived version.
updateTable_skipArchive :: Lens.Lens' UpdateTable (Prelude.Maybe Prelude.Bool)
updateTable_skipArchive :: Lens' UpdateTable (Maybe Bool)
updateTable_skipArchive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateTable' {Maybe Bool
skipArchive :: Maybe Bool
$sel:skipArchive:UpdateTable' :: UpdateTable -> Maybe Bool
skipArchive} -> Maybe Bool
skipArchive) (\s :: UpdateTable
s@UpdateTable' {} Maybe Bool
a -> UpdateTable
s {$sel:skipArchive:UpdateTable' :: Maybe Bool
skipArchive = Maybe Bool
a} :: UpdateTable)

-- | The transaction ID at which to update the table contents.
updateTable_transactionId :: Lens.Lens' UpdateTable (Prelude.Maybe Prelude.Text)
updateTable_transactionId :: Lens' UpdateTable (Maybe Text)
updateTable_transactionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateTable' {Maybe Text
transactionId :: Maybe Text
$sel:transactionId:UpdateTable' :: UpdateTable -> Maybe Text
transactionId} -> Maybe Text
transactionId) (\s :: UpdateTable
s@UpdateTable' {} Maybe Text
a -> UpdateTable
s {$sel:transactionId:UpdateTable' :: Maybe Text
transactionId = Maybe Text
a} :: UpdateTable)

-- | The version ID at which to update the table contents.
updateTable_versionId :: Lens.Lens' UpdateTable (Prelude.Maybe Prelude.Text)
updateTable_versionId :: Lens' UpdateTable (Maybe Text)
updateTable_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateTable' {Maybe Text
versionId :: Maybe Text
$sel:versionId:UpdateTable' :: UpdateTable -> Maybe Text
versionId} -> Maybe Text
versionId) (\s :: UpdateTable
s@UpdateTable' {} Maybe Text
a -> UpdateTable
s {$sel:versionId:UpdateTable' :: Maybe Text
versionId = Maybe Text
a} :: UpdateTable)

-- | The name of the catalog database in which the table resides. For Hive
-- compatibility, this name is entirely lowercase.
updateTable_databaseName :: Lens.Lens' UpdateTable Prelude.Text
updateTable_databaseName :: Lens' UpdateTable Text
updateTable_databaseName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateTable' {Text
databaseName :: Text
$sel:databaseName:UpdateTable' :: UpdateTable -> Text
databaseName} -> Text
databaseName) (\s :: UpdateTable
s@UpdateTable' {} Text
a -> UpdateTable
s {$sel:databaseName:UpdateTable' :: Text
databaseName = Text
a} :: UpdateTable)

-- | An updated @TableInput@ object to define the metadata table in the
-- catalog.
updateTable_tableInput :: Lens.Lens' UpdateTable TableInput
updateTable_tableInput :: Lens' UpdateTable TableInput
updateTable_tableInput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateTable' {TableInput
tableInput :: TableInput
$sel:tableInput:UpdateTable' :: UpdateTable -> TableInput
tableInput} -> TableInput
tableInput) (\s :: UpdateTable
s@UpdateTable' {} TableInput
a -> UpdateTable
s {$sel:tableInput:UpdateTable' :: TableInput
tableInput = TableInput
a} :: UpdateTable)

instance Core.AWSRequest UpdateTable where
  type AWSResponse UpdateTable = UpdateTableResponse
  request :: (Service -> Service) -> UpdateTable -> Request UpdateTable
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 UpdateTable
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateTable)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> UpdateTableResponse
UpdateTableResponse'
            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))
      )

instance Prelude.Hashable UpdateTable where
  hashWithSalt :: Int -> UpdateTable -> Int
hashWithSalt Int
_salt UpdateTable' {Maybe Bool
Maybe Text
Text
TableInput
tableInput :: TableInput
databaseName :: Text
versionId :: Maybe Text
transactionId :: Maybe Text
skipArchive :: Maybe Bool
catalogId :: Maybe Text
$sel:tableInput:UpdateTable' :: UpdateTable -> TableInput
$sel:databaseName:UpdateTable' :: UpdateTable -> Text
$sel:versionId:UpdateTable' :: UpdateTable -> Maybe Text
$sel:transactionId:UpdateTable' :: UpdateTable -> Maybe Text
$sel:skipArchive:UpdateTable' :: UpdateTable -> Maybe Bool
$sel:catalogId:UpdateTable' :: UpdateTable -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
catalogId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
skipArchive
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transactionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
versionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
databaseName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TableInput
tableInput

instance Prelude.NFData UpdateTable where
  rnf :: UpdateTable -> ()
rnf UpdateTable' {Maybe Bool
Maybe Text
Text
TableInput
tableInput :: TableInput
databaseName :: Text
versionId :: Maybe Text
transactionId :: Maybe Text
skipArchive :: Maybe Bool
catalogId :: Maybe Text
$sel:tableInput:UpdateTable' :: UpdateTable -> TableInput
$sel:databaseName:UpdateTable' :: UpdateTable -> Text
$sel:versionId:UpdateTable' :: UpdateTable -> Maybe Text
$sel:transactionId:UpdateTable' :: UpdateTable -> Maybe Text
$sel:skipArchive:UpdateTable' :: UpdateTable -> Maybe Bool
$sel:catalogId:UpdateTable' :: UpdateTable -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
catalogId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
skipArchive
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transactionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
versionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
databaseName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TableInput
tableInput

instance Data.ToHeaders UpdateTable where
  toHeaders :: UpdateTable -> 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
"AWSGlue.UpdateTable" :: 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 UpdateTable where
  toJSON :: UpdateTable -> Value
toJSON UpdateTable' {Maybe Bool
Maybe Text
Text
TableInput
tableInput :: TableInput
databaseName :: Text
versionId :: Maybe Text
transactionId :: Maybe Text
skipArchive :: Maybe Bool
catalogId :: Maybe Text
$sel:tableInput:UpdateTable' :: UpdateTable -> TableInput
$sel:databaseName:UpdateTable' :: UpdateTable -> Text
$sel:versionId:UpdateTable' :: UpdateTable -> Maybe Text
$sel:transactionId:UpdateTable' :: UpdateTable -> Maybe Text
$sel:skipArchive:UpdateTable' :: UpdateTable -> Maybe Bool
$sel:catalogId:UpdateTable' :: UpdateTable -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CatalogId" 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 Text
catalogId,
            (Key
"SkipArchive" 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 Bool
skipArchive,
            (Key
"TransactionId" 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 Text
transactionId,
            (Key
"VersionId" 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 Text
versionId,
            forall a. a -> Maybe a
Prelude.Just (Key
"DatabaseName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
databaseName),
            forall a. a -> Maybe a
Prelude.Just (Key
"TableInput" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TableInput
tableInput)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateTableResponse' 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', 'updateTableResponse_httpStatus' - The response's http status code.
newUpdateTableResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateTableResponse
newUpdateTableResponse :: Int -> UpdateTableResponse
newUpdateTableResponse Int
pHttpStatus_ =
  UpdateTableResponse' {$sel:httpStatus:UpdateTableResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData UpdateTableResponse where
  rnf :: UpdateTableResponse -> ()
rnf UpdateTableResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateTableResponse' :: UpdateTableResponse -> Int
..} = forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus