{-# 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.TimeStreamWrite.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)
--
-- The CreateTable operation adds a new table to an existing database in
-- your account. In an Amazon Web Services account, table names must be at
-- least unique within each Region if they are in the same database. You
-- may have identical table names in the same Region if the tables are in
-- separate databases. While creating the table, you must specify the table
-- name, database name, and the retention properties.
-- <https://docs.aws.amazon.com/timestream/latest/developerguide/ts-limits.html Service quotas apply>.
-- See
-- <https://docs.aws.amazon.com/timestream/latest/developerguide/code-samples.create-table.html code sample>
-- for details.
module Amazonka.TimeStreamWrite.CreateTable
  ( -- * Creating a Request
    CreateTable (..),
    newCreateTable,

    -- * Request Lenses
    createTable_magneticStoreWriteProperties,
    createTable_retentionProperties,
    createTable_tags,
    createTable_databaseName,
    createTable_tableName,

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

    -- * Response Lenses
    createTableResponse_table,
    createTableResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.TimeStreamWrite.Types

-- | /See:/ 'newCreateTable' smart constructor.
data CreateTable = CreateTable'
  { -- | Contains properties to set on the table when enabling magnetic store
    -- writes.
    CreateTable -> Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties :: Prelude.Maybe MagneticStoreWriteProperties,
    -- | The duration for which your time series data must be stored in the
    -- memory store and the magnetic store.
    CreateTable -> Maybe RetentionProperties
retentionProperties :: Prelude.Maybe RetentionProperties,
    -- | A list of key-value pairs to label the table.
    CreateTable -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the Timestream database.
    CreateTable -> Text
databaseName :: Prelude.Text,
    -- | The name of the Timestream table.
    CreateTable -> Text
tableName :: Prelude.Text
  }
  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:
--
-- 'magneticStoreWriteProperties', 'createTable_magneticStoreWriteProperties' - Contains properties to set on the table when enabling magnetic store
-- writes.
--
-- 'retentionProperties', 'createTable_retentionProperties' - The duration for which your time series data must be stored in the
-- memory store and the magnetic store.
--
-- 'tags', 'createTable_tags' - A list of key-value pairs to label the table.
--
-- 'databaseName', 'createTable_databaseName' - The name of the Timestream database.
--
-- 'tableName', 'createTable_tableName' - The name of the Timestream table.
newCreateTable ::
  -- | 'databaseName'
  Prelude.Text ->
  -- | 'tableName'
  Prelude.Text ->
  CreateTable
newCreateTable :: Text -> Text -> CreateTable
newCreateTable Text
pDatabaseName_ Text
pTableName_ =
  CreateTable'
    { $sel:magneticStoreWriteProperties:CreateTable' :: Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties =
        forall a. Maybe a
Prelude.Nothing,
      $sel:retentionProperties:CreateTable' :: Maybe RetentionProperties
retentionProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateTable' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseName:CreateTable' :: Text
databaseName = Text
pDatabaseName_,
      $sel:tableName:CreateTable' :: Text
tableName = Text
pTableName_
    }

-- | Contains properties to set on the table when enabling magnetic store
-- writes.
createTable_magneticStoreWriteProperties :: Lens.Lens' CreateTable (Prelude.Maybe MagneticStoreWriteProperties)
createTable_magneticStoreWriteProperties :: Lens' CreateTable (Maybe MagneticStoreWriteProperties)
createTable_magneticStoreWriteProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties :: Maybe MagneticStoreWriteProperties
$sel:magneticStoreWriteProperties:CreateTable' :: CreateTable -> Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties} -> Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties) (\s :: CreateTable
s@CreateTable' {} Maybe MagneticStoreWriteProperties
a -> CreateTable
s {$sel:magneticStoreWriteProperties:CreateTable' :: Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties = Maybe MagneticStoreWriteProperties
a} :: CreateTable)

-- | The duration for which your time series data must be stored in the
-- memory store and the magnetic store.
createTable_retentionProperties :: Lens.Lens' CreateTable (Prelude.Maybe RetentionProperties)
createTable_retentionProperties :: Lens' CreateTable (Maybe RetentionProperties)
createTable_retentionProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Maybe RetentionProperties
retentionProperties :: Maybe RetentionProperties
$sel:retentionProperties:CreateTable' :: CreateTable -> Maybe RetentionProperties
retentionProperties} -> Maybe RetentionProperties
retentionProperties) (\s :: CreateTable
s@CreateTable' {} Maybe RetentionProperties
a -> CreateTable
s {$sel:retentionProperties:CreateTable' :: Maybe RetentionProperties
retentionProperties = Maybe RetentionProperties
a} :: CreateTable)

