{-# 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.Lambda.DeleteFunction
-- 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 Lambda function. To delete a specific function version, use
-- the @Qualifier@ parameter. Otherwise, all versions and aliases are
-- deleted.
--
-- To delete Lambda event source mappings that invoke a function, use
-- DeleteEventSourceMapping. For Amazon Web Services and resources that
-- invoke your function directly, delete the trigger in the service where
-- you originally configured it.
module Amazonka.Lambda.DeleteFunction
  ( -- * Creating a Request
    DeleteFunction (..),
    newDeleteFunction,

    -- * Request Lenses
    deleteFunction_qualifier,
    deleteFunction_functionName,

    -- * Destructuring the Response
    DeleteFunctionResponse (..),
    newDeleteFunctionResponse,
  )
where

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

-- | /See:/ 'newDeleteFunction' smart constructor.
data DeleteFunction = DeleteFunction'
  { -- | Specify a version to delete. You can\'t delete a version that an alias
    -- references.
    DeleteFunction -> Maybe Text
qualifier :: Prelude.Maybe Prelude.Text,
    -- | The name of the Lambda function or version.
    --
    -- __Name formats__
    --
    -- -   __Function name__ – @my-function@ (name-only), @my-function:1@ (with
    --     version).
    --
    -- -   __Function ARN__ –
    --     @arn:aws:lambda:us-west-2:123456789012:function:my-function@.
    --
    -- -   __Partial ARN__ – @123456789012:function:my-function@.
    --
    -- You can append a version number or alias to any of the formats. The
    -- length constraint applies only to the full ARN. If you specify only the
    -- function name, it is limited to 64 characters in length.
    DeleteFunction -> Text
functionName :: Prelude.Text
  }
  deriving (DeleteFunction -> DeleteFunction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFunction -> DeleteFunction -> Bool
$c/= :: DeleteFunction -> DeleteFunction -> Bool
== :: DeleteFunction -> DeleteFunction -> Bool
$c== :: DeleteFunction -> DeleteFunction -> Bool
Prelude.Eq, ReadPrec [DeleteFunction]
ReadPrec DeleteFunction
Int -> ReadS DeleteFunction
ReadS [DeleteFunction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteFunction]
$creadListPrec :: ReadPrec [DeleteFunction]
readPrec :: ReadPrec DeleteFunction
$creadPrec :: ReadPrec DeleteFunction
readList :: ReadS [DeleteFunction]
$creadList :: ReadS [DeleteFunction]
readsPrec :: Int -> ReadS DeleteFunction
$creadsPrec :: Int -> ReadS DeleteFunction
Prelude.Read, Int -> DeleteFunction -> ShowS
[DeleteFunction] -> ShowS
DeleteFunction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFunction] -> ShowS
$cshowList :: [DeleteFunction] -> ShowS
show :: DeleteFunction -> String
$cshow :: DeleteFunction -> String
showsPrec :: Int -> DeleteFunction -> ShowS
$cshowsPrec :: Int -> DeleteFunction -> ShowS
Prelude.Show, forall x. Rep DeleteFunction x -> DeleteFunction
forall x. DeleteFunction -> Rep DeleteFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFunction x -> DeleteFunction
$cfrom :: forall x. DeleteFunction -> Rep DeleteFunction x
Prelude.Generic)

-- |
-- Create a value of 'DeleteFunction' 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:
--
-- 'qualifier', 'deleteFunction_qualifier' - Specify a version to delete. You can\'t delete a version that an alias
-- references.
--
-- 'functionName', 'deleteFunction_functionName' - The name of the Lambda function or version.
--
-- __Name formats__
--
-- -   __Function name__ – @my-function@ (name-only), @my-function:1@ (with
--     version).
--
-- -   __Function ARN__ –
--     @arn:aws:lambda:us-west-2:123456789012:function:my-function@.
--
-- -   __Partial ARN__ – @123456789012:function:my-function@.
--
-- You can append a version number or alias to any of the formats. The
-- length constraint applies only to the full ARN. If you specify only the
-- function name, it is limited to 64 characters in length.
newDeleteFunction ::
  -- | 'functionName'
  Prelude.Text ->
  DeleteFunction
newDeleteFunction :: Text -> DeleteFunction
newDeleteFunction Text
pFunctionName_ =
  DeleteFunction'
    { $sel:qualifier:DeleteFunction' :: Maybe Text
qualifier = forall a. Maybe a
Prelude.Nothing,
      $sel:functionName:DeleteFunction' :: Text
functionName = Text
pFunctionName_
    }

-- | Specify a version to delete. You can\'t delete a version that an alias
-- references.
deleteFunction_qualifier :: Lens.Lens' DeleteFunction (Prelude.Maybe Prelude.Text)
deleteFunction_qualifier :: Lens' DeleteFunction (Maybe Text)
deleteFunction_qualifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFunction' {Maybe Text
qualifier :: Maybe Text
$sel:qualifier:DeleteFunction' :: DeleteFunction -> Maybe Text
qualifier} -> Maybe Text
qualifier) (\s :: DeleteFunction
s@DeleteFunction' {} Maybe Text
a -> DeleteFunction
s {$sel:qualifier:DeleteFunction' :: Maybe Text
qualifier = Maybe Text
a} :: DeleteFunction)

-- | The name of the Lambda function or version.
--
-- __Name formats__
--
-- -   __Function name__ – @my-function@ (name-only), @my-function:1@ (with
--     version).
--
-- -   __Function ARN__ –
--     @arn:aws:lambda:us-west-2:123456789012:function:my-function@.
--
-- -   __Partial ARN__ – @123456789012:function:my-function@.
--
-- You can append a version number or alias to any of the formats. The
-- length constraint applies only to the full ARN. If you specify only the
-- function name, it is limited to 64 characters in length.
deleteFunction_functionName :: Lens.Lens' DeleteFunction Prelude.Text
deleteFunction_functionName :: Lens' DeleteFunction Text
deleteFunction_functionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFunction' {Text
functionName :: Text
$sel:functionName:DeleteFunction' :: DeleteFunction -> Text
functionName} -> Text
functionName) (\s :: DeleteFunction
s@DeleteFunction' {} Text
a -> DeleteFunction
s {$sel:functionName:DeleteFunction' :: Text
functionName = Text
a} :: DeleteFunction)

instance Core.AWSRequest DeleteFunction where
  type
    AWSResponse DeleteFunction =
      DeleteFunctionResponse
  request :: (Service -> Service) -> DeleteFunction -> Request DeleteFunction
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 DeleteFunction
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteFunction)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteFunctionResponse
DeleteFunctionResponse'

instance Prelude.Hashable DeleteFunction where
  hashWithSalt :: Int -> DeleteFunction -> Int
hashWithSalt Int
_salt DeleteFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:DeleteFunction' :: DeleteFunction -> Text
$sel:qualifier:DeleteFunction' :: DeleteFunction -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
qualifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
functionName

instance Prelude.NFData DeleteFunction where
  rnf :: DeleteFunction -> ()
rnf DeleteFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:DeleteFunction' :: DeleteFunction -> Text
$sel:qualifier:DeleteFunction' :: DeleteFunction -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
qualifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
functionName

instance Data.ToHeaders DeleteFunction where
  toHeaders :: DeleteFunction -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeleteFunction where
  toPath :: DeleteFunction -> ByteString
toPath DeleteFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:DeleteFunction' :: DeleteFunction -> Text
$sel:qualifier:DeleteFunction' :: DeleteFunction -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2015-03-31/functions/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
functionName]

instance Data.ToQuery DeleteFunction where
  toQuery :: DeleteFunction -> QueryString
toQuery DeleteFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:DeleteFunction' :: DeleteFunction -> Text
$sel:qualifier:DeleteFunction' :: DeleteFunction -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"Qualifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
qualifier]

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

-- |
-- Create a value of 'DeleteFunctionResponse' 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.
newDeleteFunctionResponse ::
  DeleteFunctionResponse
newDeleteFunctionResponse :: DeleteFunctionResponse
newDeleteFunctionResponse = DeleteFunctionResponse
DeleteFunctionResponse'

instance Prelude.NFData DeleteFunctionResponse where
  rnf :: DeleteFunctionResponse -> ()
rnf DeleteFunctionResponse
_ = ()