{-# 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.LicenseManager.DeleteLicenseConfiguration
-- 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 license configuration.
--
-- You cannot delete a license configuration that is in use.
module Amazonka.LicenseManager.DeleteLicenseConfiguration
  ( -- * Creating a Request
    DeleteLicenseConfiguration (..),
    newDeleteLicenseConfiguration,

    -- * Request Lenses
    deleteLicenseConfiguration_licenseConfigurationArn,

    -- * Destructuring the Response
    DeleteLicenseConfigurationResponse (..),
    newDeleteLicenseConfigurationResponse,

    -- * Response Lenses
    deleteLicenseConfigurationResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeleteLicenseConfiguration' 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:
--
-- 'licenseConfigurationArn', 'deleteLicenseConfiguration_licenseConfigurationArn' - ID of the license configuration.
newDeleteLicenseConfiguration ::
  -- | 'licenseConfigurationArn'
  Prelude.Text ->
  DeleteLicenseConfiguration
newDeleteLicenseConfiguration :: Text -> DeleteLicenseConfiguration
newDeleteLicenseConfiguration
  Text
pLicenseConfigurationArn_ =
    DeleteLicenseConfiguration'
      { $sel:licenseConfigurationArn:DeleteLicenseConfiguration' :: Text
licenseConfigurationArn =
          Text
pLicenseConfigurationArn_
      }

-- | ID of the license configuration.
deleteLicenseConfiguration_licenseConfigurationArn :: Lens.Lens' DeleteLicenseConfiguration Prelude.Text
deleteLicenseConfiguration_licenseConfigurationArn :: Lens' DeleteLicenseConfiguration Text
deleteLicenseConfiguration_licenseConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLicenseConfiguration' {Text
licenseConfigurationArn :: Text
$sel:licenseConfigurationArn:DeleteLicenseConfiguration' :: DeleteLicenseConfiguration -> Text
licenseConfigurationArn} -> Text
licenseConfigurationArn) (\s :: DeleteLicenseConfiguration
s@DeleteLicenseConfiguration' {} Text
a -> DeleteLicenseConfiguration
s {$sel:licenseConfigurationArn:DeleteLicenseConfiguration' :: Text
licenseConfigurationArn = Text
a} :: DeleteLicenseConfiguration)

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

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

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

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

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

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

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

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

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