{-# 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.RemovePermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Revokes function-use permission from an Amazon Web Service or another
-- Amazon Web Services account. You can get the ID of the statement from
-- the output of GetPolicy.
module Amazonka.Lambda.RemovePermission
  ( -- * Creating a Request
    RemovePermission (..),
    newRemovePermission,

    -- * Request Lenses
    removePermission_qualifier,
    removePermission_revisionId,
    removePermission_functionName,
    removePermission_statementId,

    -- * Destructuring the Response
    RemovePermissionResponse (..),
    newRemovePermissionResponse,
  )
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:/ 'newRemovePermission' smart constructor.
data RemovePermission = RemovePermission'
  { -- | Specify a version or alias to remove permissions from a published
    -- version of the function.
    RemovePermission -> Maybe Text
qualifier :: Prelude.Maybe Prelude.Text,
    -- | Update the policy only if the revision ID matches the ID that\'s
    -- specified. Use this option to avoid modifying a policy that has changed
    -- since you last read it.
    RemovePermission -> Maybe Text
revisionId :: Prelude.Maybe Prelude.Text,
    -- | The name of the Lambda function, version, or alias.
    --
    -- __Name formats__
    --
    -- -   __Function name__ – @my-function@ (name-only), @my-function:v1@
    --     (with alias).
    --
    -- -   __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.
    RemovePermission -> Text
functionName :: Prelude.Text,
    -- | Statement ID of the permission to remove.
    RemovePermission -> Text
statementId :: Prelude.Text
  }
  deriving (RemovePermission -> RemovePermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemovePermission -> RemovePermission -> Bool
$c/= :: RemovePermission -> RemovePermission -> Bool
== :: RemovePermission -> RemovePermission -> Bool
$c== :: RemovePermission -> RemovePermission -> Bool
Prelude.Eq, ReadPrec [RemovePermission]
ReadPrec RemovePermission
Int -> ReadS RemovePermission
ReadS [RemovePermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemovePermission]
$creadListPrec :: ReadPrec [RemovePermission]
readPrec :: ReadPrec RemovePermission
$creadPrec :: ReadPrec RemovePermission
readList :: ReadS [RemovePermission]
$creadList :: ReadS [RemovePermission]
readsPrec :: Int -> ReadS RemovePermission
$creadsPrec :: Int -> ReadS RemovePermission
Prelude.Read, Int -> RemovePermission -> ShowS
[RemovePermission] -> ShowS
RemovePermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemovePermission] -> ShowS
$cshowList :: [RemovePermission] -> ShowS
show :: RemovePermission -> String
$cshow :: RemovePermission -> String
showsPrec :: Int -> RemovePermission -> ShowS
$cshowsPrec :: Int -> RemovePermission -> ShowS
Prelude.Show, forall x. Rep RemovePermission x -> RemovePermission
forall x. RemovePermission -> Rep RemovePermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemovePermission x -> RemovePermission
$cfrom :: forall x. RemovePermission -> Rep RemovePermission x
Prelude.Generic)

-- |
-- Create a value of 'RemovePermission' 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', 'removePermission_qualifier' - Specify a version or alias to remove permissions from a published
-- version of the function.
--
-- 'revisionId', 'removePermission_revisionId' - Update the policy only if the revision ID matches the ID that\'s
-- specified. Use this option to avoid modifying a policy that has changed
-- since you last read it.
--
-- 'functionName', 'removePermission_functionName' - The name of the Lambda function, version, or alias.
--
-- __Name formats__
--
-- -   __Function name__ – @my-function@ (name-only), @my-function:v1@
--     (with alias).
--
-- -   __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.
--
-- 'statementId', 'removePermission_statementId' - Statement ID of the permission to remove.
newRemovePermission ::
  -- | 'functionName'
  Prelude.Text ->
  -- | 'statementId'
  Prelude.Text ->
  RemovePermission
newRemovePermission :: Text -> Text -> RemovePermission
newRemovePermission Text
pFunctionName_ Text
pStatementId_ =
  RemovePermission'
    { $sel:qualifier:RemovePermission' :: Maybe Text
qualifier = forall a. Maybe a
Prelude.Nothing,
      $sel:revisionId:RemovePermission' :: Maybe Text
revisionId = forall a. Maybe a
Prelude.Nothing,
      $sel:functionName:RemovePermission' :: Text
functionName = Text
pFunctionName_,
      $sel:statementId:RemovePermission' :: Text
statementId = Text
pStatementId_
    }

-- | Specify a version or alias to remove permissions from a published
-- version of the function.
removePermission_qualifier :: Lens.Lens' RemovePermission (Prelude.Maybe Prelude.Text)
removePermission_qualifier :: Lens' RemovePermission (Maybe Text)
removePermission_qualifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Maybe Text
qualifier :: Maybe Text
$sel:qualifier:RemovePermission' :: RemovePermission -> Maybe Text
qualifier} -> Maybe Text
qualifier) (\s :: RemovePermission
s@RemovePermission' {} Maybe Text
a -> RemovePermission
s {$sel:qualifier:RemovePermission' :: Maybe Text
qualifier = Maybe Text
a} :: RemovePermission)

-- | Update the policy only if the revision ID matches the ID that\'s
-- specified. Use this option to avoid modifying a policy that has changed
-- since you last read it.
removePermission_revisionId :: Lens.Lens' RemovePermission (Prelude.Maybe Prelude.Text)
removePermission_revisionId :: Lens' RemovePermission (Maybe Text)
removePermission_revisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Maybe Text
revisionId :: Maybe Text
$sel:revisionId:RemovePermission' :: RemovePermission -> Maybe Text
revisionId} -> Maybe Text
revisionId) (\s :: RemovePermission
s@RemovePermission' {} Maybe Text
a -> RemovePermission
s {$sel:revisionId:RemovePermission' :: Maybe Text
revisionId = Maybe Text
a} :: RemovePermission)

-- | The name of the Lambda function, version, or alias.
--
-- __Name formats__
--
-- -   __Function name__ – @my-function@ (name-only), @my-function:v1@
--     (with alias).
--
-- -   __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.
removePermission_functionName :: Lens.Lens' RemovePermission Prelude.Text
removePermission_functionName :: Lens' RemovePermission Text
removePermission_functionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Text
functionName :: Text
$sel:functionName:RemovePermission' :: RemovePermission -> Text
functionName} -> Text
functionName) (\s :: RemovePermission
s@RemovePermission' {} Text
a -> RemovePermission
s {$sel:functionName:RemovePermission' :: Text
functionName = Text
a} :: RemovePermission)

-- | Statement ID of the permission to remove.
removePermission_statementId :: Lens.Lens' RemovePermission Prelude.Text
removePermission_statementId :: Lens' RemovePermission Text
removePermission_statementId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Text
statementId :: Text
$sel:statementId:RemovePermission' :: RemovePermission -> Text
statementId} -> Text
statementId) (\s :: RemovePermission
s@RemovePermission' {} Text
a -> RemovePermission
s {$sel:statementId:RemovePermission' :: Text
statementId = Text
a} :: RemovePermission)

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

instance Prelude.Hashable RemovePermission where
  hashWithSalt :: Int -> RemovePermission -> Int
hashWithSalt Int
_salt RemovePermission' {Maybe Text
Text
statementId :: Text
functionName :: Text
revisionId :: Maybe Text
qualifier :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Text
$sel:functionName:RemovePermission' :: RemovePermission -> Text
$sel:revisionId:RemovePermission' :: RemovePermission -> Maybe Text
$sel:qualifier:RemovePermission' :: RemovePermission -> 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` Maybe Text
revisionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
functionName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
statementId

instance Prelude.NFData RemovePermission where
  rnf :: RemovePermission -> ()
rnf RemovePermission' {Maybe Text
Text
statementId :: Text
functionName :: Text
revisionId :: Maybe Text
qualifier :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Text
$sel:functionName:RemovePermission' :: RemovePermission -> Text
$sel:revisionId:RemovePermission' :: RemovePermission -> Maybe Text
$sel:qualifier:RemovePermission' :: RemovePermission -> 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 Maybe Text
revisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
functionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
statementId

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

instance Data.ToPath RemovePermission where
  toPath :: RemovePermission -> ByteString
toPath RemovePermission' {Maybe Text
Text
statementId :: Text
functionName :: Text
revisionId :: Maybe Text
qualifier :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Text
$sel:functionName:RemovePermission' :: RemovePermission -> Text
$sel:revisionId:RemovePermission' :: RemovePermission -> Maybe Text
$sel:qualifier:RemovePermission' :: RemovePermission -> 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,
        ByteString
"/policy/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
statementId
      ]

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

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

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

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