{-# 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.SSM.DeleteDocument
-- 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 the Amazon Web Services Systems Manager document (SSM document)
-- and all managed node associations to the document.
--
-- Before you delete the document, we recommend that you use
-- DeleteAssociation to disassociate all managed nodes that are associated
-- with the document.
module Amazonka.SSM.DeleteDocument
  ( -- * Creating a Request
    DeleteDocument (..),
    newDeleteDocument,

    -- * Request Lenses
    deleteDocument_documentVersion,
    deleteDocument_force,
    deleteDocument_versionName,
    deleteDocument_name,

    -- * Destructuring the Response
    DeleteDocumentResponse (..),
    newDeleteDocumentResponse,

    -- * Response Lenses
    deleteDocumentResponse_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.SSM.Types

-- | /See:/ 'newDeleteDocument' smart constructor.
data DeleteDocument = DeleteDocument'
  { -- | The version of the document that you want to delete. If not provided,
    -- all versions of the document are deleted.
    DeleteDocument -> Maybe Text
documentVersion :: Prelude.Maybe Prelude.Text,
    -- | Some SSM document types require that you specify a @Force@ flag before
    -- you can delete the document. For example, you must specify a @Force@
    -- flag to delete a document of type @ApplicationConfigurationSchema@. You
    -- can restrict access to the @Force@ flag in an Identity and Access
    -- Management (IAM) policy.
    DeleteDocument -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | The version name of the document that you want to delete. If not
    -- provided, all versions of the document are deleted.
    DeleteDocument -> Maybe Text
versionName :: Prelude.Maybe Prelude.Text,
    -- | The name of the document.
    DeleteDocument -> Text
name :: Prelude.Text
  }
  deriving (DeleteDocument -> DeleteDocument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDocument -> DeleteDocument -> Bool
$c/= :: DeleteDocument -> DeleteDocument -> Bool
== :: DeleteDocument -> DeleteDocument -> Bool
$c== :: DeleteDocument -> DeleteDocument -> Bool
Prelude.Eq, ReadPrec [DeleteDocument]
ReadPrec DeleteDocument
Int -> ReadS DeleteDocument
ReadS [DeleteDocument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDocument]
$creadListPrec :: ReadPrec [DeleteDocument]
readPrec :: ReadPrec DeleteDocument
$creadPrec :: ReadPrec DeleteDocument
readList :: ReadS [DeleteDocument]
$creadList :: ReadS [DeleteDocument]
readsPrec :: Int -> ReadS DeleteDocument
$creadsPrec :: Int -> ReadS DeleteDocument
Prelude.Read, Int -> DeleteDocument -> ShowS
[DeleteDocument] -> ShowS
DeleteDocument -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDocument] -> ShowS
$cshowList :: [DeleteDocument] -> ShowS
show :: DeleteDocument -> String
$cshow :: DeleteDocument -> String
showsPrec :: Int -> DeleteDocument -> ShowS
$cshowsPrec :: Int -> DeleteDocument -> ShowS
Prelude.Show, forall x. Rep DeleteDocument x -> DeleteDocument
forall x. DeleteDocument -> Rep DeleteDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDocument x -> DeleteDocument
$cfrom :: forall x. DeleteDocument -> Rep DeleteDocument x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDocument' 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:
--
-- 'documentVersion', 'deleteDocument_documentVersion' - The version of the document that you want to delete. If not provided,
-- all versions of the document are deleted.
--
-- 'force', 'deleteDocument_force' - Some SSM document types require that you specify a @Force@ flag before
-- you can delete the document. For example, you must specify a @Force@
-- flag to delete a document of type @ApplicationConfigurationSchema@. You
-- can restrict access to the @Force@ flag in an Identity and Access
-- Management (IAM) policy.
--
-- 'versionName', 'deleteDocument_versionName' - The version name of the document that you want to delete. If not
-- provided, all versions of the document are deleted.
--
-- 'name', 'deleteDocument_name' - The name of the document.
newDeleteDocument ::
  -- | 'name'
  Prelude.Text ->
  DeleteDocument
newDeleteDocument :: Text -> DeleteDocument
newDeleteDocument Text
pName_ =
  DeleteDocument'
    { $sel:documentVersion:DeleteDocument' :: Maybe Text
documentVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:force:DeleteDocument' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
      $sel:versionName:DeleteDocument' :: Maybe Text
versionName = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DeleteDocument' :: Text
name = Text
pName_
    }

-- | The version of the document that you want to delete. If not provided,
-- all versions of the document are deleted.
deleteDocument_documentVersion :: Lens.Lens' DeleteDocument (Prelude.Maybe Prelude.Text)
deleteDocument_documentVersion :: Lens' DeleteDocument (Maybe Text)
deleteDocument_documentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocument' {Maybe Text
documentVersion :: Maybe Text
$sel:documentVersion:DeleteDocument' :: DeleteDocument -> Maybe Text
documentVersion} -> Maybe Text
documentVersion) (\s :: DeleteDocument
s@DeleteDocument' {} Maybe Text
a -> DeleteDocument
s {$sel:documentVersion:DeleteDocument' :: Maybe Text
documentVersion = Maybe Text
a} :: DeleteDocument)

