{-# 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.ElasticTranscoder.DeletePipeline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The DeletePipeline operation removes a pipeline.
--
-- You can only delete a pipeline that has never been used or that is not
-- currently in use (doesn\'t contain any active jobs). If the pipeline is
-- currently in use, @DeletePipeline@ returns an error.
module Amazonka.ElasticTranscoder.DeletePipeline
  ( -- * Creating a Request
    DeletePipeline (..),
    newDeletePipeline,

    -- * Request Lenses
    deletePipeline_id,

    -- * Destructuring the Response
    DeletePipelineResponse (..),
    newDeletePipelineResponse,

    -- * Response Lenses
    deletePipelineResponse_httpStatus,
  )
where

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

-- | The @DeletePipelineRequest@ structure.
--
-- /See:/ 'newDeletePipeline' smart constructor.
data DeletePipeline = DeletePipeline'
  { -- | The identifier of the pipeline that you want to delete.
    DeletePipeline -> Text
id :: Prelude.Text
  }
  deriving (DeletePipeline -> DeletePipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePipeline -> DeletePipeline -> Bool
$c/= :: DeletePipeline -> DeletePipeline -> Bool
== :: DeletePipeline -> DeletePipeline -> Bool
$c== :: DeletePipeline -> DeletePipeline -> Bool
Prelude.Eq, ReadPrec [DeletePipeline]
ReadPrec DeletePipeline
Int -> ReadS DeletePipeline
ReadS [DeletePipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePipeline]
$creadListPrec :: ReadPrec [DeletePipeline]
readPrec :: ReadPrec DeletePipeline
$creadPrec :: ReadPrec DeletePipeline
readList :: ReadS [DeletePipeline]
$creadList :: ReadS [DeletePipeline]
readsPrec :: Int -> ReadS DeletePipeline
$creadsPrec :: Int -> ReadS DeletePipeline
Prelude.Read, Int -> DeletePipeline -> ShowS
[DeletePipeline] -> ShowS
DeletePipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePipeline] -> ShowS
$cshowList :: [DeletePipeline] -> ShowS
show :: DeletePipeline -> String
$cshow :: DeletePipeline -> String
showsPrec :: Int -> DeletePipeline -> ShowS
$cshowsPrec :: Int -> DeletePipeline -> ShowS
Prelude.Show, forall x. Rep DeletePipeline x -> DeletePipeline
forall x. DeletePipeline -> Rep DeletePipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePipeline x -> DeletePipeline
$cfrom :: forall x. DeletePipeline -> Rep DeletePipeline x
Prelude.Generic)

-- |
-- Create a value of 'DeletePipeline' 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:
--
-- 'id', 'deletePipeline_id' - The identifier of the pipeline that you want to delete.
newDeletePipeline ::
  -- | 'id'
  Prelude.Text ->
  DeletePipeline
newDeletePipeline :: Text -> DeletePipeline
newDeletePipeline Text
pId_ = DeletePipeline' {$sel:id:DeletePipeline' :: Text
id = Text
pId_}

-- | The identifier of the pipeline that you want to delete.
deletePipeline_id :: Lens.Lens' DeletePipeline Prelude.Text
deletePipeline_id :: Lens' DeletePipeline Text
deletePipeline_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeline' {Text
id :: Text
$sel:id:DeletePipeline' :: DeletePipeline -> Text
id} -> Text
id) (\s :: DeletePipeline
s@DeletePipeline' {} Text
a -> DeletePipeline
s {$sel:id:DeletePipeline' :: Text
id = Text
a} :: DeletePipeline)

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

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

instance Data.ToHeaders DeletePipeline where
  toHeaders :: DeletePipeline -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeletePipeline where
  toPath :: DeletePipeline -> ByteString
toPath DeletePipeline' {Text
id :: Text
$sel:id:DeletePipeline' :: DeletePipeline -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2012-09-25/pipelines/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

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

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

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

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