{-# 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.DeleteStreamProcessor
-- 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 stream processor identified by @Name@. You assign the value
-- for @Name@ when you create the stream processor with
-- CreateStreamProcessor. You might not be able to use the same name for a
-- stream processor for a few seconds after calling
-- @DeleteStreamProcessor@.
module Amazonka.Rekognition.DeleteStreamProcessor
  ( -- * Creating a Request
    DeleteStreamProcessor (..),
    newDeleteStreamProcessor,

    -- * Request Lenses
    deleteStreamProcessor_name,

    -- * Destructuring the Response
    DeleteStreamProcessorResponse (..),
    newDeleteStreamProcessorResponse,

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

-- |
-- Create a value of 'DeleteStreamProcessor' 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:
--
-- 'name', 'deleteStreamProcessor_name' - The name of the stream processor you want to delete.
newDeleteStreamProcessor ::
  -- | 'name'
  Prelude.Text ->
  DeleteStreamProcessor
newDeleteStreamProcessor :: Text -> DeleteStreamProcessor
newDeleteStreamProcessor Text
pName_ =
  DeleteStreamProcessor' {$sel:name:DeleteStreamProcessor' :: Text
name = Text
pName_}

-- | The name of the stream processor you want to delete.
deleteStreamProcessor_name :: Lens.Lens' DeleteStreamProcessor Prelude.Text
deleteStreamProcessor_name :: Lens' DeleteStreamProcessor Text
deleteStreamProcessor_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteStreamProcessor' {Text
name :: Text
$sel:name:DeleteStreamProcessor' :: DeleteStreamProcessor -> Text
name} -> Text
name) (\s :: DeleteStreamProcessor
s@DeleteStreamProcessor' {} Text
a -> DeleteStreamProcessor
s {$sel:name:DeleteStreamProcessor' :: Text
name = Text
a} :: DeleteStreamProcessor)

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

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

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

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

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

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

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

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

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