{-# 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.DynamoDB.DeleteTable
-- 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 @DeleteTable@ operation deletes a table and all of its items. After
-- a @DeleteTable@ request, the specified table is in the @DELETING@ state
-- until DynamoDB completes the deletion. If the table is in the @ACTIVE@
-- state, you can delete it. If a table is in @CREATING@ or @UPDATING@
-- states, then DynamoDB returns a @ResourceInUseException@. If the
-- specified table does not exist, DynamoDB returns a
-- @ResourceNotFoundException@. If table is already in the @DELETING@
-- state, no error is returned.
--
-- DynamoDB might continue to accept data read and write operations, such
-- as @GetItem@ and @PutItem@, on a table in the @DELETING@ state until the
-- table deletion is complete.
--
-- When you delete a table, any indexes on that table are also deleted.
--
-- If you have DynamoDB Streams enabled on the table, then the
-- corresponding stream on that table goes into the @DISABLED@ state, and
-- the stream is automatically deleted after 24 hours.
--
-- Use the @DescribeTable@ action to check the status of the table.
module Amazonka.DynamoDB.DeleteTable
  ( -- * Creating a Request
    DeleteTable (..),
    newDeleteTable,

    -- * Request Lenses
    deleteTable_tableName,

    -- * Destructuring the Response
    DeleteTableResponse (..),
    newDeleteTableResponse,

    -- * Response Lenses
    deleteTableResponse_tableDescription,
    deleteTableResponse_httpStatus,
  )
where

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

-- | Represents the input of a @DeleteTable@ operation.
--
-- /See:/ 'newDeleteTable' smart constructor.
data DeleteTable = DeleteTable'
  { -- | The name of the table to delete.
    DeleteTable -> Text
tableName :: Prelude.Text
  }
  deriving (DeleteTable -> DeleteTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteTable -> DeleteTable -> Bool
$c/= :: DeleteTable -> DeleteTable -> Bool
== :: DeleteTable -> DeleteTable -> Bool
$c== :: DeleteTable -> DeleteTable -> Bool
Prelude.Eq, ReadPrec [DeleteTable]
ReadPrec DeleteTable
Int -> ReadS DeleteTable
ReadS [DeleteTable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteTable]
$creadListPrec :: ReadPrec [DeleteTable]
readPrec :: ReadPrec DeleteTable
$creadPrec :: ReadPrec DeleteTable
readList :: ReadS [DeleteTable]
$creadList :: ReadS [DeleteTable]
readsPrec :: Int -> ReadS DeleteTable
$creadsPrec :: Int -> ReadS DeleteTable
Prelude.Read, Int -> DeleteTable -> ShowS
[DeleteTable] -> ShowS
DeleteTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteTable] -> ShowS
$cshowList :: [DeleteTable] -> ShowS
show :: DeleteTable -> String
$cshow :: DeleteTable -> String
showsPrec :: Int -> DeleteTable -> ShowS
$cshowsPrec :: Int -> DeleteTable -> ShowS
Prelude.Show, forall x. Rep DeleteTable x -> DeleteTable
forall x. DeleteTable -> Rep DeleteTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteTable x -> DeleteTable
$cfrom :: forall x. DeleteTable -> Rep DeleteTable x
Prelude.Generic)

-- |
-- Create a value of 'DeleteTable' 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:
--
-- 'tableName', 'deleteTable_tableName' - The name of the table to delete.
newDeleteTable ::
  -- | 'tableName'
  Prelude.Text ->
  DeleteTable
newDeleteTable :: Text -> DeleteTable
newDeleteTable Text
pTableName_ =
  DeleteTable' {$sel:tableName:DeleteTable' :: Text
tableName = Text
pTableName_}

-- | The name of the table to delete.
deleteTable_tableName :: Lens.Lens' DeleteTable Prelude.Text
deleteTable_tableName :: Lens' DeleteTable Text
deleteTable_tableName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTable' {Text
tableName :: Text
$sel:tableName:DeleteTable' :: DeleteTable -> Text
tableName} -> Text
tableName) (\s :: DeleteTable
s@DeleteTable' {} Text
a -> DeleteTable
s {$sel:tableName:DeleteTable' :: Text
tableName = Text
a} :: DeleteTable)

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

instance Prelude.NFData DeleteTable where
  rnf :: DeleteTable -> ()
rnf DeleteTable' {Text
tableName :: Text
$sel:tableName:DeleteTable' :: DeleteTable -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
tableName

instance Data.ToHeaders DeleteTable where
  toHeaders :: DeleteTable -> 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
"DynamoDB_20120810.DeleteTable" ::
                          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 DeleteTable where
  toJSON :: DeleteTable -> Value
toJSON DeleteTable' {Text
tableName :: Text
$sel:tableName:DeleteTable' :: DeleteTable -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [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 DeleteTable where
  toPath :: DeleteTable -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | Represents the output of a @DeleteTable@ operation.
--
-- /See:/ 'newDeleteTableResponse' smart constructor.
data DeleteTableResponse = DeleteTableResponse'
  { -- | Represents the properties of a table.
    DeleteTableResponse -> Maybe TableDescription
tableDescription :: Prelude.Maybe TableDescription,
    -- | The response's http status code.
    DeleteTableResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteTableResponse -> DeleteTableResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteTableResponse -> DeleteTableResponse -> Bool
$c/= :: DeleteTableResponse -> DeleteTableResponse -> Bool
== :: DeleteTableResponse -> DeleteTableResponse -> Bool
$c== :: DeleteTableResponse -> DeleteTableResponse -> Bool
Prelude.Eq, ReadPrec [DeleteTableResponse]
ReadPrec DeleteTableResponse
Int -> ReadS DeleteTableResponse
ReadS [DeleteTableResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteTableResponse]
$creadListPrec :: ReadPrec [DeleteTableResponse]
readPrec :: ReadPrec DeleteTableResponse
$creadPrec :: ReadPrec DeleteTableResponse
readList :: ReadS [DeleteTableResponse]
$creadList :: ReadS [DeleteTableResponse]
readsPrec :: Int -> ReadS DeleteTableResponse
$creadsPrec :: Int -> ReadS DeleteTableResponse
Prelude.Read, Int -> DeleteTableResponse -> ShowS
[DeleteTableResponse] -> ShowS
DeleteTableResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteTableResponse] -> ShowS
$cshowList :: [DeleteTableResponse] -> ShowS
show :: DeleteTableResponse -> String
$cshow :: DeleteTableResponse -> String
showsPrec :: Int -> DeleteTableResponse -> ShowS
$cshowsPrec :: Int -> DeleteTableResponse -> ShowS
Prelude.Show, forall x. Rep DeleteTableResponse x -> DeleteTableResponse
forall x. DeleteTableResponse -> Rep DeleteTableResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteTableResponse x -> DeleteTableResponse
$cfrom :: forall x. DeleteTableResponse -> Rep DeleteTableResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteTableResponse' 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:
--
-- 'tableDescription', 'deleteTableResponse_tableDescription' - Represents the properties of a table.
--
-- 'httpStatus', 'deleteTableResponse_httpStatus' - The response's http status code.
newDeleteTableResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteTableResponse
newDeleteTableResponse :: Int -> DeleteTableResponse
newDeleteTableResponse Int
pHttpStatus_ =
  DeleteTableResponse'
    { $sel:tableDescription:DeleteTableResponse' :: Maybe TableDescription
tableDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteTableResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Represents the properties of a table.
deleteTableResponse_tableDescription :: Lens.Lens' DeleteTableResponse (Prelude.Maybe TableDescription)
deleteTableResponse_tableDescription :: Lens' DeleteTableResponse (Maybe TableDescription)
deleteTableResponse_tableDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTableResponse' {Maybe TableDescription
tableDescription :: Maybe TableDescription
$sel:tableDescription:DeleteTableResponse' :: DeleteTableResponse -> Maybe TableDescription
tableDescription} -> Maybe TableDescription
tableDescription) (\s :: DeleteTableResponse
s@DeleteTableResponse' {} Maybe TableDescription
a -> DeleteTableResponse
s {$sel:tableDescription:DeleteTableResponse' :: Maybe TableDescription
tableDescription = Maybe TableDescription
a} :: DeleteTableResponse)

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

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