{-# 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.RedshiftServerLess.DeleteNamespace
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a namespace from Amazon Redshift Serverless. Before you delete
-- the namespace, you can create a final snapshot that has all of the data
-- within the namespace.
module Amazonka.RedshiftServerLess.DeleteNamespace
  ( -- * Creating a Request
    DeleteNamespace (..),
    newDeleteNamespace,

    -- * Request Lenses
    deleteNamespace_finalSnapshotName,
    deleteNamespace_finalSnapshotRetentionPeriod,
    deleteNamespace_namespaceName,

    -- * Destructuring the Response
    DeleteNamespaceResponse (..),
    newDeleteNamespaceResponse,

    -- * Response Lenses
    deleteNamespaceResponse_httpStatus,
    deleteNamespaceResponse_namespace,
  )
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.RedshiftServerLess.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteNamespace' smart constructor.
data DeleteNamespace = DeleteNamespace'
  { -- | The name of the snapshot to be created before the namespace is deleted.
    DeleteNamespace -> Maybe Text
finalSnapshotName :: Prelude.Maybe Prelude.Text,
    -- | How long to retain the final snapshot.
    DeleteNamespace -> Maybe Int
finalSnapshotRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | The name of the namespace to delete.
    DeleteNamespace -> Text
namespaceName :: Prelude.Text
  }
  deriving (DeleteNamespace -> DeleteNamespace -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteNamespace -> DeleteNamespace -> Bool
$c/= :: DeleteNamespace -> DeleteNamespace -> Bool
== :: DeleteNamespace -> DeleteNamespace -> Bool
$c== :: DeleteNamespace -> DeleteNamespace -> Bool
Prelude.Eq, ReadPrec [DeleteNamespace]
ReadPrec DeleteNamespace
Int -> ReadS DeleteNamespace
ReadS [DeleteNamespace]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteNamespace]
$creadListPrec :: ReadPrec [DeleteNamespace]
readPrec :: ReadPrec DeleteNamespace
$creadPrec :: ReadPrec DeleteNamespace
readList :: ReadS [DeleteNamespace]
$creadList :: ReadS [DeleteNamespace]
readsPrec :: Int -> ReadS DeleteNamespace
$creadsPrec :: Int -> ReadS DeleteNamespace
Prelude.Read, Int -> DeleteNamespace -> ShowS
[DeleteNamespace] -> ShowS
DeleteNamespace -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteNamespace] -> ShowS
$cshowList :: [DeleteNamespace] -> ShowS
show :: DeleteNamespace -> String
$cshow :: DeleteNamespace -> String
showsPrec :: Int -> DeleteNamespace -> ShowS
$cshowsPrec :: Int -> DeleteNamespace -> ShowS
Prelude.Show, forall x. Rep DeleteNamespace x -> DeleteNamespace
forall x. DeleteNamespace -> Rep DeleteNamespace x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteNamespace x -> DeleteNamespace
$cfrom :: forall x. DeleteNamespace -> Rep DeleteNamespace x
Prelude.Generic)

-- |
-- Create a value of 'DeleteNamespace' 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:
--
-- 'finalSnapshotName', 'deleteNamespace_finalSnapshotName' - The name of the snapshot to be created before the namespace is deleted.
--
-- 'finalSnapshotRetentionPeriod', 'deleteNamespace_finalSnapshotRetentionPeriod' - How long to retain the final snapshot.
--
-- 'namespaceName', 'deleteNamespace_namespaceName' - The name of the namespace to delete.
newDeleteNamespace ::
  -- | 'namespaceName'
  Prelude.Text ->
  DeleteNamespace
newDeleteNamespace :: Text -> DeleteNamespace
newDeleteNamespace Text
pNamespaceName_ =
  DeleteNamespace'
    { $sel:finalSnapshotName:DeleteNamespace' :: Maybe Text
finalSnapshotName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:finalSnapshotRetentionPeriod:DeleteNamespace' :: Maybe Int
finalSnapshotRetentionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:namespaceName:DeleteNamespace' :: Text
namespaceName = Text
pNamespaceName_
    }

