{-# 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.GetFunction
-- 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 information about the function or function version, with a link
-- to download the deployment package that\'s valid for 10 minutes. If you
-- specify a function version, only details that are specific to that
-- version are returned.
module Amazonka.Lambda.GetFunction
  ( -- * Creating a Request
    GetFunction (..),
    newGetFunction,

    -- * Request Lenses
    getFunction_qualifier,
    getFunction_functionName,

    -- * Destructuring the Response
    GetFunctionResponse (..),
    newGetFunctionResponse,

    -- * Response Lenses
    getFunctionResponse_code,
    getFunctionResponse_concurrency,
    getFunctionResponse_configuration,
    getFunctionResponse_tags,
    getFunctionResponse_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:/ 'newGetFunction' smart constructor.
data GetFunction = GetFunction'
  { -- | Specify a version or alias to get details about a published version of
    -- the function.
    GetFunction -> 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.
    GetFunction -> Text
functionName :: Prelude.Text
  }
  deriving (GetFunction -> GetFunction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFunction -> GetFunction -> Bool
$c/= :: GetFunction -> GetFunction -> Bool
== :: GetFunction -> GetFunction -> Bool
$c== :: GetFunction -> GetFunction -> Bool
Prelude.Eq, ReadPrec [GetFunction]
ReadPrec GetFunction
Int -> ReadS GetFunction
ReadS [GetFunction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFunction]
$creadListPrec :: ReadPrec [GetFunction]
readPrec :: ReadPrec GetFunction
$creadPrec :: ReadPrec GetFunction
readList :: ReadS [GetFunction]
$creadList :: ReadS [GetFunction]
readsPrec :: Int -> ReadS GetFunction
$creadsPrec :: Int -> ReadS GetFunction
Prelude.Read, Int -> GetFunction -> ShowS
[GetFunction] -> ShowS
GetFunction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFunction] -> ShowS
$cshowList :: [GetFunction] -> ShowS
show :: GetFunction -> String
$cshow :: GetFunction -> String
showsPrec :: Int -> GetFunction -> ShowS
$cshowsPrec :: Int -> GetFunction -> ShowS
Prelude.Show, forall x. Rep GetFunction x -> GetFunction
forall x. GetFunction -> Rep GetFunction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFunction x -> GetFunction
$cfrom :: forall x. GetFunction -> Rep GetFunction x
Prelude.Generic)

-- |
-- Create a value of 'GetFunction' 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', 'getFunction_qualifier' - Specify a version or alias to get details about a published version of
-- the function.
--
-- 'functionName', 'getFunction_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.
newGetFunction ::
  -- | 'functionName'
  Prelude.Text ->
  GetFunction
newGetFunction :: Text -> GetFunction
newGetFunction Text
pFunctionName_ =
  GetFunction'
    { $sel:qualifier:GetFunction' :: Maybe Text
qualifier = forall a. Maybe a
Prelude.Nothing,
      $sel:functionName:GetFunction' :: Text
functionName = Text
pFunctionName_
    }

-- | Specify a version or alias to get details about a published version of
-- the function.
getFunction_qualifier :: Lens.Lens' GetFunction (Prelude.Maybe Prelude.Text)
getFunction_qualifier :: Lens' GetFunction (Maybe Text)
getFunction_qualifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunction' {Maybe Text
qualifier :: Maybe Text
$sel:qualifier:GetFunction' :: GetFunction -> Maybe Text
qualifier} -> Maybe Text
qualifier) (\s :: GetFunction
s@GetFunction' {} Maybe Text
a -> GetFunction
s {$sel:qualifier:GetFunction' :: Maybe Text
qualifier = Maybe Text
a} :: GetFunction)

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

instance Core.AWSRequest GetFunction where
  type AWSResponse GetFunction = GetFunctionResponse
  request :: (Service -> Service) -> GetFunction -> Request GetFunction
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 GetFunction
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetFunction)))
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 FunctionCodeLocation
-> Maybe Concurrency
-> Maybe FunctionConfiguration
-> Maybe (HashMap Text Text)
-> Int
-> GetFunctionResponse
GetFunctionResponse'
            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
"Code")
            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
"Concurrency")
            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