-- | A list of key-value pairs to label the table.
createTable_tags :: Lens.Lens' CreateTable (Prelude.Maybe [Tag])
createTable_tags :: Lens' CreateTable (Maybe [Tag])
createTable_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateTable' :: CreateTable -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateTable
s@CreateTable' {} Maybe [Tag]
a -> CreateTable
s {$sel:tags:CreateTable' :: Maybe [Tag]
tags = Maybe [Tag]
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 name of the Timestream database.
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 name of the Timestream table.
createTable_tableName :: Lens.Lens' CreateTable Prelude.Text
createTable_tableName :: Lens' CreateTable Text
createTable_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTable' {Text
tableName :: Text
$sel:tableName:CreateTable' :: CreateTable -> Text
tableName} -> Text
tableName) (\s :: CreateTable
s@CreateTable' {} Text
a -> CreateTable
s {$sel:tableName:CreateTable' :: Text
tableName = Text
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 -> 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 Table -> Int -> CreateTableResponse
CreateTableResponse'
            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
"Table")
            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 CreateTable where
  hashWithSalt :: Int -> CreateTable -> Int
hashWithSalt Int
_salt CreateTable' {Maybe [Tag]
Maybe RetentionProperties
Maybe MagneticStoreWriteProperties
Text
tableName :: Text
databaseName :: Text
tags :: Maybe [Tag]
retentionProperties :: Maybe RetentionProperties
magneticStoreWriteProperties :: Maybe MagneticStoreWriteProperties
$sel:tableName:CreateTable' :: CreateTable -> Text
$sel:databaseName:CreateTable' :: CreateTable -> Text
$sel:tags:CreateTable' :: CreateTable -> Maybe [Tag]
$sel:retentionProperties:CreateTable' :: CreateTable -> Maybe RetentionProperties
$sel:magneticStoreWriteProperties:CreateTable' :: CreateTable -> Maybe MagneticStoreWriteProperties
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RetentionProperties
retentionProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
databaseName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tableName

instance Prelude.NFData CreateTable where
  rnf :: CreateTable -> ()
rnf CreateTable' {Maybe [Tag]
Maybe RetentionProperties
Maybe MagneticStoreWriteProperties
Text
tableName :: Text
databaseName :: Text
tags :: Maybe [Tag]
retentionProperties :: Maybe RetentionProperties
magneticStoreWriteProperties :: Maybe MagneticStoreWriteProperties
$sel:tableName:CreateTable' :: CreateTable -> Text
$sel:databaseName:CreateTable' :: CreateTable -> Text
$sel:tags:CreateTable' :: CreateTable -> Maybe [Tag]
$sel:retentionProperties:CreateTable' :: CreateTable -> Maybe RetentionProperties
$sel:magneticStoreWriteProperties:CreateTable' :: CreateTable -> Maybe MagneticStoreWriteProperties
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe MagneticStoreWriteProperties
magneticStoreWriteProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RetentionProperties
retentionProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      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 Text
tableName

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
"Timestream_20181101.CreateTable" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateTable where
  toJSON :: CreateTable -> Value
toJSON CreateTable' {Maybe [Tag]
Maybe RetentionProperties
Maybe MagneticStoreWriteProperties
Text
tableName :: Text
databaseName :: Text
tags :: Maybe [Tag]
retentionProperties :: Maybe RetentionProperties
magneticStoreWriteProperties :: Maybe MagneticStoreWriteProperties
$sel:tableName:CreateTable' :: CreateTable -> Text
$sel:databaseName:CreateTable' :: CreateTable -> Text
$sel:tags:CreateTable' :: CreateTable -> Maybe [Tag]
$sel:retentionProperties:CreateTable' :: CreateTable -> Maybe RetentionProperties
$sel:magneticStoreWriteProperties:CreateTable' :: CreateTable -> Maybe MagneticStoreWriteProperties
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MagneticStoreWriteProperties" 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 MagneticStoreWriteProperties
magneticStoreWriteProperties,
            (Key
"RetentionProperties" 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 RetentionProperties
retentionProperties,
            (Key
"Tags" 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 [Tag]
tags,
            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
"TableName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
tableName)
          ]
      )

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 newly created Timestream table.
    CreateTableResponse -> Maybe Table
table :: Prelude.Maybe Table,
    -- | 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:
--
-- 'table', 'createTableResponse_table' - The newly created Timestream table.
--
-- 'httpStatus', 'createTableResponse_httpStatus' - The response's http status code.
newCreateTableResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateTableResponse
newCreateTableResponse :: Int -> CreateTableResponse
newCreateTableResponse Int
pHttpStatus_ =
  CreateTableResponse'
    { $sel:table:CreateTableResponse' :: Maybe Table
table = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateTableResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The newly created Timestream table.
createTableResponse_table :: Lens.Lens' CreateTableResponse (Prelude.Maybe Table)
createTableResponse_table :: Lens' CreateTableResponse (Maybe Table)
createTableResponse_table = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateTableResponse' {Maybe Table
table :: Maybe Table
$sel:table:CreateTableResponse' :: CreateTableResponse -> Maybe Table
table} -> Maybe Table
table) (\s :: CreateTableResponse
s@CreateTableResponse' {} Maybe Table
a -> CreateTableResponse
s {$sel:table:CreateTableResponse' :: Maybe Table
table = Maybe Table
a} :: CreateTableResponse)

-- | 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
Maybe Table
httpStatus :: Int
table :: Maybe Table
$sel:httpStatus:CreateTableResponse' :: CreateTableResponse -> Int
$sel:table:CreateTableResponse' :: CreateTableResponse -> Maybe Table
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Table
table
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus