{-# 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.GetPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the
-- <https://docs.aws.amazon.com/lambda/latest/dg/access-control-resource-based.html resource-based IAM policy>
-- for a function, version, or alias.
module Amazonka.Lambda.GetPolicy
  ( -- * Creating a Request
    GetPolicy (..),
    newGetPolicy,

    -- * Request Lenses
    getPolicy_qualifier,
    getPolicy_functionName,

    -- * Destructuring the Response
    GetPolicyResponse (..),
    newGetPolicyResponse,

    -- * Response Lenses
    getPolicyResponse_policy,
    getPolicyResponse_revisionId,
    getPolicyResponse_httpStatus,
  )
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:/ 'newGetPolicy' smart constructor.
data GetPolicy = GetPolicy'
  { -- | Specify a version or alias to get the policy for that resource.
    GetPolicy -> Maybe Text
qualifier :: 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.
    GetPolicy -> Text
functionName :: Prelude.Text
  }
  deriving (GetPolicy -> GetPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPolicy -> GetPolicy -> Bool
$c/= :: GetPolicy -> GetPolicy -> Bool
== :: GetPolicy -> GetPolicy -> Bool
$c== :: GetPolicy -> GetPolicy -> Bool
Prelude.Eq, ReadPrec [GetPolicy]
ReadPrec GetPolicy
Int -> ReadS GetPolicy
ReadS [GetPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPolicy]
$creadListPrec :: ReadPrec [GetPolicy]
readPrec :: ReadPrec GetPolicy
$creadPrec :: ReadPrec GetPolicy
readList :: ReadS [GetPolicy]
$creadList :: ReadS [GetPolicy]
readsPrec :: Int -> ReadS GetPolicy
$creadsPrec :: Int -> ReadS GetPolicy
Prelude.Read, Int -> GetPolicy -> ShowS
[GetPolicy] -> ShowS
GetPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPolicy] -> ShowS
$cshowList :: [GetPolicy] -> ShowS
show :: GetPolicy -> String
$cshow :: GetPolicy -> String
showsPrec :: Int -> GetPolicy -> ShowS
$cshowsPrec :: Int -> GetPolicy -> ShowS
Prelude.Show, forall x. Rep GetPolicy x -> GetPolicy
forall x. GetPolicy -> Rep GetPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPolicy x -> GetPolicy
$cfrom :: forall x. GetPolicy -> Rep GetPolicy x
Prelude.Generic)

-- |
-- Create a value of 'GetPolicy' 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', 'getPolicy_qualifier' - Specify a version or alias to get the policy for that resource.
--
-- 'functionName', 'getPolicy_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.
newGetPolicy ::
  -- | 'functionName'
  Prelude.Text ->
  GetPolicy
newGetPolicy :: Text -> GetPolicy
newGetPolicy Text
pFunctionName_ =
  GetPolicy'
    { $sel:qualifier:GetPolicy' :: Maybe Text
qualifier = forall a. Maybe a
Prelude.Nothing,
      $sel:functionName:GetPolicy' :: Text
functionName = Text
pFunctionName_
    }

-- | Specify a version or alias to get the policy for that resource.
getPolicy_qualifier :: Lens.Lens' GetPolicy (Prelude.Maybe Prelude.Text)
getPolicy_qualifier :: Lens' GetPolicy (Maybe Text)
getPolicy_qualifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicy' {Maybe Text
qualifier :: Maybe Text
$sel:qualifier:GetPolicy' :: GetPolicy -> Maybe Text
qualifier} -> Maybe Text
qualifier) (\s :: GetPolicy
s@GetPolicy' {} Maybe Text
a -> GetPolicy
s {$sel:qualifier:GetPolicy' :: Maybe Text
qualifier = Maybe Text
a} :: GetPolicy)

-- | 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.
getPolicy_functionName :: Lens.Lens' GetPolicy Prelude.Text
getPolicy_functionName :: Lens' GetPolicy Text
getPolicy_functionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicy' {Text
functionName :: Text
$sel:functionName:GetPolicy' :: GetPolicy -> Text
functionName} -> Text
functionName) (\s :: GetPolicy
s@GetPolicy' {} Text
a -> GetPolicy
s {$sel:functionName:GetPolicy' :: Text
functionName = Text
a} :: GetPolicy)

instance Core.AWSRequest GetPolicy where
  type AWSResponse GetPolicy = GetPolicyResponse
  request :: (Service -> Service) -> GetPolicy -> Request GetPolicy
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetPolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetPolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe Text -> Int -> GetPolicyResponse
GetPolicyResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Policy")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RevisionId")
            forall (f :: * -> *) a b. Applicative f => 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 GetPolicy where
  hashWithSalt :: Int -> GetPolicy -> Int
hashWithSalt Int
_salt GetPolicy' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetPolicy' :: GetPolicy -> Text
$sel:qualifier:GetPolicy' :: GetPolicy -> 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 GetPolicy where
  rnf :: GetPolicy -> ()
rnf GetPolicy' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetPolicy' :: GetPolicy -> Text
$sel:qualifier:GetPolicy' :: GetPolicy -> 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 GetPolicy where
  toHeaders :: GetPolicy -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetPolicy where
  toPath :: GetPolicy -> ByteString
toPath GetPolicy' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetPolicy' :: GetPolicy -> Text
$sel:qualifier:GetPolicy' :: GetPolicy -> 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"
      ]

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

-- | /See:/ 'newGetPolicyResponse' smart constructor.
data GetPolicyResponse = GetPolicyResponse'
  { -- | The resource-based policy.
    GetPolicyResponse -> Maybe Text
policy :: Prelude.Maybe Prelude.Text,
    -- | A unique identifier for the current revision of the policy.
    GetPolicyResponse -> Maybe Text
revisionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetPolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetPolicyResponse -> GetPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPolicyResponse -> GetPolicyResponse -> Bool
$c/= :: GetPolicyResponse -> GetPolicyResponse -> Bool
== :: GetPolicyResponse -> GetPolicyResponse -> Bool
$c== :: GetPolicyResponse -> GetPolicyResponse -> Bool
Prelude.Eq, ReadPrec [GetPolicyResponse]
ReadPrec GetPolicyResponse
Int -> ReadS GetPolicyResponse
ReadS [GetPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPolicyResponse]
$creadListPrec :: ReadPrec [GetPolicyResponse]
readPrec :: ReadPrec GetPolicyResponse
$creadPrec :: ReadPrec GetPolicyResponse
readList :: ReadS [GetPolicyResponse]
$creadList :: ReadS [GetPolicyResponse]
readsPrec :: Int -> ReadS GetPolicyResponse
$creadsPrec :: Int -> ReadS GetPolicyResponse
Prelude.Read, Int -> GetPolicyResponse -> ShowS
[GetPolicyResponse] -> ShowS
GetPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPolicyResponse] -> ShowS
$cshowList :: [GetPolicyResponse] -> ShowS
show :: GetPolicyResponse -> String
$cshow :: GetPolicyResponse -> String
showsPrec :: Int -> GetPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetPolicyResponse -> ShowS
Prelude.Show, forall x. Rep GetPolicyResponse x -> GetPolicyResponse
forall x. GetPolicyResponse -> Rep GetPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPolicyResponse x -> GetPolicyResponse
$cfrom :: forall x. GetPolicyResponse -> Rep GetPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetPolicyResponse' 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:
--
-- 'policy', 'getPolicyResponse_policy' - The resource-based policy.
--
-- 'revisionId', 'getPolicyResponse_revisionId' - A unique identifier for the current revision of the policy.
--
-- 'httpStatus', 'getPolicyResponse_httpStatus' - The response's http status code.
newGetPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetPolicyResponse
newGetPolicyResponse :: Int -> GetPolicyResponse
newGetPolicyResponse Int
pHttpStatus_ =
  GetPolicyResponse'
    { $sel:policy:GetPolicyResponse' :: Maybe Text
policy = forall a. Maybe a
Prelude.Nothing,
      $sel:revisionId:GetPolicyResponse' :: Maybe Text
revisionId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The resource-based policy.
getPolicyResponse_policy :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_policy :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
policy :: Maybe Text
$sel:policy:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
policy} -> Maybe Text
policy) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:policy:GetPolicyResponse' :: Maybe Text
policy = Maybe Text
a} :: GetPolicyResponse)

-- | A unique identifier for the current revision of the policy.
getPolicyResponse_revisionId :: Lens.Lens' GetPolicyResponse (Prelude.Maybe Prelude.Text)
getPolicyResponse_revisionId :: Lens' GetPolicyResponse (Maybe Text)
getPolicyResponse_revisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyResponse' {Maybe Text
revisionId :: Maybe Text
$sel:revisionId:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
revisionId} -> Maybe Text
revisionId) (\s :: GetPolicyResponse
s@GetPolicyResponse' {} Maybe Text
a -> GetPolicyResponse
s {$sel:revisionId:GetPolicyResponse' :: Maybe Text
revisionId = Maybe Text
a} :: GetPolicyResponse)

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

instance Prelude.NFData GetPolicyResponse where
  rnf :: GetPolicyResponse -> ()
rnf GetPolicyResponse' {Int
Maybe Text
httpStatus :: Int
revisionId :: Maybe Text
policy :: Maybe Text
$sel:httpStatus:GetPolicyResponse' :: GetPolicyResponse -> Int
$sel:revisionId:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
$sel:policy:GetPolicyResponse' :: GetPolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policy
      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 Int
httpStatus