{-# 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.CustomerProfiles.DeleteProfileObjectType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes a ProfileObjectType from a specific domain as well as removes
-- all the ProfileObjects of that type. It also disables integrations from
-- this specific ProfileObjectType. In addition, it scrubs all of the
-- fields of the standard profile that were populated from this
-- ProfileObjectType.
module Amazonka.CustomerProfiles.DeleteProfileObjectType
  ( -- * Creating a Request
    DeleteProfileObjectType (..),
    newDeleteProfileObjectType,

    -- * Request Lenses
    deleteProfileObjectType_domainName,
    deleteProfileObjectType_objectTypeName,

    -- * Destructuring the Response
    DeleteProfileObjectTypeResponse (..),
    newDeleteProfileObjectTypeResponse,

    -- * Response Lenses
    deleteProfileObjectTypeResponse_httpStatus,
    deleteProfileObjectTypeResponse_message,
  )
where

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

-- | /See:/ 'newDeleteProfileObjectType' smart constructor.
data DeleteProfileObjectType = DeleteProfileObjectType'
  { -- | The unique name of the domain.
    DeleteProfileObjectType -> Text
domainName :: Prelude.Text,
    -- | The name of the profile object type.
    DeleteProfileObjectType -> Text
objectTypeName :: Prelude.Text
  }
  deriving (DeleteProfileObjectType -> DeleteProfileObjectType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteProfileObjectType -> DeleteProfileObjectType -> Bool
$c/= :: DeleteProfileObjectType -> DeleteProfileObjectType -> Bool
== :: DeleteProfileObjectType -> DeleteProfileObjectType -> Bool
$c== :: DeleteProfileObjectType -> DeleteProfileObjectType -> Bool
Prelude.Eq, ReadPrec [DeleteProfileObjectType]
ReadPrec DeleteProfileObjectType
Int -> ReadS DeleteProfileObjectType
ReadS [DeleteProfileObjectType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteProfileObjectType]
$creadListPrec :: ReadPrec [DeleteProfileObjectType]
readPrec :: ReadPrec DeleteProfileObjectType
$creadPrec :: ReadPrec DeleteProfileObjectType
readList :: ReadS [DeleteProfileObjectType]
$creadList :: ReadS [DeleteProfileObjectType]
readsPrec :: Int -> ReadS DeleteProfileObjectType
$creadsPrec :: Int -> ReadS DeleteProfileObjectType
Prelude.Read, Int -> DeleteProfileObjectType -> ShowS
[DeleteProfileObjectType] -> ShowS
DeleteProfileObjectType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteProfileObjectType] -> ShowS
$cshowList :: [DeleteProfileObjectType] -> ShowS
show :: DeleteProfileObjectType -> String
$cshow :: DeleteProfileObjectType -> String
showsPrec :: Int -> DeleteProfileObjectType -> ShowS
$cshowsPrec :: Int -> DeleteProfileObjectType -> ShowS
Prelude.Show, forall x. Rep DeleteProfileObjectType x -> DeleteProfileObjectType
forall x. DeleteProfileObjectType -> Rep DeleteProfileObjectType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteProfileObjectType x -> DeleteProfileObjectType
$cfrom :: forall x. DeleteProfileObjectType -> Rep DeleteProfileObjectType x
Prelude.Generic)

-- |
-- Create a value of 'DeleteProfileObjectType' 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:
--
-- 'domainName', 'deleteProfileObjectType_domainName' - The unique name of the domain.
--
-- 'objectTypeName', 'deleteProfileObjectType_objectTypeName' - The name of the profile object type.
newDeleteProfileObjectType ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'objectTypeName'
  Prelude.Text ->
  DeleteProfileObjectType
newDeleteProfileObjectType :: Text -> Text -> DeleteProfileObjectType
newDeleteProfileObjectType
  Text
pDomainName_
  Text
pObjectTypeName_ =
    DeleteProfileObjectType'
      { $sel:domainName:DeleteProfileObjectType' :: Text
domainName = Text
pDomainName_,
        $sel:objectTypeName:DeleteProfileObjectType' :: Text
objectTypeName = Text
pObjectTypeName_
      }

-- | The unique name of the domain.
deleteProfileObjectType_domainName :: Lens.Lens' DeleteProfileObjectType Prelude.Text
deleteProfileObjectType_domainName :: Lens' DeleteProfileObjectType Text
deleteProfileObjectType_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteProfileObjectType' {Text
domainName :: Text
$sel:domainName:DeleteProfileObjectType' :: DeleteProfileObjectType -> Text
domainName} -> Text
domainName) (\s :: DeleteProfileObjectType
s@DeleteProfileObjectType' {} Text
a -> DeleteProfileObjectType
s {$sel:domainName:DeleteProfileObjectType' :: Text
domainName = Text
a} :: DeleteProfileObjectType)

