{-# 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.DeleteGeofenceCollection
-- 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 geofence collection from your AWS account.
--
-- This operation deletes the resource permanently. If the geofence
-- collection is the target of a tracker resource, the devices will no
-- longer be monitored.
module Amazonka.Location.DeleteGeofenceCollection
  ( -- * Creating a Request
    DeleteGeofenceCollection (..),
    newDeleteGeofenceCollection,

    -- * Request Lenses
    deleteGeofenceCollection_collectionName,

    -- * Destructuring the Response
    DeleteGeofenceCollectionResponse (..),
    newDeleteGeofenceCollectionResponse,

    -- * Response Lenses
    deleteGeofenceCollectionResponse_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:/ 'newDeleteGeofenceCollection' smart constructor.
data DeleteGeofenceCollection = DeleteGeofenceCollection'
  { -- | The name of the geofence collection to be deleted.
    DeleteGeofenceCollection -> Text
collectionName :: Prelude.Text
  }
  deriving (DeleteGeofenceCollection -> DeleteGeofenceCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGeofenceCollection -> DeleteGeofenceCollection -> Bool
$c/= :: DeleteGeofenceCollection -> DeleteGeofenceCollection -> Bool
== :: DeleteGeofenceCollection -> DeleteGeofenceCollection -> Bool
$c== :: DeleteGeofenceCollection -> DeleteGeofenceCollection -> Bool
Prelude.Eq, ReadPrec [DeleteGeofenceCollection]
ReadPrec DeleteGeofenceCollection
Int -> ReadS DeleteGeofenceCollection
ReadS [DeleteGeofenceCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGeofenceCollection]
$creadListPrec :: ReadPrec [DeleteGeofenceCollection]
readPrec :: ReadPrec DeleteGeofenceCollection
$creadPrec :: ReadPrec DeleteGeofenceCollection
readList :: ReadS [DeleteGeofenceCollection]
$creadList :: ReadS [DeleteGeofenceCollection]
readsPrec :: Int -> ReadS DeleteGeofenceCollection
$creadsPrec :: Int -> ReadS DeleteGeofenceCollection
Prelude.Read, Int -> DeleteGeofenceCollection -> ShowS
[DeleteGeofenceCollection] -> ShowS
DeleteGeofenceCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGeofenceCollection] -> ShowS
$cshowList :: [DeleteGeofenceCollection] -> ShowS
show :: DeleteGeofenceCollection -> String
$cshow :: DeleteGeofenceCollection -> String
showsPrec :: Int -> DeleteGeofenceCollection -> ShowS
$cshowsPrec :: Int -> DeleteGeofenceCollection -> ShowS
Prelude.Show, forall x.
Rep DeleteGeofenceCollection x -> DeleteGeofenceCollection
forall x.
DeleteGeofenceCollection -> Rep DeleteGeofenceCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteGeofenceCollection x -> DeleteGeofenceCollection
$cfrom :: forall x.
DeleteGeofenceCollection -> Rep DeleteGeofenceCollection x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGeofenceCollection' 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:
--
-- 'collectionName', 'deleteGeofenceCollection_collectionName' - The name of the geofence collection to be deleted.
newDeleteGeofenceCollection ::
  -- | 'collectionName'
  Prelude.Text ->
  DeleteGeofenceCollection
newDeleteGeofenceCollection :: Text -> DeleteGeofenceCollection
newDeleteGeofenceCollection Text
pCollectionName_ =
  DeleteGeofenceCollection'
    { $sel:collectionName:DeleteGeofenceCollection' :: Text
collectionName =
        Text
pCollectionName_
    }

-- | The name of the geofence collection to be deleted.
deleteGeofenceCollection_collectionName :: Lens.Lens' DeleteGeofenceCollection Prelude.Text
deleteGeofenceCollection_collectionName :: Lens' DeleteGeofenceCollection Text
deleteGeofenceCollection_collectionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGeofenceCollection' {Text
collectionName :: Text
$sel:collectionName:DeleteGeofenceCollection' :: DeleteGeofenceCollection -> Text
collectionName} -> Text
collectionName) (\s :: DeleteGeofenceCollection
s@DeleteGeofenceCollection' {} Text
a -> DeleteGeofenceCollection
s {$sel:collectionName:DeleteGeofenceCollection' :: Text
collectionName = Text
a} :: DeleteGeofenceCollection)

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

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

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

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

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

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

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

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