"Configuration")
            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
"Tags" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 GetFunction where
  hashWithSalt :: Int -> GetFunction -> Int
hashWithSalt Int
_salt GetFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetFunction' :: GetFunction -> Text
$sel:qualifier:GetFunction' :: GetFunction -> 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 GetFunction where
  rnf :: GetFunction -> ()
rnf GetFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetFunction' :: GetFunction -> Text
$sel:qualifier:GetFunction' :: GetFunction -> 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 GetFunction where
  toHeaders :: GetFunction -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetFunction where
  toPath :: GetFunction -> ByteString
toPath GetFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetFunction' :: GetFunction -> Text
$sel:qualifier:GetFunction' :: GetFunction -> 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 GetFunction where
  toQuery :: GetFunction -> QueryString
toQuery GetFunction' {Maybe Text
Text
functionName :: Text
qualifier :: Maybe Text
$sel:functionName:GetFunction' :: GetFunction -> Text
$sel:qualifier:GetFunction' :: GetFunction -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"Qualifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
qualifier]

-- | /See:/ 'newGetFunctionResponse' smart constructor.
data GetFunctionResponse = GetFunctionResponse'
  { -- | The deployment package of the function or version.
    GetFunctionResponse -> Maybe FunctionCodeLocation
code :: Prelude.Maybe FunctionCodeLocation,
    -- | The function\'s
    -- <https://docs.aws.amazon.com/lambda/latest/dg/concurrent-executions.html reserved concurrency>.
    GetFunctionResponse -> Maybe Concurrency
concurrency :: Prelude.Maybe Concurrency,
    -- | The configuration of the function or version.
    GetFunctionResponse -> Maybe FunctionConfiguration
configuration :: Prelude.Maybe FunctionConfiguration,
    -- | The function\'s
    -- <https://docs.aws.amazon.com/lambda/latest/dg/tagging.html tags>.
    GetFunctionResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    GetFunctionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetFunctionResponse -> GetFunctionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFunctionResponse -> GetFunctionResponse -> Bool
$c/= :: GetFunctionResponse -> GetFunctionResponse -> Bool
== :: GetFunctionResponse -> GetFunctionResponse -> Bool
$c== :: GetFunctionResponse -> GetFunctionResponse -> Bool
Prelude.Eq, Int -> GetFunctionResponse -> ShowS
[GetFunctionResponse] -> ShowS
GetFunctionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFunctionResponse] -> ShowS
$cshowList :: [GetFunctionResponse] -> ShowS
show :: GetFunctionResponse -> String
$cshow :: GetFunctionResponse -> String
showsPrec :: Int -> GetFunctionResponse -> ShowS
$cshowsPrec :: Int -> GetFunctionResponse -> ShowS
Prelude.Show, forall x. Rep GetFunctionResponse x -> GetFunctionResponse
forall x. GetFunctionResponse -> Rep GetFunctionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFunctionResponse x -> GetFunctionResponse
$cfrom :: forall x. GetFunctionResponse -> Rep GetFunctionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFunctionResponse' 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:
--
-- 'code', 'getFunctionResponse_code' - The deployment package of the function or version.
--
-- 'concurrency', 'getFunctionResponse_concurrency' - The function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/concurrent-executions.html reserved concurrency>.
--
-- 'configuration', 'getFunctionResponse_configuration' - The configuration of the function or version.
--
-- 'tags', 'getFunctionResponse_tags' - The function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/tagging.html tags>.
--
-- 'httpStatus', 'getFunctionResponse_httpStatus' - The response's http status code.
newGetFunctionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFunctionResponse
newGetFunctionResponse :: Int -> GetFunctionResponse
newGetFunctionResponse Int
pHttpStatus_ =
  GetFunctionResponse'
    { $sel:code:GetFunctionResponse' :: Maybe FunctionCodeLocation
code = forall a. Maybe a
Prelude.Nothing,
      $sel:concurrency:GetFunctionResponse' :: Maybe Concurrency
concurrency = forall a. Maybe a
Prelude.Nothing,
      $sel:configuration:GetFunctionResponse' :: Maybe FunctionConfiguration
configuration = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:GetFunctionResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFunctionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The deployment package of the function or version.
getFunctionResponse_code :: Lens.Lens' GetFunctionResponse (Prelude.Maybe FunctionCodeLocation)
getFunctionResponse_code :: Lens' GetFunctionResponse (Maybe FunctionCodeLocation)
getFunctionResponse_code = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunctionResponse' {Maybe FunctionCodeLocation
code :: Maybe FunctionCodeLocation
$sel:code:GetFunctionResponse' :: GetFunctionResponse -> Maybe FunctionCodeLocation
code} -> Maybe FunctionCodeLocation
code) (\s :: GetFunctionResponse
s@GetFunctionResponse' {} Maybe FunctionCodeLocation
a -> GetFunctionResponse
s {$sel:code:GetFunctionResponse' :: Maybe FunctionCodeLocation
code = Maybe FunctionCodeLocation
a} :: GetFunctionResponse)

-- | The function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/concurrent-executions.html reserved concurrency>.
getFunctionResponse_concurrency :: Lens.Lens' GetFunctionResponse (Prelude.Maybe Concurrency)
getFunctionResponse_concurrency :: Lens' GetFunctionResponse (Maybe Concurrency)
getFunctionResponse_concurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunctionResponse' {Maybe Concurrency
concurrency :: Maybe Concurrency
$sel:concurrency:GetFunctionResponse' :: GetFunctionResponse -> Maybe Concurrency
concurrency} -> Maybe Concurrency
concurrency) (\s :: GetFunctionResponse
s@GetFunctionResponse' {} Maybe Concurrency
a -> GetFunctionResponse
s {$sel:concurrency:GetFunctionResponse' :: Maybe Concurrency
concurrency = Maybe Concurrency
a} :: GetFunctionResponse)

-- | The configuration of the function or version.
getFunctionResponse_configuration :: Lens.Lens' GetFunctionResponse (Prelude.Maybe FunctionConfiguration)
getFunctionResponse_configuration :: Lens' GetFunctionResponse (Maybe FunctionConfiguration)
getFunctionResponse_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunctionResponse' {Maybe FunctionConfiguration
configuration :: Maybe FunctionConfiguration
$sel:configuration:GetFunctionResponse' :: GetFunctionResponse -> Maybe FunctionConfiguration
configuration} -> Maybe FunctionConfiguration
configuration) (\s :: GetFunctionResponse
s@GetFunctionResponse' {} Maybe FunctionConfiguration
a -> GetFunctionResponse
s {$sel:configuration:GetFunctionResponse' :: Maybe FunctionConfiguration
configuration = Maybe FunctionConfiguration
a} :: GetFunctionResponse)

-- | The function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/tagging.html tags>.
getFunctionResponse_tags :: Lens.Lens' GetFunctionResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
getFunctionResponse_tags :: Lens' GetFunctionResponse (Maybe (HashMap Text Text))
getFunctionResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFunctionResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:GetFunctionResponse' :: GetFunctionResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: GetFunctionResponse
s@GetFunctionResponse' {} Maybe (HashMap Text Text)
a -> GetFunctionResponse
s {$sel:tags:GetFunctionResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: GetFunctionResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetFunctionResponse where
  rnf :: GetFunctionResponse -> ()
rnf GetFunctionResponse' {Int
Maybe (HashMap Text Text)
Maybe Concurrency
Maybe FunctionCodeLocation
Maybe FunctionConfiguration
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
configuration :: Maybe FunctionConfiguration
concurrency :: Maybe Concurrency
code :: Maybe FunctionCodeLocation
$sel:httpStatus:GetFunctionResponse' :: GetFunctionResponse -> Int
$sel:tags:GetFunctionResponse' :: GetFunctionResponse -> Maybe (HashMap Text Text)
$sel:configuration:GetFunctionResponse' :: GetFunctionResponse -> Maybe FunctionConfiguration
$sel:concurrency:GetFunctionResponse' :: GetFunctionResponse -> Maybe Concurrency
$sel:code:GetFunctionResponse' :: GetFunctionResponse -> Maybe FunctionCodeLocation
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe FunctionCodeLocation
code
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Concurrency
concurrency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FunctionConfiguration
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus