{-# 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.ServiceCatalog.DeleteProvisionedProductPlan
-- 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 plan.
module Amazonka.ServiceCatalog.DeleteProvisionedProductPlan
  ( -- * Creating a Request
    DeleteProvisionedProductPlan (..),
    newDeleteProvisionedProductPlan,

    -- * Request Lenses
    deleteProvisionedProductPlan_acceptLanguage,
    deleteProvisionedProductPlan_ignoreErrors,
    deleteProvisionedProductPlan_planId,

    -- * Destructuring the Response
    DeleteProvisionedProductPlanResponse (..),
    newDeleteProvisionedProductPlanResponse,

    -- * Response Lenses
    deleteProvisionedProductPlanResponse_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.ServiceCatalog.Types

-- | /See:/ 'newDeleteProvisionedProductPlan' smart constructor.
data DeleteProvisionedProductPlan = DeleteProvisionedProductPlan'
  { -- | The language code.
    --
    -- -   @en@ - English (default)
    --
    -- -   @jp@ - Japanese
    --
    -- -   @zh@ - Chinese
    DeleteProvisionedProductPlan -> Maybe Text
acceptLanguage :: Prelude.Maybe Prelude.Text,
    -- | If set to true, Service Catalog stops managing the specified provisioned
    -- product even if it cannot delete the underlying resources.
    DeleteProvisionedProductPlan -> Maybe Bool
ignoreErrors :: Prelude.Maybe Prelude.Bool,
    -- | The plan identifier.
    DeleteProvisionedProductPlan -> Text
planId :: Prelude.Text
  }
  deriving (DeleteProvisionedProductPlan
-> DeleteProvisionedProductPlan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteProvisionedProductPlan
-> DeleteProvisionedProductPlan -> Bool
$c/= :: DeleteProvisionedProductPlan
-> DeleteProvisionedProductPlan -> Bool
== :: DeleteProvisionedProductPlan
-> DeleteProvisionedProductPlan -> Bool
$c== :: DeleteProvisionedProductPlan
-> DeleteProvisionedProductPlan -> Bool
Prelude.Eq, ReadPrec [DeleteProvisionedProductPlan]
ReadPrec DeleteProvisionedProductPlan
Int -> ReadS DeleteProvisionedProductPlan
ReadS [DeleteProvisionedProductPlan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteProvisionedProductPlan]
$creadListPrec :: ReadPrec [DeleteProvisionedProductPlan]
readPrec :: ReadPrec DeleteProvisionedProductPlan
$creadPrec :: ReadPrec DeleteProvisionedProductPlan
readList :: ReadS [DeleteProvisionedProductPlan]
$creadList :: ReadS [DeleteProvisionedProductPlan]
readsPrec :: Int -> ReadS DeleteProvisionedProductPlan
$creadsPrec :: Int -> ReadS DeleteProvisionedProductPlan
Prelude.Read, Int -> DeleteProvisionedProductPlan -> ShowS
[DeleteProvisionedProductPlan] -> ShowS
DeleteProvisionedProductPlan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteProvisionedProductPlan] -> ShowS
$cshowList :: [DeleteProvisionedProductPlan] -> ShowS
show :: DeleteProvisionedProductPlan -> String
$cshow :: DeleteProvisionedProductPlan -> String
showsPrec :: Int -> DeleteProvisionedProductPlan -> ShowS
$cshowsPrec :: Int -> DeleteProvisionedProductPlan -> ShowS
Prelude.Show, forall x.
Rep DeleteProvisionedProductPlan x -> DeleteProvisionedProductPlan
forall x.
DeleteProvisionedProductPlan -> Rep DeleteProvisionedProductPlan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteProvisionedProductPlan x -> DeleteProvisionedProductPlan
$cfrom :: forall x.
DeleteProvisionedProductPlan -> Rep DeleteProvisionedProductPlan x
Prelude.Generic)

-- |
-- Create a value of 'DeleteProvisionedProductPlan' 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:
--
-- 'acceptLanguage', 'deleteProvisionedProductPlan_acceptLanguage' - The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
--
-- 'ignoreErrors', 'deleteProvisionedProductPlan_ignoreErrors' - If set to true, Service Catalog stops managing the specified provisioned
-- product even if it cannot delete the underlying resources.
--
-- 'planId', 'deleteProvisionedProductPlan_planId' - The plan identifier.
newDeleteProvisionedProductPlan ::
  -- | 'planId'
  Prelude.Text ->
  DeleteProvisionedProductPlan
newDeleteProvisionedProductPlan :: Text -> DeleteProvisionedProductPlan
newDeleteProvisionedProductPlan Text
pPlanId_ =
  DeleteProvisionedProductPlan'
    { $sel:acceptLanguage:DeleteProvisionedProductPlan' :: Maybe Text
acceptLanguage =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ignoreErrors:DeleteProvisionedProductPlan' :: Maybe Bool
ignoreErrors = forall a. Maybe a
Prelude.Nothing,
      $sel:planId:DeleteProvisionedProductPlan' :: Text
planId = Text
pPlanId_
    }

-- | The language code.
--
-- -   @en@ - English (default)
--
-- -   @jp@ - Japanese
--
-- -   @zh@ - Chinese
deleteProvisionedProductPlan_acceptLanguage :: Lens.Lens' DeleteProvisionedProductPlan (Prelude.Maybe Prelude.Text)
deleteProvisionedProductPlan_acceptLanguage :: Lens' DeleteProvisionedProductPlan (Maybe Text)
deleteProvisionedProductPlan_acceptLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteProvisionedProductPlan' {Maybe Text
acceptLanguage :: Maybe Text
$sel:acceptLanguage:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Maybe Text
acceptLanguage} -> Maybe Text
acceptLanguage) (\s :: DeleteProvisionedProductPlan
s@DeleteProvisionedProductPlan' {} Maybe Text
a -> DeleteProvisionedProductPlan
s {$sel:acceptLanguage:DeleteProvisionedProductPlan' :: Maybe Text
acceptLanguage = Maybe Text
a} :: DeleteProvisionedProductPlan)