-- | The name of the profile object type.
deleteProfileObjectType_objectTypeName :: Lens.Lens' DeleteProfileObjectType Prelude.Text
deleteProfileObjectType_objectTypeName :: Lens' DeleteProfileObjectType Text
deleteProfileObjectType_objectTypeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteProfileObjectType' {Text
objectTypeName :: Text
$sel:objectTypeName:DeleteProfileObjectType' :: DeleteProfileObjectType -> Text
objectTypeName} -> Text
objectTypeName) (\s :: DeleteProfileObjectType
s@DeleteProfileObjectType' {} Text
a -> DeleteProfileObjectType
s {$sel:objectTypeName:DeleteProfileObjectType' :: Text
objectTypeName = Text
a} :: DeleteProfileObjectType)

instance Core.AWSRequest DeleteProfileObjectType where
  type
    AWSResponse DeleteProfileObjectType =
      DeleteProfileObjectTypeResponse
  request :: (Service -> Service)
-> DeleteProfileObjectType -> Request DeleteProfileObjectType
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 DeleteProfileObjectType
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteProfileObjectType)))
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 -> Text -> DeleteProfileObjectTypeResponse
DeleteProfileObjectTypeResponse'
            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
"Message")
      )

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

instance Prelude.NFData DeleteProfileObjectType where
  rnf :: DeleteProfileObjectType -> ()
rnf DeleteProfileObjectType' {Text
objectTypeName :: Text
domainName :: Text
$sel:objectTypeName:DeleteProfileObjectType' :: DeleteProfileObjectType -> Text
$sel:domainName:DeleteProfileObjectType' :: DeleteProfileObjectType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
objectTypeName

instance Data.ToHeaders DeleteProfileObjectType where
  toHeaders :: DeleteProfileObjectType -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteProfileObjectType where
  toPath :: DeleteProfileObjectType -> ByteString
toPath DeleteProfileObjectType' {Text
objectTypeName :: Text
domainName :: Text
$sel:objectTypeName:DeleteProfileObjectType' :: DeleteProfileObjectType -> Text
$sel:domainName:DeleteProfileObjectType' :: DeleteProfileObjectType -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/domains/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
domainName,
        ByteString
"/object-types/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
objectTypeName
      ]

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

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

-- |
-- Create a value of 'DeleteProfileObjectTypeResponse' 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', 'deleteProfileObjectTypeResponse_httpStatus' - The response's http status code.
--
-- 'message', 'deleteProfileObjectTypeResponse_message' - A message that indicates the delete request is done.
newDeleteProfileObjectTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'message'
  Prelude.Text ->
  DeleteProfileObjectTypeResponse
newDeleteProfileObjectTypeResponse :: Int -> Text -> DeleteProfileObjectTypeResponse
newDeleteProfileObjectTypeResponse
  Int
pHttpStatus_
  Text
pMessage_ =
    DeleteProfileObjectTypeResponse'
      { $sel:httpStatus:DeleteProfileObjectTypeResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:message:DeleteProfileObjectTypeResponse' :: Text
message = Text
pMessage_
      }

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

-- | A message that indicates the delete request is done.
deleteProfileObjectTypeResponse_message :: Lens.Lens' DeleteProfileObjectTypeResponse Prelude.Text
deleteProfileObjectTypeResponse_message :: Lens' DeleteProfileObjectTypeResponse Text
deleteProfileObjectTypeResponse_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteProfileObjectTypeResponse' {Text
message :: Text
$sel:message:DeleteProfileObjectTypeResponse' :: DeleteProfileObjectTypeResponse -> Text
message} -> Text
message) (\s :: DeleteProfileObjectTypeResponse
s@DeleteProfileObjectTypeResponse' {} Text
a -> DeleteProfileObjectTypeResponse
s {$sel:message:DeleteProfileObjectTypeResponse' :: Text
message = Text
a} :: DeleteProfileObjectTypeResponse)

instance
  Prelude.NFData
    DeleteProfileObjectTypeResponse
  where
  rnf :: DeleteProfileObjectTypeResponse -> ()
rnf DeleteProfileObjectTypeResponse' {Int
Text
message :: Text
httpStatus :: Int
$sel:message:DeleteProfileObjectTypeResponse' :: DeleteProfileObjectTypeResponse -> Text
$sel:httpStatus:DeleteProfileObjectTypeResponse' :: DeleteProfileObjectTypeResponse -> 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 Text
message