{-# 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.QLDB.DeleteLedger
-- 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 ledger and all of its contents. This action is irreversible.
--
-- If deletion protection is enabled, you must first disable it before you
-- can delete the ledger. You can disable it by calling the @UpdateLedger@
-- operation to set the flag to @false@.
module Amazonka.QLDB.DeleteLedger
  ( -- * Creating a Request
    DeleteLedger (..),
    newDeleteLedger,

    -- * Request Lenses
    deleteLedger_name,

    -- * Destructuring the Response
    DeleteLedgerResponse (..),
    newDeleteLedgerResponse,
  )
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.QLDB.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

-- |
-- Create a value of 'DeleteLedger' 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:
--
-- 'name', 'deleteLedger_name' - The name of the ledger that you want to delete.
newDeleteLedger ::
  -- | 'name'
  Prelude.Text ->
  DeleteLedger
newDeleteLedger :: Text -> DeleteLedger
newDeleteLedger Text
pName_ = DeleteLedger' {$sel:name:DeleteLedger' :: Text
name = Text
pName_}

-- | The name of the ledger that you want to delete.
deleteLedger_name :: Lens.Lens' DeleteLedger Prelude.Text
deleteLedger_name :: Lens' DeleteLedger Text
deleteLedger_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLedger' {Text
name :: Text
$sel:name:DeleteLedger' :: DeleteLedger -> Text
name} -> Text
name) (\s :: DeleteLedger
s@DeleteLedger' {} Text
a -> DeleteLedger
s {$sel:name:DeleteLedger' :: Text
name = Text
a} :: DeleteLedger)

instance Core.AWSRequest DeleteLedger where
  type AWSResponse DeleteLedger = DeleteLedgerResponse
  request :: (Service -> Service) -> DeleteLedger -> Request DeleteLedger
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteLedger
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteLedger)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteLedgerResponse
DeleteLedgerResponse'

instance Prelude.Hashable DeleteLedger where
  hashWithSalt :: Int -> DeleteLedger -> Int
hashWithSalt Int
_salt DeleteLedger' {Text
name :: Text
$sel:name:DeleteLedger' :: DeleteLedger -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders DeleteLedger where
  toHeaders :: DeleteLedger -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteLedger where
  toPath :: DeleteLedger -> ByteString
toPath DeleteLedger' {Text
name :: Text
$sel:name:DeleteLedger' :: DeleteLedger -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/ledgers/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

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

-- |
-- Create a value of 'DeleteLedgerResponse' 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.
newDeleteLedgerResponse ::
  DeleteLedgerResponse
newDeleteLedgerResponse :: DeleteLedgerResponse
newDeleteLedgerResponse = DeleteLedgerResponse
DeleteLedgerResponse'

instance Prelude.NFData DeleteLedgerResponse where
  rnf :: DeleteLedgerResponse -> ()
rnf DeleteLedgerResponse
_ = ()