-- | The name of the snapshot to be created before the namespace is deleted.
deleteNamespace_finalSnapshotName :: Lens.Lens' DeleteNamespace (Prelude.Maybe Prelude.Text)
deleteNamespace_finalSnapshotName :: Lens' DeleteNamespace (Maybe Text)
deleteNamespace_finalSnapshotName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNamespace' {Maybe Text
finalSnapshotName :: Maybe Text
$sel:finalSnapshotName:DeleteNamespace' :: DeleteNamespace -> Maybe Text
finalSnapshotName} -> Maybe Text
finalSnapshotName) (\s :: DeleteNamespace
s@DeleteNamespace' {} Maybe Text
a -> DeleteNamespace
s {$sel:finalSnapshotName:DeleteNamespace' :: Maybe Text
finalSnapshotName = Maybe Text
a} :: DeleteNamespace)

-- | How long to retain the final snapshot.
deleteNamespace_finalSnapshotRetentionPeriod :: Lens.Lens' DeleteNamespace (Prelude.Maybe Prelude.Int)
deleteNamespace_finalSnapshotRetentionPeriod :: Lens' DeleteNamespace (Maybe Int)
deleteNamespace_finalSnapshotRetentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNamespace' {Maybe Int
finalSnapshotRetentionPeriod :: Maybe Int
$sel:finalSnapshotRetentionPeriod:DeleteNamespace' :: DeleteNamespace -> Maybe Int
finalSnapshotRetentionPeriod} -> Maybe Int
finalSnapshotRetentionPeriod) (\s :: DeleteNamespace
s@DeleteNamespace' {} Maybe Int
a -> DeleteNamespace
s {$sel:finalSnapshotRetentionPeriod:DeleteNamespace' :: Maybe Int
finalSnapshotRetentionPeriod = Maybe Int
a} :: DeleteNamespace)

-- | The name of the namespace to delete.
deleteNamespace_namespaceName :: Lens.Lens' DeleteNamespace Prelude.Text
deleteNamespace_namespaceName :: Lens' DeleteNamespace Text
deleteNamespace_namespaceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNamespace' {Text
namespaceName :: Text
$sel:namespaceName:DeleteNamespace' :: DeleteNamespace -> Text
namespaceName} -> Text
namespaceName) (\s :: DeleteNamespace
s@DeleteNamespace' {} Text
a -> DeleteNamespace
s {$sel:namespaceName:DeleteNamespace' :: Text
namespaceName = Text
a} :: DeleteNamespace)

instance Core.AWSRequest DeleteNamespace where
  type
    AWSResponse DeleteNamespace =
      DeleteNamespaceResponse
  request :: (Service -> Service) -> DeleteNamespace -> Request DeleteNamespace
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 DeleteNamespace
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteNamespace)))
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 ->
          Int -> Namespace -> DeleteNamespaceResponse
DeleteNamespaceResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"namespace")
      )

instance Prelude.Hashable DeleteNamespace where
  hashWithSalt :: Int -> DeleteNamespace -> Int
hashWithSalt Int
_salt DeleteNamespace' {Maybe Int
Maybe Text
Text
namespaceName :: Text
finalSnapshotRetentionPeriod :: Maybe Int
finalSnapshotName :: Maybe Text
$sel:namespaceName:DeleteNamespace' :: DeleteNamespace -> Text
$sel:finalSnapshotRetentionPeriod:DeleteNamespace' :: DeleteNamespace -> Maybe Int
$sel:finalSnapshotName:DeleteNamespace' :: DeleteNamespace -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
finalSnapshotName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
finalSnapshotRetentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
namespaceName

instance Prelude.NFData DeleteNamespace where
  rnf :: DeleteNamespace -> ()
rnf DeleteNamespace' {Maybe Int
Maybe Text
Text
namespaceName :: Text
finalSnapshotRetentionPeriod :: Maybe Int
finalSnapshotName :: Maybe Text
$sel:namespaceName:DeleteNamespace' :: DeleteNamespace -> Text
$sel:finalSnapshotRetentionPeriod:DeleteNamespace' :: DeleteNamespace -> Maybe Int
$sel:finalSnapshotName:DeleteNamespace' :: DeleteNamespace -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
finalSnapshotName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
finalSnapshotRetentionPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
namespaceName

instance Data.ToHeaders DeleteNamespace where
  toHeaders :: DeleteNamespace -> 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
"RedshiftServerless.DeleteNamespace" ::
                          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 DeleteNamespace where
  toJSON :: DeleteNamespace -> Value
toJSON DeleteNamespace' {Maybe Int
Maybe Text
Text
namespaceName :: Text
finalSnapshotRetentionPeriod :: Maybe Int
finalSnapshotName :: Maybe Text
$sel:namespaceName:DeleteNamespace' :: DeleteNamespace -> Text
$sel:finalSnapshotRetentionPeriod:DeleteNamespace' :: DeleteNamespace -> Maybe Int
$sel:finalSnapshotName:DeleteNamespace' :: DeleteNamespace -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"finalSnapshotName" 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
finalSnapshotName,
            (Key
"finalSnapshotRetentionPeriod" 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 Int
finalSnapshotRetentionPeriod,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"namespaceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
namespaceName)
          ]
      )

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

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

-- | /See:/ 'newDeleteNamespaceResponse' smart constructor.
data DeleteNamespaceResponse = DeleteNamespaceResponse'
  { -- | The response's http status code.
    DeleteNamespaceResponse -> Int
httpStatus :: Prelude.Int,
    -- | The deleted namespace object.
    DeleteNamespaceResponse -> Namespace
namespace :: Namespace
  }
  deriving (DeleteNamespaceResponse -> DeleteNamespaceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteNamespaceResponse -> DeleteNamespaceResponse -> Bool
$c/= :: DeleteNamespaceResponse -> DeleteNamespaceResponse -> Bool
== :: DeleteNamespaceResponse -> DeleteNamespaceResponse -> Bool
$c== :: DeleteNamespaceResponse -> DeleteNamespaceResponse -> Bool
Prelude.Eq, Int -> DeleteNamespaceResponse -> ShowS
[DeleteNamespaceResponse] -> ShowS
DeleteNamespaceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteNamespaceResponse] -> ShowS
$cshowList :: [DeleteNamespaceResponse] -> ShowS
show :: DeleteNamespaceResponse -> String
$cshow :: DeleteNamespaceResponse -> String
showsPrec :: Int -> DeleteNamespaceResponse -> ShowS
$cshowsPrec :: Int -> DeleteNamespaceResponse -> ShowS
Prelude.Show, forall x. Rep DeleteNamespaceResponse x -> DeleteNamespaceResponse
forall x. DeleteNamespaceResponse -> Rep DeleteNamespaceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteNamespaceResponse x -> DeleteNamespaceResponse
$cfrom :: forall x. DeleteNamespaceResponse -> Rep DeleteNamespaceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteNamespaceResponse' 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', 'deleteNamespaceResponse_httpStatus' - The response's http status code.
--
-- 'namespace', 'deleteNamespaceResponse_namespace' - The deleted namespace object.
newDeleteNamespaceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'namespace'
  Namespace ->
  DeleteNamespaceResponse
newDeleteNamespaceResponse :: Int -> Namespace -> DeleteNamespaceResponse
newDeleteNamespaceResponse Int
pHttpStatus_ Namespace
pNamespace_ =
  DeleteNamespaceResponse'
    { $sel:httpStatus:DeleteNamespaceResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:namespace:DeleteNamespaceResponse' :: Namespace
namespace = Namespace
pNamespace_
    }

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

-- | The deleted namespace object.
deleteNamespaceResponse_namespace :: Lens.Lens' DeleteNamespaceResponse Namespace
deleteNamespaceResponse_namespace :: Lens' DeleteNamespaceResponse Namespace
deleteNamespaceResponse_namespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNamespaceResponse' {Namespace
namespace :: Namespace
$sel:namespace:DeleteNamespaceResponse' :: DeleteNamespaceResponse -> Namespace
namespace} -> Namespace
namespace) (\s :: DeleteNamespaceResponse
s@DeleteNamespaceResponse' {} Namespace
a -> DeleteNamespaceResponse
s {$sel:namespace:DeleteNamespaceResponse' :: Namespace
namespace = Namespace
a} :: DeleteNamespaceResponse)

instance Prelude.NFData DeleteNamespaceResponse where
  rnf :: DeleteNamespaceResponse -> ()
rnf DeleteNamespaceResponse' {Int
Namespace
namespace :: Namespace
httpStatus :: Int
$sel:namespace:DeleteNamespaceResponse' :: DeleteNamespaceResponse -> Namespace
$sel:httpStatus:DeleteNamespaceResponse' :: DeleteNamespaceResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Namespace
namespace