{-# 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.GetLayerVersionByArn
-- 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 a version of an
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-layers.html Lambda layer>,
-- with a link to download the layer archive that\'s valid for 10 minutes.
module Amazonka.Lambda.GetLayerVersionByArn
  ( -- * Creating a Request
    GetLayerVersionByArn (..),
    newGetLayerVersionByArn,

    -- * Request Lenses
    getLayerVersionByArn_arn,

    -- * Destructuring the Response
    GetLayerVersionResponse (..),
    newGetLayerVersionResponse,

    -- * Response Lenses
    getLayerVersionResponse_compatibleArchitectures,
    getLayerVersionResponse_compatibleRuntimes,
    getLayerVersionResponse_content,
    getLayerVersionResponse_createdDate,
    getLayerVersionResponse_description,
    getLayerVersionResponse_layerArn,
    getLayerVersionResponse_layerVersionArn,
    getLayerVersionResponse_licenseInfo,
    getLayerVersionResponse_version,
  )
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:/ 'newGetLayerVersionByArn' smart constructor.
data GetLayerVersionByArn = GetLayerVersionByArn'
  { -- | The ARN of the layer version.
    GetLayerVersionByArn -> Text
arn :: Prelude.Text
  }
  deriving (GetLayerVersionByArn -> GetLayerVersionByArn -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLayerVersionByArn -> GetLayerVersionByArn -> Bool
$c/= :: GetLayerVersionByArn -> GetLayerVersionByArn -> Bool
== :: GetLayerVersionByArn -> GetLayerVersionByArn -> Bool
$c== :: GetLayerVersionByArn -> GetLayerVersionByArn -> Bool
Prelude.Eq, ReadPrec [GetLayerVersionByArn]
ReadPrec GetLayerVersionByArn
Int -> ReadS GetLayerVersionByArn
ReadS [GetLayerVersionByArn]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetLayerVersionByArn]
$creadListPrec :: ReadPrec [GetLayerVersionByArn]
readPrec :: ReadPrec GetLayerVersionByArn
$creadPrec :: ReadPrec GetLayerVersionByArn
readList :: ReadS [GetLayerVersionByArn]
$creadList :: ReadS [GetLayerVersionByArn]
readsPrec :: Int -> ReadS GetLayerVersionByArn
$creadsPrec :: Int -> ReadS GetLayerVersionByArn
Prelude.Read, Int -> GetLayerVersionByArn -> ShowS
[GetLayerVersionByArn] -> ShowS
GetLayerVersionByArn -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLayerVersionByArn] -> ShowS
$cshowList :: [GetLayerVersionByArn] -> ShowS
show :: GetLayerVersionByArn -> String
$cshow :: GetLayerVersionByArn -> String
showsPrec :: Int -> GetLayerVersionByArn -> ShowS
$cshowsPrec :: Int -> GetLayerVersionByArn -> ShowS
Prelude.Show, forall x. Rep GetLayerVersionByArn x -> GetLayerVersionByArn
forall x. GetLayerVersionByArn -> Rep GetLayerVersionByArn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLayerVersionByArn x -> GetLayerVersionByArn
$cfrom :: forall x. GetLayerVersionByArn -> Rep GetLayerVersionByArn x
Prelude.Generic)

-- |
-- Create a value of 'GetLayerVersionByArn' 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:
--
-- 'arn', 'getLayerVersionByArn_arn' - The ARN of the layer version.
newGetLayerVersionByArn ::
  -- | 'arn'
  Prelude.Text ->
  GetLayerVersionByArn
newGetLayerVersionByArn :: Text -> GetLayerVersionByArn
newGetLayerVersionByArn Text
pArn_ =
  GetLayerVersionByArn' {$sel:arn:GetLayerVersionByArn' :: Text
arn = Text
pArn_}

-- | The ARN of the layer version.
getLayerVersionByArn_arn :: Lens.Lens' GetLayerVersionByArn Prelude.Text
getLayerVersionByArn_arn :: Lens' GetLayerVersionByArn Text
getLayerVersionByArn_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetLayerVersionByArn' {Text
arn :: Text
$sel:arn:GetLayerVersionByArn' :: GetLayerVersionByArn -> Text
arn} -> Text
arn) (\s :: GetLayerVersionByArn
s@GetLayerVersionByArn' {} Text
a -> GetLayerVersionByArn
s {$sel:arn:GetLayerVersionByArn' :: Text
arn = Text
a} :: GetLayerVersionByArn)

instance Core.AWSRequest GetLayerVersionByArn where
  type
    AWSResponse GetLayerVersionByArn =
      GetLayerVersionResponse
  request :: (Service -> Service)
-> GetLayerVersionByArn -> Request GetLayerVersionByArn
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 GetLayerVersionByArn
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetLayerVersionByArn)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable GetLayerVersionByArn where
  hashWithSalt :: Int -> GetLayerVersionByArn -> Int
hashWithSalt Int
_salt GetLayerVersionByArn' {Text
arn :: Text
$sel:arn:GetLayerVersionByArn' :: GetLayerVersionByArn -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn

instance Prelude.NFData GetLayerVersionByArn where
  rnf :: GetLayerVersionByArn -> ()
rnf GetLayerVersionByArn' {Text
arn :: Text
$sel:arn:GetLayerVersionByArn' :: GetLayerVersionByArn -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
arn

instance Data.ToHeaders GetLayerVersionByArn where
  toHeaders :: GetLayerVersionByArn -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath GetLayerVersionByArn where
  toPath :: GetLayerVersionByArn -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2018-10-31/layers"

instance Data.ToQuery GetLayerVersionByArn where
  toQuery :: GetLayerVersionByArn -> QueryString
toQuery GetLayerVersionByArn' {Text
arn :: Text
$sel:arn:GetLayerVersionByArn' :: GetLayerVersionByArn -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"Arn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
arn, QueryString
"find=LayerVersion"]