-- | Some SSM document types require that you specify a @Force@ flag before
-- you can delete the document. For example, you must specify a @Force@
-- flag to delete a document of type @ApplicationConfigurationSchema@. You
-- can restrict access to the @Force@ flag in an Identity and Access
-- Management (IAM) policy.
deleteDocument_force :: Lens.Lens' DeleteDocument (Prelude.Maybe Prelude.Bool)
deleteDocument_force :: Lens' DeleteDocument (Maybe Bool)
deleteDocument_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocument' {Maybe Bool
force :: Maybe Bool
$sel:force:DeleteDocument' :: DeleteDocument -> Maybe Bool
force} -> Maybe Bool
force) (\s :: DeleteDocument
s@DeleteDocument' {} Maybe Bool
a -> DeleteDocument
s {$sel:force:DeleteDocument' :: Maybe Bool
force = Maybe Bool
a} :: DeleteDocument)

-- | The version name of the document that you want to delete. If not
-- provided, all versions of the document are deleted.
deleteDocument_versionName :: Lens.Lens' DeleteDocument (Prelude.Maybe Prelude.Text)
deleteDocument_versionName :: Lens' DeleteDocument (Maybe Text)
deleteDocument_versionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocument' {Maybe Text
versionName :: Maybe Text
$sel:versionName:DeleteDocument' :: DeleteDocument -> Maybe Text
versionName} -> Maybe Text
versionName) (\s :: DeleteDocument
s@DeleteDocument' {} Maybe Text
a -> DeleteDocument
s {$sel:versionName:DeleteDocument' :: Maybe Text
versionName = Maybe Text
a} :: DeleteDocument)

-- | The name of the document.
deleteDocument_name :: Lens.Lens' DeleteDocument Prelude.Text
deleteDocument_name :: Lens' DeleteDocument Text
deleteDocument_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocument' {Text
name :: Text
$sel:name:DeleteDocument' :: DeleteDocument -> Text
name} -> Text
name) (\s :: DeleteDocument
s@DeleteDocument' {} Text
a -> DeleteDocument
s {$sel:name:DeleteDocument' :: Text
name = Text
a} :: DeleteDocument)

instance Core.AWSRequest DeleteDocument where
  type
    AWSResponse DeleteDocument =
      DeleteDocumentResponse
  request :: (Service -> Service) -> DeleteDocument -> Request DeleteDocument
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 DeleteDocument
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteDocument)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteDocumentResponse
DeleteDocumentResponse'
            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))
      )

instance Prelude.Hashable DeleteDocument where
  hashWithSalt :: Int -> DeleteDocument -> Int
hashWithSalt Int
_salt DeleteDocument' {Maybe Bool
Maybe Text
Text
name :: Text
versionName :: Maybe Text
force :: Maybe Bool
documentVersion :: Maybe Text
$sel:name:DeleteDocument' :: DeleteDocument -> Text
$sel:versionName:DeleteDocument' :: DeleteDocument -> Maybe Text
$sel:force:DeleteDocument' :: DeleteDocument -> Maybe Bool
$sel:documentVersion:DeleteDocument' :: DeleteDocument -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
documentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
force
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
versionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData DeleteDocument where
  rnf :: DeleteDocument -> ()
rnf DeleteDocument' {Maybe Bool
Maybe Text
Text
name :: Text
versionName :: Maybe Text
force :: Maybe Bool
documentVersion :: Maybe Text
$sel:name:DeleteDocument' :: DeleteDocument -> Text
$sel:versionName:DeleteDocument' :: DeleteDocument -> Maybe Text
$sel:force:DeleteDocument' :: DeleteDocument -> Maybe Bool
$sel:documentVersion:DeleteDocument' :: DeleteDocument -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
versionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders DeleteDocument where
  toHeaders :: DeleteDocument -> 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
"AmazonSSM.DeleteDocument" :: 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 DeleteDocument where
  toJSON :: DeleteDocument -> Value
toJSON DeleteDocument' {Maybe Bool
Maybe Text
Text
name :: Text
versionName :: Maybe Text
force :: Maybe Bool
documentVersion :: Maybe Text
$sel:name:DeleteDocument' :: DeleteDocument -> Text
$sel:versionName:DeleteDocument' :: DeleteDocument -> Maybe Text
$sel:force:DeleteDocument' :: DeleteDocument -> Maybe Bool
$sel:documentVersion:DeleteDocument' :: DeleteDocument -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DocumentVersion" 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
documentVersion,
            (Key
"Force" 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 Bool
force,
            (Key
"VersionName" 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
versionName,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

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

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

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

-- |
-- Create a value of 'DeleteDocumentResponse' 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', 'deleteDocumentResponse_httpStatus' - The response's http status code.
newDeleteDocumentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteDocumentResponse
newDeleteDocumentResponse :: Int -> DeleteDocumentResponse
newDeleteDocumentResponse Int
pHttpStatus_ =
  DeleteDocumentResponse' {$sel:httpStatus:DeleteDocumentResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData DeleteDocumentResponse where
  rnf :: DeleteDocumentResponse -> ()
rnf DeleteDocumentResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteDocumentResponse' :: DeleteDocumentResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus