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

    -- * Request Lenses
    createTable_catalogId,
    createTable_partitionIndexes,
    createTable_transactionId,
    createTable_databaseName,
    createTable_tableInput,

    -- * Destructuring the Response
    CreateTableResponse (..),
    newCreateTableResponse,

    -- * Response Lenses
    createTableResponse_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:/ 'newCreateTable' smart constructor.
data CreateTable = CreateTable'
  { -- | The ID of the Data Catalog in which to create the @Table@. If none is
    -- supplied, the Amazon Web Services account ID is used by default.
    CreateTable -> Maybe Text
catalogId :: Prelude.Maybe Prelude.Text,
    -- | A list of partition indexes, @PartitionIndex@ structures, to create in
    -- the table.
    CreateTable -> Maybe [PartitionIndex]
partitionIndexes :: Prelude.Maybe [PartitionIndex],
    -- | The ID of the transaction.
    CreateTable -> Maybe Text
transactionId :: Prelude.Maybe Prelude.Text,
    -- | The catalog database in which to create the new table. For Hive
    -- compatibility, this name is entirely lowercase.
    CreateTable -> Text
databaseName :: Prelude.Text,
    -- | The @TableInput@ object that defines the metadata table to create in the
    -- catalog.
    CreateTable -> TableInput
tableInput :: TableInput
  }
  deriving (CreateTable -> CreateTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateTable -> CreateTable -> Bool
$c/= :: CreateTable -> CreateTable -> Bool
== :: CreateTable -> CreateTable -> Bool
$c== :: CreateTable -> CreateTable -> Bool
Prelude.Eq, ReadPrec [CreateTable]
ReadPrec CreateTable
Int -> ReadS CreateTable
ReadS [CreateTable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateTable]
$creadListPrec :: ReadPrec [CreateTable]
readPrec :: ReadPrec CreateTable
$creadPrec :: ReadPrec CreateTable
readList :: ReadS [CreateTable]
$creadList :: ReadS [CreateTable]
readsPrec :: Int -> ReadS CreateTable
$creadsPrec :: Int -> ReadS CreateTable
Prelude.Read, Int -> CreateTable -> ShowS
[CreateTable] -> ShowS
CreateTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateTable] -> ShowS
$cshowList :: [CreateTable] -> ShowS
show :: CreateTable -> String
$cshow :: CreateTable -> String
showsPrec :: Int -> CreateTable -> ShowS
$cshowsPrec :: Int -> CreateTable -> ShowS
Prelude.Show, forall x. Rep CreateTable x -> CreateTable
forall x. CreateTable -> Rep CreateTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateTable x -> CreateTable
$cfrom :: forall x. CreateTable -> Rep CreateTable x
Prelude.Generic)

-- |
-- Create a value of 'CreateTable' 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', 'createTable_catalogId' - The ID of the Data Catalog in which to create the @Table@. If none is
-- supplied, the Amazon Web Services account ID is used by default.
--
-- 'partitionIndexes', 'createTable_partitionIndexes' - A list of partition indexes, @PartitionIndex@ structures, to create in
-- the table.
--
-- 'transactionId', 'createTable_transactionId' - The ID of the transaction.
--
-- 'databaseName', 'createTable_databaseName' - The catalog database in which to create the new table. For Hive
-- compatibility, this name is entirely lowercase.
--
-- 'tableInput', 'createTable_tableInput' - The @TableInput@ object that defines the metadata table to create in the
-- catalog.
newCreateTable ::
  -- | 'databaseName'
  Prelude.Text ->
  -- | 'tableInput'
  TableInput ->
  CreateTable
newCreateTable :: Text -> TableInput -> CreateTable
newCreateTable Text
pDatabaseName_ TableInput
pTableInput_ =
  CreateTable'
    { $sel:catalogId:CreateTable' :: Maybe Text
catalogId = forall a. Maybe a
Prelude.Nothing,
      $sel:partitionIndexes:CreateTable' :: Maybe [PartitionIndex]
partitionIndexes = forall a. Maybe a
Prelude.Nothing,
      $sel:transactionId:CreateTable' :: Maybe Text
transactionId = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseName:CreateTable' :: Text
databaseName = Text
pDatabaseName_,
      $sel:tableInput:CreateTable' :: TableInput
tableInput = TableInput
pTableInput_
    }

-- | The ID of the Data Catalog in which to create the @Table@. If none is
-- supplied, the Amazon Web Services account ID is used by default.
createTable_catalogId :: Lens.Lens' CreateTable (Prelude.Maybe Prelude.Text)
createTable_catalogId :: Lens' CreateTable (Maybe Text)
createTable_catalogId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Maybe Text
catalogId :: Maybe Text
$sel:catalogId:CreateTable' :: CreateTable -> Maybe Text
catalogId} -> Maybe Text
catalogId) (\s :: CreateTable
s@CreateTable' {} Maybe Text
a -> CreateTable
s {$sel:catalogId:CreateTable' :: Maybe Text
catalogId = Maybe Text
a} :: CreateTable)

-- | A list of partition indexes, @PartitionIndex@ structures, to create in
-- the table.
createTable_partitionIndexes :: Lens.Lens' CreateTable (Prelude.Maybe [PartitionIndex])
createTable_partitionIndexes :: Lens' CreateTable (Maybe [PartitionIndex])
createTable_partitionIndexes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Maybe [PartitionIndex]
partitionIndexes :: Maybe [PartitionIndex]
$sel:partitionIndexes:CreateTable' :: CreateTable -> Maybe [PartitionIndex]
partitionIndexes} -> Maybe [PartitionIndex]
partitionIndexes) (\s :: CreateTable
s@CreateTable' {} Maybe [PartitionIndex]
a -> CreateTable
s {$sel:partitionIndexes:CreateTable' :: Maybe [PartitionIndex]
partitionIndexes = Maybe [PartitionIndex]
a} :: CreateTable) 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 ID of the transaction.
createTable_transactionId :: Lens.Lens' CreateTable (Prelude.Maybe Prelude.Text)
createTable_transactionId :: Lens' CreateTable (Maybe Text)
createTable_transactionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Maybe Text
transactionId :: Maybe Text
$sel:transactionId:CreateTable' :: CreateTable -> Maybe Text
transactionId} -> Maybe Text
transactionId) (\s :: CreateTable
s@CreateTable' {} Maybe Text
a -> CreateTable
s {$sel:transactionId:CreateTable' :: Maybe Text
transactionId = Maybe Text
a} :: CreateTable)

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

-- | The @TableInput@ object that defines the metadata table to create in the
-- catalog.
createTable_tableInput :: Lens.Lens' CreateTable TableInput
createTable_tableInput :: Lens' CreateTable TableInput
createTable_tableInput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {TableInput
tableInput :: TableInput
$sel:tableInput:CreateTable' :: CreateTable -> TableInput
tableInput} -> TableInput
tableInput) (\s :: CreateTable
s@CreateTable' {} TableInput
a -> CreateTable
s {$sel:tableInput:CreateTable' :: TableInput
tableInput = TableInput
a} :: CreateTable)

instance Core.AWSRequest CreateTable where
  type AWSResponse CreateTable = CreateTableResponse
  request :: (Service -> Service) -> CreateTable -> Request CreateTable
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 CreateTable
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateTable)))
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 -> CreateTableResponse
CreateTableResponse'
            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 CreateTable where
  hashWithSalt :: Int -> CreateTable -> Int
hashWithSalt Int
_salt CreateTable' {Maybe [PartitionIndex]
Maybe Text
Text
TableInput
tableInput :: TableInput
databaseName :: Text
transactionId :: Maybe Text
partitionIndexes :: Maybe [PartitionIndex]
catalogId :: Maybe Text
$sel:tableInput:CreateTable' :: CreateTable -> TableInput
$sel:databaseName:CreateTable' :: CreateTable -> Text
$sel:transactionId:CreateTable' :: CreateTable -> Maybe Text
$sel:partitionIndexes:CreateTable' :: CreateTable -> Maybe [PartitionIndex]
$sel:catalogId:CreateTable' :: CreateTable -> 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 [PartitionIndex]
partitionIndexes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transactionId
      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 CreateTable where
  rnf :: CreateTable -> ()
rnf CreateTable' {Maybe [PartitionIndex]
Maybe Text
Text
TableInput
tableInput :: TableInput
databaseName :: Text
transactionId :: Maybe Text
partitionIndexes :: Maybe [PartitionIndex]
catalogId :: Maybe Text
$sel:tableInput:CreateTable' :: CreateTable -> TableInput
$sel:databaseName:CreateTable' :: CreateTable -> Text
$sel:transactionId:CreateTable' :: CreateTable -> Maybe Text
$sel:partitionIndexes:CreateTable' :: CreateTable -> Maybe [PartitionIndex]
$sel:catalogId:CreateTable' :: CreateTable -> 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 [PartitionIndex]
partitionIndexes
      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 Text
databaseName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TableInput
tableInput

instance Data.ToHeaders CreateTable where
  toHeaders :: CreateTable -> 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.CreateTable" :: 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 CreateTable where
  toJSON :: CreateTable -> Value
toJSON CreateTable' {Maybe [PartitionIndex]
Maybe Text
Text
TableInput
tableInput :: TableInput
databaseName :: Text
transactionId :: Maybe Text
partitionIndexes :: Maybe [PartitionIndex]
catalogId :: Maybe Text
$sel:tableInput:CreateTable' :: CreateTable -> TableInput
$sel:databaseName:CreateTable' :: CreateTable -> Text
$sel:transactionId:CreateTable' :: CreateTable -> Maybe Text
$sel:partitionIndexes:CreateTable' :: CreateTable -> Maybe [PartitionIndex]
$sel:catalogId:CreateTable' :: CreateTable -> 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
"PartitionIndexes" 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 [PartitionIndex]
partitionIndexes,
            (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,
            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 CreateTable where
  toPath :: CreateTable -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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