{-# 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.IAM.GetPolicyVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about the specified version of the specified
-- managed policy, including the policy document.
--
-- Policies returned by this operation are URL-encoded compliant with
-- <https://tools.ietf.org/html/rfc3986 RFC 3986>. You can use a URL
-- decoding method to convert the policy back to plain JSON text. For
-- example, if you use Java, you can use the @decode@ method of the
-- @java.net.URLDecoder@ utility class in the Java SDK. Other languages and
-- SDKs provide similar functionality.
--
-- To list the available versions for a policy, use ListPolicyVersions.
--
-- This operation retrieves information about managed policies. To retrieve
-- information about an inline policy that is embedded in a user, group, or
-- role, use GetUserPolicy, GetGroupPolicy, or GetRolePolicy.
--
-- For more information about the types of policies, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
--
-- For more information about managed policy versions, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-versions.html Versioning for managed policies>
-- in the /IAM User Guide/.
module Amazonka.IAM.GetPolicyVersion
  ( -- * Creating a Request
    GetPolicyVersion (..),
    newGetPolicyVersion,

    -- * Request Lenses
    getPolicyVersion_policyArn,
    getPolicyVersion_versionId,

    -- * Destructuring the Response
    GetPolicyVersionResponse (..),
    newGetPolicyVersionResponse,

    -- * Response Lenses
    getPolicyVersionResponse_policyVersion,
    getPolicyVersionResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IAM.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetPolicyVersion' smart constructor.
data GetPolicyVersion = GetPolicyVersion'
  { -- | The Amazon Resource Name (ARN) of the managed policy that you want
    -- information about.
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    GetPolicyVersion -> Text
policyArn :: Prelude.Text,
    -- | Identifies the policy version to retrieve.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- that consists of the lowercase letter \'v\' followed by one or two
    -- digits, and optionally followed by a period \'.\' and a string of
    -- letters and digits.
    GetPolicyVersion -> Text
versionId :: Prelude.Text
  }
  deriving (GetPolicyVersion -> GetPolicyVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPolicyVersion -> GetPolicyVersion -> Bool
$c/= :: GetPolicyVersion -> GetPolicyVersion -> Bool
== :: GetPolicyVersion -> GetPolicyVersion -> Bool
$c== :: GetPolicyVersion -> GetPolicyVersion -> Bool
Prelude.Eq, ReadPrec [GetPolicyVersion]
ReadPrec GetPolicyVersion
Int -> ReadS GetPolicyVersion
ReadS [GetPolicyVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPolicyVersion]
$creadListPrec :: ReadPrec [GetPolicyVersion]
readPrec :: ReadPrec GetPolicyVersion
$creadPrec :: ReadPrec GetPolicyVersion
readList :: ReadS [GetPolicyVersion]
$creadList :: ReadS [GetPolicyVersion]
readsPrec :: Int -> ReadS GetPolicyVersion
$creadsPrec :: Int -> ReadS GetPolicyVersion
Prelude.Read, Int -> GetPolicyVersion -> ShowS
[GetPolicyVersion] -> ShowS
GetPolicyVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPolicyVersion] -> ShowS
$cshowList :: [GetPolicyVersion] -> ShowS
show :: GetPolicyVersion -> String
$cshow :: GetPolicyVersion -> String
showsPrec :: Int -> GetPolicyVersion -> ShowS
$cshowsPrec :: Int -> GetPolicyVersion -> ShowS
Prelude.Show, forall x. Rep GetPolicyVersion x -> GetPolicyVersion
forall x. GetPolicyVersion -> Rep GetPolicyVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPolicyVersion x -> GetPolicyVersion
$cfrom :: forall x. GetPolicyVersion -> Rep GetPolicyVersion x
Prelude.Generic)

-- |
-- Create a value of 'GetPolicyVersion' 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:
--
-- 'policyArn', 'getPolicyVersion_policyArn' - The Amazon Resource Name (ARN) of the managed policy that you want
-- information about.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
--
-- 'versionId', 'getPolicyVersion_versionId' - Identifies the policy version to retrieve.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- that consists of the lowercase letter \'v\' followed by one or two
-- digits, and optionally followed by a period \'.\' and a string of
-- letters and digits.
newGetPolicyVersion ::
  -- | 'policyArn'
  Prelude.Text ->
  -- | 'versionId'
  Prelude.Text ->
  GetPolicyVersion
newGetPolicyVersion :: Text -> Text -> GetPolicyVersion
newGetPolicyVersion Text
pPolicyArn_ Text
pVersionId_ =
  GetPolicyVersion'
    { $sel:policyArn:GetPolicyVersion' :: Text
policyArn = Text
pPolicyArn_,
      $sel:versionId:GetPolicyVersion' :: Text
versionId = Text
pVersionId_
    }

-- | The Amazon Resource Name (ARN) of the managed policy that you want
-- information about.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
getPolicyVersion_policyArn :: Lens.Lens' GetPolicyVersion Prelude.Text
getPolicyVersion_policyArn :: Lens' GetPolicyVersion Text
getPolicyVersion_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyVersion' {Text
policyArn :: Text
$sel:policyArn:GetPolicyVersion' :: GetPolicyVersion -> Text
policyArn} -> Text
policyArn) (\s :: GetPolicyVersion
s@GetPolicyVersion' {} Text
a -> GetPolicyVersion
s {$sel:policyArn:GetPolicyVersion' :: Text
policyArn = Text
a} :: GetPolicyVersion)

-- | Identifies the policy version to retrieve.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- that consists of the lowercase letter \'v\' followed by one or two
-- digits, and optionally followed by a period \'.\' and a string of
-- letters and digits.
getPolicyVersion_versionId :: Lens.Lens' GetPolicyVersion Prelude.Text
getPolicyVersion_versionId :: Lens' GetPolicyVersion Text
getPolicyVersion_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyVersion' {Text
versionId :: Text
$sel:versionId:GetPolicyVersion' :: GetPolicyVersion -> Text
versionId} -> Text
versionId) (\s :: GetPolicyVersion
s@GetPolicyVersion' {} Text
a -> GetPolicyVersion
s {$sel:versionId:GetPolicyVersion' :: Text
versionId = Text
a} :: GetPolicyVersion)

instance Core.AWSRequest GetPolicyVersion where
  type
    AWSResponse GetPolicyVersion =
      GetPolicyVersionResponse
  request :: (Service -> Service)
-> GetPolicyVersion -> Request GetPolicyVersion
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetPolicyVersion
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetPolicyVersion)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"GetPolicyVersionResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe PolicyVersion -> Int -> GetPolicyVersionResponse
GetPolicyVersionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PolicyVersion")
            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 GetPolicyVersion where
  hashWithSalt :: Int -> GetPolicyVersion -> Int
hashWithSalt Int
_salt GetPolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:GetPolicyVersion' :: GetPolicyVersion -> Text
$sel:policyArn:GetPolicyVersion' :: GetPolicyVersion -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
versionId

instance Prelude.NFData GetPolicyVersion where
  rnf :: GetPolicyVersion -> ()
rnf GetPolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:GetPolicyVersion' :: GetPolicyVersion -> Text
$sel:policyArn:GetPolicyVersion' :: GetPolicyVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
versionId

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

instance Data.ToPath GetPolicyVersion where
  toPath :: GetPolicyVersion -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery GetPolicyVersion where
  toQuery :: GetPolicyVersion -> QueryString
toQuery GetPolicyVersion' {Text
versionId :: Text
policyArn :: Text
$sel:versionId:GetPolicyVersion' :: GetPolicyVersion -> Text
$sel:policyArn:GetPolicyVersion' :: GetPolicyVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetPolicyVersion" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"PolicyArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyArn,
        ByteString
"VersionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
versionId
      ]

-- | Contains the response to a successful GetPolicyVersion request.
--
-- /See:/ 'newGetPolicyVersionResponse' smart constructor.
data GetPolicyVersionResponse = GetPolicyVersionResponse'
  { -- | A structure containing details about the policy version.
    GetPolicyVersionResponse -> Maybe PolicyVersion
policyVersion :: Prelude.Maybe PolicyVersion,
    -- | The response's http status code.
    GetPolicyVersionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetPolicyVersionResponse -> GetPolicyVersionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPolicyVersionResponse -> GetPolicyVersionResponse -> Bool
$c/= :: GetPolicyVersionResponse -> GetPolicyVersionResponse -> Bool
== :: GetPolicyVersionResponse -> GetPolicyVersionResponse -> Bool
$c== :: GetPolicyVersionResponse -> GetPolicyVersionResponse -> Bool
Prelude.Eq, ReadPrec [GetPolicyVersionResponse]
ReadPrec GetPolicyVersionResponse
Int -> ReadS GetPolicyVersionResponse
ReadS [GetPolicyVersionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetPolicyVersionResponse]
$creadListPrec :: ReadPrec [GetPolicyVersionResponse]
readPrec :: ReadPrec GetPolicyVersionResponse
$creadPrec :: ReadPrec GetPolicyVersionResponse
readList :: ReadS [GetPolicyVersionResponse]
$creadList :: ReadS [GetPolicyVersionResponse]
readsPrec :: Int -> ReadS GetPolicyVersionResponse
$creadsPrec :: Int -> ReadS GetPolicyVersionResponse
Prelude.Read, Int -> GetPolicyVersionResponse -> ShowS
[GetPolicyVersionResponse] -> ShowS
GetPolicyVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPolicyVersionResponse] -> ShowS
$cshowList :: [GetPolicyVersionResponse] -> ShowS
show :: GetPolicyVersionResponse -> String
$cshow :: GetPolicyVersionResponse -> String
showsPrec :: Int -> GetPolicyVersionResponse -> ShowS
$cshowsPrec :: Int -> GetPolicyVersionResponse -> ShowS
Prelude.Show, forall x.
Rep GetPolicyVersionResponse x -> GetPolicyVersionResponse
forall x.
GetPolicyVersionResponse -> Rep GetPolicyVersionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPolicyVersionResponse x -> GetPolicyVersionResponse
$cfrom :: forall x.
GetPolicyVersionResponse -> Rep GetPolicyVersionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetPolicyVersionResponse' 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:
--
-- 'policyVersion', 'getPolicyVersionResponse_policyVersion' - A structure containing details about the policy version.
--
-- 'httpStatus', 'getPolicyVersionResponse_httpStatus' - The response's http status code.
newGetPolicyVersionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetPolicyVersionResponse
newGetPolicyVersionResponse :: Int -> GetPolicyVersionResponse
newGetPolicyVersionResponse Int
pHttpStatus_ =
  GetPolicyVersionResponse'
    { $sel:policyVersion:GetPolicyVersionResponse' :: Maybe PolicyVersion
policyVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetPolicyVersionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A structure containing details about the policy version.
getPolicyVersionResponse_policyVersion :: Lens.Lens' GetPolicyVersionResponse (Prelude.Maybe PolicyVersion)
getPolicyVersionResponse_policyVersion :: Lens' GetPolicyVersionResponse (Maybe PolicyVersion)
getPolicyVersionResponse_policyVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetPolicyVersionResponse' {Maybe PolicyVersion
policyVersion :: Maybe PolicyVersion
$sel:policyVersion:GetPolicyVersionResponse' :: GetPolicyVersionResponse -> Maybe PolicyVersion
policyVersion} -> Maybe PolicyVersion
policyVersion) (\s :: GetPolicyVersionResponse
s@GetPolicyVersionResponse' {} Maybe PolicyVersion
a -> GetPolicyVersionResponse
s {$sel:policyVersion:GetPolicyVersionResponse' :: Maybe PolicyVersion
policyVersion = Maybe PolicyVersion
a} :: GetPolicyVersionResponse)

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

instance Prelude.NFData GetPolicyVersionResponse where
  rnf :: GetPolicyVersionResponse -> ()
rnf GetPolicyVersionResponse' {Int
Maybe PolicyVersion
httpStatus :: Int
policyVersion :: Maybe PolicyVersion
$sel:httpStatus:GetPolicyVersionResponse' :: GetPolicyVersionResponse -> Int
$sel:policyVersion:GetPolicyVersionResponse' :: GetPolicyVersionResponse -> Maybe PolicyVersion
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe PolicyVersion
policyVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus