{-# 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.CloudFront.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 CloudFront function.
--
-- You cannot delete a function if it\'s associated with a cache behavior.
-- First, update your distributions to remove the function association from
-- all cache behaviors, then delete the function.
--
-- To delete a function, you must provide the function\'s name and version
-- (@ETag@ value). To get these values, you can use @ListFunctions@ and
-- @DescribeFunction@.
module Amazonka.CloudFront.DeleteFunction
  ( -- * Creating a Request
    DeleteFunction (..),
    newDeleteFunction,

    -- * Request Lenses
    deleteFunction_ifMatch,
    deleteFunction_name,

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

import Amazonka.CloudFront.Types
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

-- | /See:/ 'newDeleteFunction' smart constructor.
data DeleteFunction = DeleteFunction'
  { -- | The current version (@ETag@ value) of the function that you are
    -- deleting, which you can get using @DescribeFunction@.
    DeleteFunction -> Text
ifMatch :: Prelude.Text,
    -- | The name of the function that you are deleting.
    DeleteFunction -> Text
name :: 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:
--
-- 'ifMatch', 'deleteFunction_ifMatch' - The current version (@ETag@ value) of the function that you are
-- deleting, which you can get using @DescribeFunction@.
--
-- 'name', 'deleteFunction_name' - The name of the function that you are deleting.
newDeleteFunction ::
  -- | 'ifMatch'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  DeleteFunction
newDeleteFunction :: Text -> Text -> DeleteFunction
newDeleteFunction Text
pIfMatch_ Text
pName_ =
  DeleteFunction' {$sel:ifMatch:DeleteFunction' :: Text
ifMatch = Text
pIfMatch_, $sel:name:DeleteFunction' :: Text
name = Text
pName_}

-- | The current version (@ETag@ value) of the function that you are
-- deleting, which you can get using @DescribeFunction@.
deleteFunction_ifMatch :: Lens.Lens' DeleteFunction Prelude.Text
deleteFunction_ifMatch :: Lens' DeleteFunction Text
deleteFunction_ifMatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFunction' {Text
ifMatch :: Text
$sel:ifMatch:DeleteFunction' :: DeleteFunction -> Text
ifMatch} -> Text
ifMatch) (\s :: DeleteFunction
s@DeleteFunction' {} Text
a -> DeleteFunction
s {$sel:ifMatch:DeleteFunction' :: Text
ifMatch = Text
a} :: DeleteFunction)

-- | The name of the function that you are deleting.
deleteFunction_name :: Lens.Lens' DeleteFunction Prelude.Text
deleteFunction_name :: Lens' DeleteFunction Text
deleteFunction_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFunction' {Text
name :: Text
$sel:name:DeleteFunction' :: DeleteFunction -> Text
name} -> Text
name) (\s :: DeleteFunction
s@DeleteFunction' {} Text
a -> DeleteFunction
s {$sel:name:DeleteFunction' :: Text
name = 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' {Text
name :: Text
ifMatch :: Text
$sel:name:DeleteFunction' :: DeleteFunction -> Text
$sel:ifMatch:DeleteFunction' :: DeleteFunction -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ifMatch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders DeleteFunction where
  toHeaders :: DeleteFunction -> [Header]
toHeaders DeleteFunction' {Text
name :: Text
ifMatch :: Text
$sel:name:DeleteFunction' :: DeleteFunction -> Text
$sel:ifMatch:DeleteFunction' :: DeleteFunction -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [HeaderName
"If-Match" forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Text
ifMatch]

instance Data.ToPath DeleteFunction where
  toPath :: DeleteFunction -> ByteString
toPath DeleteFunction' {Text
name :: Text
ifMatch :: Text
$sel:name:DeleteFunction' :: DeleteFunction -> Text
$sel:ifMatch:DeleteFunction' :: DeleteFunction -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2020-05-31/function/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

-- | /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
_ = ()