{-# 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.Rekognition.DeleteCollection
-- 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 the specified collection. Note that this operation removes all
-- faces in the collection. For an example, see
-- <https://docs.aws.amazon.com/rekognition/latest/dg/delete-collection-procedure.html Deleting a collection>.
--
-- This operation requires permissions to perform the
-- @rekognition:DeleteCollection@ action.
module Amazonka.Rekognition.DeleteCollection
  ( -- * Creating a Request
    DeleteCollection (..),
    newDeleteCollection,

    -- * Request Lenses
    deleteCollection_collectionId,

    -- * Destructuring the Response
    DeleteCollectionResponse (..),
    newDeleteCollectionResponse,

    -- * Response Lenses
    deleteCollectionResponse_statusCode,
    deleteCollectionResponse_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 Amazonka.Rekognition.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteCollection' smart constructor.
data DeleteCollection = DeleteCollection'
  { -- | ID of the collection to delete.
    DeleteCollection -> Text
collectionId :: Prelude.Text
  }
  deriving (DeleteCollection -> DeleteCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteCollection -> DeleteCollection -> Bool
$c/= :: DeleteCollection -> DeleteCollection -> Bool
== :: DeleteCollection -> DeleteCollection -> Bool
$c== :: DeleteCollection -> DeleteCollection -> Bool
Prelude.Eq, ReadPrec [DeleteCollection]
ReadPrec DeleteCollection
Int -> ReadS DeleteCollection
ReadS [DeleteCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteCollection]
$creadListPrec :: ReadPrec [DeleteCollection]
readPrec :: ReadPrec DeleteCollection
$creadPrec :: ReadPrec DeleteCollection
readList :: ReadS [DeleteCollection]
$creadList :: ReadS [DeleteCollection]
readsPrec :: Int -> ReadS DeleteCollection
$creadsPrec :: Int -> ReadS DeleteCollection
Prelude.Read, Int -> DeleteCollection -> ShowS
[DeleteCollection] -> ShowS
DeleteCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteCollection] -> ShowS
$cshowList :: [DeleteCollection] -> ShowS
show :: DeleteCollection -> String
$cshow :: DeleteCollection -> String
showsPrec :: Int -> DeleteCollection -> ShowS
$cshowsPrec :: Int -> DeleteCollection -> ShowS
Prelude.Show, forall x. Rep DeleteCollection x -> DeleteCollection
forall x. DeleteCollection -> Rep DeleteCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteCollection x -> DeleteCollection
$cfrom :: forall x. DeleteCollection -> Rep DeleteCollection x
Prelude.Generic)

-- |
-- Create a value of 'DeleteCollection' 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:
--
-- 'collectionId', 'deleteCollection_collectionId' - ID of the collection to delete.
newDeleteCollection ::
  -- | 'collectionId'
  Prelude.Text ->
  DeleteCollection
newDeleteCollection :: Text -> DeleteCollection
newDeleteCollection Text
pCollectionId_ =
  DeleteCollection' {$sel:collectionId:DeleteCollection' :: Text
collectionId = Text
pCollectionId_}

-- | ID of the collection to delete.
deleteCollection_collectionId :: Lens.Lens' DeleteCollection Prelude.Text
deleteCollection_collectionId :: Lens' DeleteCollection Text
deleteCollection_collectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCollection' {Text
collectionId :: Text
$sel:collectionId:DeleteCollection' :: DeleteCollection -> Text
collectionId} -> Text
collectionId) (\s :: DeleteCollection
s@DeleteCollection' {} Text
a -> DeleteCollection
s {$sel:collectionId:DeleteCollection' :: Text
collectionId = Text
a} :: DeleteCollection)

instance Core.AWSRequest DeleteCollection where
  type
    AWSResponse DeleteCollection =
      DeleteCollectionResponse
  request :: (Service -> Service)
-> DeleteCollection -> Request DeleteCollection
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 DeleteCollection
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteCollection)))
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 ->
          Maybe Natural -> Int -> DeleteCollectionResponse
DeleteCollectionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StatusCode")
            forall (f :: * -> *) a b. Applicative f => 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 DeleteCollection where
  hashWithSalt :: Int -> DeleteCollection -> Int
hashWithSalt Int
_salt DeleteCollection' {Text
collectionId :: Text
$sel:collectionId:DeleteCollection' :: DeleteCollection -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
collectionId

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

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

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

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

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

-- |
-- Create a value of 'DeleteCollectionResponse' 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:
--
-- 'statusCode', 'deleteCollectionResponse_statusCode' - HTTP status code that indicates the result of the operation.
--
-- 'httpStatus', 'deleteCollectionResponse_httpStatus' - The response's http status code.
newDeleteCollectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteCollectionResponse
newDeleteCollectionResponse :: Int -> DeleteCollectionResponse
newDeleteCollectionResponse Int
pHttpStatus_ =
  DeleteCollectionResponse'
    { $sel:statusCode:DeleteCollectionResponse' :: Maybe Natural
statusCode =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteCollectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | HTTP status code that indicates the result of the operation.
deleteCollectionResponse_statusCode :: Lens.Lens' DeleteCollectionResponse (Prelude.Maybe Prelude.Natural)
deleteCollectionResponse_statusCode :: Lens' DeleteCollectionResponse (Maybe Natural)
deleteCollectionResponse_statusCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCollectionResponse' {Maybe Natural
statusCode :: Maybe Natural
$sel:statusCode:DeleteCollectionResponse' :: DeleteCollectionResponse -> Maybe Natural
statusCode} -> Maybe Natural
statusCode) (\s :: DeleteCollectionResponse
s@DeleteCollectionResponse' {} Maybe Natural
a -> DeleteCollectionResponse
s {$sel:statusCode:DeleteCollectionResponse' :: Maybe Natural
statusCode = Maybe Natural
a} :: DeleteCollectionResponse)

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

instance Prelude.NFData DeleteCollectionResponse where
  rnf :: DeleteCollectionResponse -> ()
rnf DeleteCollectionResponse' {Int
Maybe Natural
httpStatus :: Int
statusCode :: Maybe Natural
$sel:httpStatus:DeleteCollectionResponse' :: DeleteCollectionResponse -> Int
$sel:statusCode:DeleteCollectionResponse' :: DeleteCollectionResponse -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
statusCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus