{-# 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.DirectoryService.DeleteDirectory
-- 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 an Directory Service directory.
--
-- Before you call @DeleteDirectory@, ensure that all of the required
-- permissions have been explicitly granted through a policy. For details
-- about what permissions are required to run the @DeleteDirectory@
-- operation, see
-- <http://docs.aws.amazon.com/directoryservice/latest/admin-guide/UsingWithDS_IAM_ResourcePermissions.html Directory Service API Permissions: Actions, Resources, and Conditions Reference>.
module Amazonka.DirectoryService.DeleteDirectory
  ( -- * Creating a Request
    DeleteDirectory (..),
    newDeleteDirectory,

    -- * Request Lenses
    deleteDirectory_directoryId,

    -- * Destructuring the Response
    DeleteDirectoryResponse (..),
    newDeleteDirectoryResponse,

    -- * Response Lenses
    deleteDirectoryResponse_directoryId,
    deleteDirectoryResponse_httpStatus,
  )
where

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

-- | Contains the inputs for the DeleteDirectory operation.
--
-- /See:/ 'newDeleteDirectory' smart constructor.
data DeleteDirectory = DeleteDirectory'
  { -- | The identifier of the directory to delete.
    DeleteDirectory -> Text
directoryId :: Prelude.Text
  }
  deriving (DeleteDirectory -> DeleteDirectory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDirectory -> DeleteDirectory -> Bool
$c/= :: DeleteDirectory -> DeleteDirectory -> Bool
== :: DeleteDirectory -> DeleteDirectory -> Bool
$c== :: DeleteDirectory -> DeleteDirectory -> Bool
Prelude.Eq, ReadPrec [DeleteDirectory]
ReadPrec DeleteDirectory
Int -> ReadS DeleteDirectory
ReadS [DeleteDirectory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDirectory]
$creadListPrec :: ReadPrec [DeleteDirectory]
readPrec :: ReadPrec DeleteDirectory
$creadPrec :: ReadPrec DeleteDirectory
readList :: ReadS [DeleteDirectory]
$creadList :: ReadS [DeleteDirectory]
readsPrec :: Int -> ReadS DeleteDirectory
$creadsPrec :: Int -> ReadS DeleteDirectory
Prelude.Read, Int -> DeleteDirectory -> ShowS
[DeleteDirectory] -> ShowS
DeleteDirectory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDirectory] -> ShowS
$cshowList :: [DeleteDirectory] -> ShowS
show :: DeleteDirectory -> String
$cshow :: DeleteDirectory -> String
showsPrec :: Int -> DeleteDirectory -> ShowS
$cshowsPrec :: Int -> DeleteDirectory -> ShowS
Prelude.Show, forall x. Rep DeleteDirectory x -> DeleteDirectory
forall x. DeleteDirectory -> Rep DeleteDirectory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDirectory x -> DeleteDirectory
$cfrom :: forall x. DeleteDirectory -> Rep DeleteDirectory x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDirectory' 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:
--
-- 'directoryId', 'deleteDirectory_directoryId' - The identifier of the directory to delete.
newDeleteDirectory ::
  -- | 'directoryId'
  Prelude.Text ->
  DeleteDirectory
newDeleteDirectory :: Text -> DeleteDirectory
newDeleteDirectory Text
pDirectoryId_ =
  DeleteDirectory' {$sel:directoryId:DeleteDirectory' :: Text
directoryId = Text
pDirectoryId_}

-- | The identifier of the directory to delete.
deleteDirectory_directoryId :: Lens.Lens' DeleteDirectory Prelude.Text
deleteDirectory_directoryId :: Lens' DeleteDirectory Text
deleteDirectory_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDirectory' {Text
directoryId :: Text
$sel:directoryId:DeleteDirectory' :: DeleteDirectory -> Text
directoryId} -> Text
directoryId) (\s :: DeleteDirectory
s@DeleteDirectory' {} Text
a -> DeleteDirectory
s {$sel:directoryId:DeleteDirectory' :: Text
directoryId = Text
a} :: DeleteDirectory)

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

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

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

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

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

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

-- |
-- Create a value of 'DeleteDirectoryResponse' 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:
--
-- 'directoryId', 'deleteDirectoryResponse_directoryId' - The directory identifier.
--
-- 'httpStatus', 'deleteDirectoryResponse_httpStatus' - The response's http status code.
newDeleteDirectoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteDirectoryResponse
newDeleteDirectoryResponse :: Int -> DeleteDirectoryResponse
newDeleteDirectoryResponse Int
pHttpStatus_ =
  DeleteDirectoryResponse'
    { $sel:directoryId:DeleteDirectoryResponse' :: Maybe Text
directoryId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteDirectoryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The directory identifier.
deleteDirectoryResponse_directoryId :: Lens.Lens' DeleteDirectoryResponse (Prelude.Maybe Prelude.Text)
deleteDirectoryResponse_directoryId :: Lens' DeleteDirectoryResponse (Maybe Text)
deleteDirectoryResponse_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDirectoryResponse' {Maybe Text
directoryId :: Maybe Text
$sel:directoryId:DeleteDirectoryResponse' :: DeleteDirectoryResponse -> Maybe Text
directoryId} -> Maybe Text
directoryId) (\s :: DeleteDirectoryResponse
s@DeleteDirectoryResponse' {} Maybe Text
a -> DeleteDirectoryResponse
s {$sel:directoryId:DeleteDirectoryResponse' :: Maybe Text
directoryId = Maybe Text
a} :: DeleteDirectoryResponse)

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

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