{-# 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.SSMContacts.DeleteContact
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- To remove a contact from Incident Manager, you can delete the contact.
-- Deleting a contact removes them from all escalation plans and related
-- response plans. Deleting an escalation plan removes it from all related
-- response plans. You will have to recreate the contact and its contact
-- channels before you can use it again.
module Amazonka.SSMContacts.DeleteContact
  ( -- * Creating a Request
    DeleteContact (..),
    newDeleteContact,

    -- * Request Lenses
    deleteContact_contactId,

    -- * Destructuring the Response
    DeleteContactResponse (..),
    newDeleteContactResponse,

    -- * Response Lenses
    deleteContactResponse_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.SSMContacts.Types

-- | /See:/ 'newDeleteContact' smart constructor.
data DeleteContact = DeleteContact'
  { -- | The Amazon Resource Name (ARN) of the contact that you\'re deleting.
    DeleteContact -> Text
contactId :: Prelude.Text
  }
  deriving (DeleteContact -> DeleteContact -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteContact -> DeleteContact -> Bool
$c/= :: DeleteContact -> DeleteContact -> Bool
== :: DeleteContact -> DeleteContact -> Bool
$c== :: DeleteContact -> DeleteContact -> Bool
Prelude.Eq, ReadPrec [DeleteContact]
ReadPrec DeleteContact
Int -> ReadS DeleteContact
ReadS [DeleteContact]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteContact]
$creadListPrec :: ReadPrec [DeleteContact]
readPrec :: ReadPrec DeleteContact
$creadPrec :: ReadPrec DeleteContact
readList :: ReadS [DeleteContact]
$creadList :: ReadS [DeleteContact]
readsPrec :: Int -> ReadS DeleteContact
$creadsPrec :: Int -> ReadS DeleteContact
Prelude.Read, Int -> DeleteContact -> ShowS
[DeleteContact] -> ShowS
DeleteContact -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteContact] -> ShowS
$cshowList :: [DeleteContact] -> ShowS
show :: DeleteContact -> String
$cshow :: DeleteContact -> String
showsPrec :: Int -> DeleteContact -> ShowS
$cshowsPrec :: Int -> DeleteContact -> ShowS
Prelude.Show, forall x. Rep DeleteContact x -> DeleteContact
forall x. DeleteContact -> Rep DeleteContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteContact x -> DeleteContact
$cfrom :: forall x. DeleteContact -> Rep DeleteContact x
Prelude.Generic)

-- |
-- Create a value of 'DeleteContact' 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:
--
-- 'contactId', 'deleteContact_contactId' - The Amazon Resource Name (ARN) of the contact that you\'re deleting.
newDeleteContact ::
  -- | 'contactId'
  Prelude.Text ->
  DeleteContact
newDeleteContact :: Text -> DeleteContact
newDeleteContact Text
pContactId_ =
  DeleteContact' {$sel:contactId:DeleteContact' :: Text
contactId = Text
pContactId_}

-- | The Amazon Resource Name (ARN) of the contact that you\'re deleting.
deleteContact_contactId :: Lens.Lens' DeleteContact Prelude.Text
deleteContact_contactId :: Lens' DeleteContact Text
deleteContact_contactId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteContact' {Text
contactId :: Text
$sel:contactId:DeleteContact' :: DeleteContact -> Text
contactId} -> Text
contactId) (\s :: DeleteContact
s@DeleteContact' {} Text
a -> DeleteContact
s {$sel:contactId:DeleteContact' :: Text
contactId = Text
a} :: DeleteContact)

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

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

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

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

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

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

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

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

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