-- | If set to true, Service Catalog stops managing the specified provisioned
-- product even if it cannot delete the underlying resources.
deleteProvisionedProductPlan_ignoreErrors :: Lens.Lens' DeleteProvisionedProductPlan (Prelude.Maybe Prelude.Bool)
deleteProvisionedProductPlan_ignoreErrors :: Lens' DeleteProvisionedProductPlan (Maybe Bool)
deleteProvisionedProductPlan_ignoreErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteProvisionedProductPlan' {Maybe Bool
ignoreErrors :: Maybe Bool
$sel:ignoreErrors:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Maybe Bool
ignoreErrors} -> Maybe Bool
ignoreErrors) (\s :: DeleteProvisionedProductPlan
s@DeleteProvisionedProductPlan' {} Maybe Bool
a -> DeleteProvisionedProductPlan
s {$sel:ignoreErrors:DeleteProvisionedProductPlan' :: Maybe Bool
ignoreErrors = Maybe Bool
a} :: DeleteProvisionedProductPlan)

-- | The plan identifier.
deleteProvisionedProductPlan_planId :: Lens.Lens' DeleteProvisionedProductPlan Prelude.Text
deleteProvisionedProductPlan_planId :: Lens' DeleteProvisionedProductPlan Text
deleteProvisionedProductPlan_planId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteProvisionedProductPlan' {Text
planId :: Text
$sel:planId:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Text
planId} -> Text
planId) (\s :: DeleteProvisionedProductPlan
s@DeleteProvisionedProductPlan' {} Text
a -> DeleteProvisionedProductPlan
s {$sel:planId:DeleteProvisionedProductPlan' :: Text
planId = Text
a} :: DeleteProvisionedProductPlan)

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

instance Prelude.NFData DeleteProvisionedProductPlan where
  rnf :: DeleteProvisionedProductPlan -> ()
rnf DeleteProvisionedProductPlan' {Maybe Bool
Maybe Text
Text
planId :: Text
ignoreErrors :: Maybe Bool
acceptLanguage :: Maybe Text
$sel:planId:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Text
$sel:ignoreErrors:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Maybe Bool
$sel:acceptLanguage:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
acceptLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
ignoreErrors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
planId

instance Data.ToHeaders DeleteProvisionedProductPlan where
  toHeaders :: DeleteProvisionedProductPlan -> 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
"AWS242ServiceCatalogService.DeleteProvisionedProductPlan" ::
                          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 DeleteProvisionedProductPlan where
  toJSON :: DeleteProvisionedProductPlan -> Value
toJSON DeleteProvisionedProductPlan' {Maybe Bool
Maybe Text
Text
planId :: Text
ignoreErrors :: Maybe Bool
acceptLanguage :: Maybe Text
$sel:planId:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Text
$sel:ignoreErrors:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Maybe Bool
$sel:acceptLanguage:DeleteProvisionedProductPlan' :: DeleteProvisionedProductPlan -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AcceptLanguage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
acceptLanguage,
            (Key
"IgnoreErrors" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
ignoreErrors,
            forall a. a -> Maybe a
Prelude.Just (Key
"PlanId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
planId)
          ]
      )

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

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

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

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

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

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