{-# 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.Location.DeletePlaceIndex
-- 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 a place index resource from your AWS account.
--
-- This operation deletes the resource permanently.
module Amazonka.Location.DeletePlaceIndex
  ( -- * Creating a Request
    DeletePlaceIndex (..),
    newDeletePlaceIndex,

    -- * Request Lenses
    deletePlaceIndex_indexName,

    -- * Destructuring the Response
    DeletePlaceIndexResponse (..),
    newDeletePlaceIndexResponse,

    -- * Response Lenses
    deletePlaceIndexResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeletePlaceIndex' smart constructor.
data DeletePlaceIndex = DeletePlaceIndex'
  { -- | The name of the place index resource to be deleted.
    DeletePlaceIndex -> Text
indexName :: Prelude.Text
  }
  deriving (DeletePlaceIndex -> DeletePlaceIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePlaceIndex -> DeletePlaceIndex -> Bool
$c/= :: DeletePlaceIndex -> DeletePlaceIndex -> Bool
== :: DeletePlaceIndex -> DeletePlaceIndex -> Bool
$c== :: DeletePlaceIndex -> DeletePlaceIndex -> Bool
Prelude.Eq, ReadPrec [DeletePlaceIndex]
ReadPrec DeletePlaceIndex
Int -> ReadS DeletePlaceIndex
ReadS [DeletePlaceIndex]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePlaceIndex]
$creadListPrec :: ReadPrec [DeletePlaceIndex]
readPrec :: ReadPrec DeletePlaceIndex
$creadPrec :: ReadPrec DeletePlaceIndex
readList :: ReadS [DeletePlaceIndex]
$creadList :: ReadS [DeletePlaceIndex]
readsPrec :: Int -> ReadS DeletePlaceIndex
$creadsPrec :: Int -> ReadS DeletePlaceIndex
Prelude.Read, Int -> DeletePlaceIndex -> ShowS
[DeletePlaceIndex] -> ShowS
DeletePlaceIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePlaceIndex] -> ShowS
$cshowList :: [DeletePlaceIndex] -> ShowS
show :: DeletePlaceIndex -> String
$cshow :: DeletePlaceIndex -> String
showsPrec :: Int -> DeletePlaceIndex -> ShowS
$cshowsPrec :: Int -> DeletePlaceIndex -> ShowS
Prelude.Show, forall x. Rep DeletePlaceIndex x -> DeletePlaceIndex
forall x. DeletePlaceIndex -> Rep DeletePlaceIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePlaceIndex x -> DeletePlaceIndex
$cfrom :: forall x. DeletePlaceIndex -> Rep DeletePlaceIndex x
Prelude.Generic)

-- |
-- Create a value of 'DeletePlaceIndex' 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:
--
-- 'indexName', 'deletePlaceIndex_indexName' - The name of the place index resource to be deleted.
newDeletePlaceIndex ::
  -- | 'indexName'
  Prelude.Text ->
  DeletePlaceIndex
newDeletePlaceIndex :: Text -> DeletePlaceIndex
newDeletePlaceIndex Text
pIndexName_ =
  DeletePlaceIndex' {$sel:indexName:DeletePlaceIndex' :: Text
indexName = Text
pIndexName_}

-- | The name of the place index resource to be deleted.
deletePlaceIndex_indexName :: Lens.Lens' DeletePlaceIndex Prelude.Text
deletePlaceIndex_indexName :: Lens' DeletePlaceIndex Text
deletePlaceIndex_indexName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePlaceIndex' {Text
indexName :: Text
$sel:indexName:DeletePlaceIndex' :: DeletePlaceIndex -> Text
indexName} -> Text
indexName) (\s :: DeletePlaceIndex
s@DeletePlaceIndex' {} Text
a -> DeletePlaceIndex
s {$sel:indexName:DeletePlaceIndex' :: Text
indexName = Text
a} :: DeletePlaceIndex)

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

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

instance Data.ToHeaders DeletePlaceIndex where
  toHeaders :: DeletePlaceIndex -> 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 DeletePlaceIndex where
  toPath :: DeletePlaceIndex -> ByteString
toPath DeletePlaceIndex' {Text
indexName :: Text
$sel:indexName:DeletePlaceIndex' :: DeletePlaceIndex -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/places/v0/indexes/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
indexName]

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

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

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

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

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