{-# 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.Pinpoint.DeleteEndpoint
-- 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 endpoint from an application.
module Amazonka.Pinpoint.DeleteEndpoint
  ( -- * Creating a Request
    DeleteEndpoint (..),
    newDeleteEndpoint,

    -- * Request Lenses
    deleteEndpoint_applicationId,
    deleteEndpoint_endpointId,

    -- * Destructuring the Response
    DeleteEndpointResponse (..),
    newDeleteEndpointResponse,

    -- * Response Lenses
    deleteEndpointResponse_httpStatus,
    deleteEndpointResponse_endpointResponse,
  )
where

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

-- | /See:/ 'newDeleteEndpoint' smart constructor.
data DeleteEndpoint = DeleteEndpoint'
  { -- | The unique identifier for the application. This identifier is displayed
    -- as the __Project ID__ on the Amazon Pinpoint console.
    DeleteEndpoint -> Text
applicationId :: Prelude.Text,
    -- | The unique identifier for the endpoint.
    DeleteEndpoint -> Text
endpointId :: Prelude.Text
  }
  deriving (DeleteEndpoint -> DeleteEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEndpoint -> DeleteEndpoint -> Bool
$c/= :: DeleteEndpoint -> DeleteEndpoint -> Bool
== :: DeleteEndpoint -> DeleteEndpoint -> Bool
$c== :: DeleteEndpoint -> DeleteEndpoint -> Bool
Prelude.Eq, ReadPrec [DeleteEndpoint]
ReadPrec DeleteEndpoint
Int -> ReadS DeleteEndpoint
ReadS [DeleteEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteEndpoint]
$creadListPrec :: ReadPrec [DeleteEndpoint]
readPrec :: ReadPrec DeleteEndpoint
$creadPrec :: ReadPrec DeleteEndpoint
readList :: ReadS [DeleteEndpoint]
$creadList :: ReadS [DeleteEndpoint]
readsPrec :: Int -> ReadS DeleteEndpoint
$creadsPrec :: Int -> ReadS DeleteEndpoint
Prelude.Read, Int -> DeleteEndpoint -> ShowS
[DeleteEndpoint] -> ShowS
DeleteEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEndpoint] -> ShowS
$cshowList :: [DeleteEndpoint] -> ShowS
show :: DeleteEndpoint -> String
$cshow :: DeleteEndpoint -> String
showsPrec :: Int -> DeleteEndpoint -> ShowS
$cshowsPrec :: Int -> DeleteEndpoint -> ShowS
Prelude.Show, forall x. Rep DeleteEndpoint x -> DeleteEndpoint
forall x. DeleteEndpoint -> Rep DeleteEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteEndpoint x -> DeleteEndpoint
$cfrom :: forall x. DeleteEndpoint -> Rep DeleteEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEndpoint' 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:
--
-- 'applicationId', 'deleteEndpoint_applicationId' - The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
--
-- 'endpointId', 'deleteEndpoint_endpointId' - The unique identifier for the endpoint.
newDeleteEndpoint ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'endpointId'
  Prelude.Text ->
  DeleteEndpoint
newDeleteEndpoint :: Text -> Text -> DeleteEndpoint
newDeleteEndpoint Text
pApplicationId_ Text
pEndpointId_ =
  DeleteEndpoint'
    { $sel:applicationId:DeleteEndpoint' :: Text
applicationId = Text
pApplicationId_,
      $sel:endpointId:DeleteEndpoint' :: Text
endpointId = Text
pEndpointId_
    }

-- | The unique identifier for the application. This identifier is displayed
-- as the __Project ID__ on the Amazon Pinpoint console.
deleteEndpoint_applicationId :: Lens.Lens' DeleteEndpoint Prelude.Text
deleteEndpoint_applicationId :: Lens' DeleteEndpoint Text
deleteEndpoint_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEndpoint' {Text
applicationId :: Text
$sel:applicationId:DeleteEndpoint' :: DeleteEndpoint -> Text
applicationId} -> Text
applicationId) (\s :: DeleteEndpoint
s@DeleteEndpoint' {} Text
a -> DeleteEndpoint
s {$sel:applicationId:DeleteEndpoint' :: Text
applicationId = Text
a} :: DeleteEndpoint)

-- | The unique identifier for the endpoint.
deleteEndpoint_endpointId :: Lens.Lens' DeleteEndpoint Prelude.Text
deleteEndpoint_endpointId :: Lens' DeleteEndpoint Text
deleteEndpoint_endpointId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEndpoint' {Text
endpointId :: Text
$sel:endpointId:DeleteEndpoint' :: DeleteEndpoint -> Text
endpointId} -> Text
endpointId) (\s :: DeleteEndpoint
s@DeleteEndpoint' {} Text
a -> DeleteEndpoint
s {$sel:endpointId:DeleteEndpoint' :: Text
endpointId = Text
a} :: DeleteEndpoint)

instance Core.AWSRequest DeleteEndpoint where
  type
    AWSResponse DeleteEndpoint =
      DeleteEndpointResponse
  request :: (Service -> Service) -> DeleteEndpoint -> Request DeleteEndpoint
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 DeleteEndpoint
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteEndpoint)))
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 -> EndpointResponse -> DeleteEndpointResponse
DeleteEndpointResponse'
            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.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

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

instance Prelude.NFData DeleteEndpoint where
  rnf :: DeleteEndpoint -> ()
rnf DeleteEndpoint' {Text
endpointId :: Text
applicationId :: Text
$sel:endpointId:DeleteEndpoint' :: DeleteEndpoint -> Text
$sel:applicationId:DeleteEndpoint' :: DeleteEndpoint -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointId

instance Data.ToHeaders DeleteEndpoint where
  toHeaders :: DeleteEndpoint -> 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 DeleteEndpoint where
  toPath :: DeleteEndpoint -> ByteString
toPath DeleteEndpoint' {Text
endpointId :: Text
applicationId :: Text
$sel:endpointId:DeleteEndpoint' :: DeleteEndpoint -> Text
$sel:applicationId:DeleteEndpoint' :: DeleteEndpoint -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/apps/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/endpoints/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
endpointId
      ]

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

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

-- |
-- Create a value of 'DeleteEndpointResponse' 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', 'deleteEndpointResponse_httpStatus' - The response's http status code.
--
-- 'endpointResponse', 'deleteEndpointResponse_endpointResponse' - Undocumented member.
newDeleteEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'endpointResponse'
  EndpointResponse ->
  DeleteEndpointResponse
newDeleteEndpointResponse :: Int -> EndpointResponse -> DeleteEndpointResponse
newDeleteEndpointResponse
  Int
pHttpStatus_
  EndpointResponse
pEndpointResponse_ =
    DeleteEndpointResponse'
      { $sel:httpStatus:DeleteEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:endpointResponse:DeleteEndpointResponse' :: EndpointResponse
endpointResponse = EndpointResponse
pEndpointResponse_
      }

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

-- | Undocumented member.
deleteEndpointResponse_endpointResponse :: Lens.Lens' DeleteEndpointResponse EndpointResponse
deleteEndpointResponse_endpointResponse :: Lens' DeleteEndpointResponse EndpointResponse
deleteEndpointResponse_endpointResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEndpointResponse' {EndpointResponse
endpointResponse :: EndpointResponse
$sel:endpointResponse:DeleteEndpointResponse' :: DeleteEndpointResponse -> EndpointResponse
endpointResponse} -> EndpointResponse
endpointResponse) (\s :: DeleteEndpointResponse
s@DeleteEndpointResponse' {} EndpointResponse
a -> DeleteEndpointResponse
s {$sel:endpointResponse:DeleteEndpointResponse' :: EndpointResponse
endpointResponse = EndpointResponse
a} :: DeleteEndpointResponse)

instance Prelude.NFData DeleteEndpointResponse where
  rnf :: DeleteEndpointResponse -> ()
rnf DeleteEndpointResponse' {Int
EndpointResponse
endpointResponse :: EndpointResponse
httpStatus :: Int
$sel:endpointResponse:DeleteEndpointResponse' :: DeleteEndpointResponse -> EndpointResponse
$sel:httpStatus:DeleteEndpointResponse' :: DeleteEndpointResponse -> 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 EndpointResponse
endpointResponse