{-# 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.SageMaker.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)
--
-- Deletes a pipeline if there are no running instances of the pipeline. To
-- delete a pipeline, you must stop all running instances of the pipeline
-- using the @StopPipelineExecution@ API. When you delete a pipeline, all
-- instances of the pipeline are deleted.
module Amazonka.SageMaker.DeletePipeline
  ( -- * Creating a Request
    DeletePipeline (..),
    newDeletePipeline,

    -- * Request Lenses
    deletePipeline_pipelineName,
    deletePipeline_clientRequestToken,

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

    -- * Response Lenses
    deletePipelineResponse_pipelineArn,
    deletePipelineResponse_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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMaker.Types

-- | /See:/ 'newDeletePipeline' smart constructor.
data DeletePipeline = DeletePipeline'
  { -- | The name of the pipeline to delete.
    DeletePipeline -> Text
pipelineName :: Prelude.Text,
    -- | A unique, case-sensitive identifier that you provide to ensure the
    -- idempotency of the operation. An idempotent operation completes no more
    -- than one time.
    DeletePipeline -> Text
clientRequestToken :: 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:
--
-- 'pipelineName', 'deletePipeline_pipelineName' - The name of the pipeline to delete.
--
-- 'clientRequestToken', 'deletePipeline_clientRequestToken' - A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the operation. An idempotent operation completes no more
-- than one time.
newDeletePipeline ::
  -- | 'pipelineName'
  Prelude.Text ->
  -- | 'clientRequestToken'
  Prelude.Text ->
  DeletePipeline
newDeletePipeline :: Text -> Text -> DeletePipeline
newDeletePipeline Text
pPipelineName_ Text
pClientRequestToken_ =
  DeletePipeline'
    { $sel:pipelineName:DeletePipeline' :: Text
pipelineName = Text
pPipelineName_,
      $sel:clientRequestToken:DeletePipeline' :: Text
clientRequestToken = Text
pClientRequestToken_
    }

-- | The name of the pipeline to delete.
deletePipeline_pipelineName :: Lens.Lens' DeletePipeline Prelude.Text
deletePipeline_pipelineName :: Lens' DeletePipeline Text
deletePipeline_pipelineName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeline' {Text
pipelineName :: Text
$sel:pipelineName:DeletePipeline' :: DeletePipeline -> Text
pipelineName} -> Text
pipelineName) (\s :: DeletePipeline
s@DeletePipeline' {} Text
a -> DeletePipeline
s {$sel:pipelineName:DeletePipeline' :: Text
pipelineName = Text
a} :: DeletePipeline)

-- | A unique, case-sensitive identifier that you provide to ensure the
-- idempotency of the operation. An idempotent operation completes no more
-- than one time.
deletePipeline_clientRequestToken :: Lens.Lens' DeletePipeline Prelude.Text
deletePipeline_clientRequestToken :: Lens' DeletePipeline Text
deletePipeline_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipeline' {Text
clientRequestToken :: Text
$sel:clientRequestToken:DeletePipeline' :: DeletePipeline -> Text
clientRequestToken} -> Text
clientRequestToken) (\s :: DeletePipeline
s@DeletePipeline' {} Text
a -> DeletePipeline
s {$sel:clientRequestToken:DeletePipeline' :: Text
clientRequestToken = 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, ToJSON a) => Service -> a -> Request a
Request.postJSON (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 -> 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 Text -> Int -> DeletePipelineResponse
DeletePipelineResponse'
            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
"PipelineArn")
            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 DeletePipeline where
  hashWithSalt :: Int -> DeletePipeline -> Int
hashWithSalt Int
_salt DeletePipeline' {Text
clientRequestToken :: Text
pipelineName :: Text
$sel:clientRequestToken:DeletePipeline' :: DeletePipeline -> Text
$sel:pipelineName:DeletePipeline' :: DeletePipeline -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientRequestToken

instance Prelude.NFData DeletePipeline where
  rnf :: DeletePipeline -> ()
rnf DeletePipeline' {Text
clientRequestToken :: Text
pipelineName :: Text
$sel:clientRequestToken:DeletePipeline' :: DeletePipeline -> Text
$sel:pipelineName:DeletePipeline' :: DeletePipeline -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientRequestToken

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

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

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

-- | /See:/ 'newDeletePipelineResponse' smart constructor.
data DeletePipelineResponse = DeletePipelineResponse'
  { -- | The Amazon Resource Name (ARN) of the pipeline to delete.
    DeletePipelineResponse -> Maybe Text
pipelineArn :: Prelude.Maybe Prelude.Text,
    -- | 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:
--
-- 'pipelineArn', 'deletePipelineResponse_pipelineArn' - The Amazon Resource Name (ARN) of the pipeline to delete.
--
-- 'httpStatus', 'deletePipelineResponse_httpStatus' - The response's http status code.
newDeletePipelineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeletePipelineResponse
newDeletePipelineResponse :: Int -> DeletePipelineResponse
newDeletePipelineResponse Int
pHttpStatus_ =
  DeletePipelineResponse'
    { $sel:pipelineArn:DeletePipelineResponse' :: Maybe Text
pipelineArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeletePipelineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the pipeline to delete.
deletePipelineResponse_pipelineArn :: Lens.Lens' DeletePipelineResponse (Prelude.Maybe Prelude.Text)
deletePipelineResponse_pipelineArn :: Lens' DeletePipelineResponse (Maybe Text)
deletePipelineResponse_pipelineArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePipelineResponse' {Maybe Text
pipelineArn :: Maybe Text
$sel:pipelineArn:DeletePipelineResponse' :: DeletePipelineResponse -> Maybe Text
pipelineArn} -> Maybe Text
pipelineArn) (\s :: DeletePipelineResponse
s@DeletePipelineResponse' {} Maybe Text
a -> DeletePipelineResponse
s {$sel:pipelineArn:DeletePipelineResponse' :: Maybe Text
pipelineArn = Maybe Text
a} :: DeletePipelineResponse)

-- | 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
Maybe Text
httpStatus :: Int
pipelineArn :: Maybe Text
$sel:httpStatus:DeletePipelineResponse' :: DeletePipelineResponse -> Int
$sel:pipelineArn:DeletePipelineResponse' :: DeletePipelineResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pipelineArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus