{-# 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.CreatePolicyVersion
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new version of the specified managed policy. To update a
-- managed policy, you create a new policy version. A managed policy can
-- have up to five versions. If the policy has five versions, you must
-- delete an existing version using DeletePolicyVersion before you create a
-- new version.
--
-- Optionally, you can set the new version as the policy\'s default
-- version. The default version is the version that is in effect for the
-- IAM users, groups, and roles to which the policy is attached.
--
-- 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.CreatePolicyVersion
  ( -- * Creating a Request
    CreatePolicyVersion (..),
    newCreatePolicyVersion,

    -- * Request Lenses
    createPolicyVersion_setAsDefault,
    createPolicyVersion_policyArn,
    createPolicyVersion_policyDocument,

    -- * Destructuring the Response
    CreatePolicyVersionResponse (..),
    newCreatePolicyVersionResponse,

    -- * Response Lenses
    createPolicyVersionResponse_policyVersion,
    createPolicyVersionResponse_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:/ 'newCreatePolicyVersion' smart constructor.
data CreatePolicyVersion = CreatePolicyVersion'
  { -- | Specifies whether to set this version as the policy\'s default version.
    --
    -- When this parameter is @true@, the new policy version becomes the
    -- operative version. That is, it becomes the version that is in effect for
    -- the IAM users, groups, and roles that the policy is attached to.
    --
    -- 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/.
    CreatePolicyVersion -> Maybe Bool
setAsDefault :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the IAM policy to which you want to
    -- add a new version.
    --
    -- 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/.
    CreatePolicyVersion -> Text
policyArn :: Prelude.Text,
    -- | The JSON policy document that you want to use as the content for this
    -- new version of the policy.
    --
    -- You must provide policies in JSON format in IAM. However, for
    -- CloudFormation templates formatted in YAML, you can provide the policy
    -- in JSON or YAML format. CloudFormation always converts a YAML policy to
    -- JSON format before submitting it to IAM.
    --
    -- The maximum length of the policy document that you can pass in this
    -- operation, including whitespace, is listed below. To view the maximum
    -- character counts of a managed policy with no whitespaces, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_iam-quotas.html#reference_iam-quotas-entity-length IAM and STS character quotas>.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
    -- this parameter is a string of characters consisting of the following:
    --
    -- -   Any printable ASCII character ranging from the space character
    --     (@\\u0020@) through the end of the ASCII character range
    --
    -- -   The printable characters in the Basic Latin and Latin-1 Supplement
    --     character set (through @\\u00FF@)
    --
    -- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
    --     carriage return (@\\u000D@)
    CreatePolicyVersion -> Text
policyDocument :: Prelude.Text
  }
  deriving (CreatePolicyVersion -> CreatePolicyVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePolicyVersion -> CreatePolicyVersion -> Bool
$c/= :: CreatePolicyVersion -> CreatePolicyVersion -> Bool
== :: CreatePolicyVersion -> CreatePolicyVersion -> Bool
$c== :: CreatePolicyVersion -> CreatePolicyVersion -> Bool
Prelude.Eq, ReadPrec [CreatePolicyVersion]
ReadPrec CreatePolicyVersion
Int -> ReadS CreatePolicyVersion
ReadS [CreatePolicyVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePolicyVersion]
$creadListPrec :: ReadPrec [CreatePolicyVersion]
readPrec :: ReadPrec CreatePolicyVersion
$creadPrec :: ReadPrec CreatePolicyVersion
readList :: ReadS [CreatePolicyVersion]
$creadList :: ReadS [CreatePolicyVersion]
readsPrec :: Int -> ReadS CreatePolicyVersion
$creadsPrec :: Int -> ReadS CreatePolicyVersion
Prelude.Read, Int -> CreatePolicyVersion -> ShowS
[CreatePolicyVersion] -> ShowS
CreatePolicyVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePolicyVersion] -> ShowS
$cshowList :: [CreatePolicyVersion] -> ShowS
show :: CreatePolicyVersion -> String
$cshow :: CreatePolicyVersion -> String
showsPrec :: Int -> CreatePolicyVersion -> ShowS
$cshowsPrec :: Int -> CreatePolicyVersion -> ShowS
Prelude.Show, forall x. Rep CreatePolicyVersion x -> CreatePolicyVersion
forall x. CreatePolicyVersion -> Rep CreatePolicyVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePolicyVersion x -> CreatePolicyVersion
$cfrom :: forall x. CreatePolicyVersion -> Rep CreatePolicyVersion x
Prelude.Generic)

-- |
-- Create a value of 'CreatePolicyVersion' 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:
--
-- 'setAsDefault', 'createPolicyVersion_setAsDefault' - Specifies whether to set this version as the policy\'s default version.
--
-- When this parameter is @true@, the new policy version becomes the
-- operative version. That is, it becomes the version that is in effect for
-- the IAM users, groups, and roles that the policy is attached to.
--
-- 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/.
--
-- 'policyArn', 'createPolicyVersion_policyArn' - The Amazon Resource Name (ARN) of the IAM policy to which you want to
-- add a new version.
--
-- 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/.
--
-- 'policyDocument', 'createPolicyVersion_policyDocument' - The JSON policy document that you want to use as the content for this
-- new version of the policy.
--
-- You must provide policies in JSON format in IAM. However, for
-- CloudFormation templates formatted in YAML, you can provide the policy
-- in JSON or YAML format. CloudFormation always converts a YAML policy to
-- JSON format before submitting it to IAM.
--
-- The maximum length of the policy document that you can pass in this
-- operation, including whitespace, is listed below. To view the maximum
-- character counts of a managed policy with no whitespaces, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_iam-quotas.html#reference_iam-quotas-entity-length IAM and STS character quotas>.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
-- this parameter is a string of characters consisting of the following:
--
-- -   Any printable ASCII character ranging from the space character
--     (@\\u0020@) through the end of the ASCII character range
--
-- -   The printable characters in the Basic Latin and Latin-1 Supplement
--     character set (through @\\u00FF@)
--
-- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
--     carriage return (@\\u000D@)
newCreatePolicyVersion ::
  -- | 'policyArn'
  Prelude.Text ->
  -- | 'policyDocument'
  Prelude.Text ->
  CreatePolicyVersion
newCreatePolicyVersion :: Text -> Text -> CreatePolicyVersion
newCreatePolicyVersion Text
pPolicyArn_ Text
pPolicyDocument_ =
  CreatePolicyVersion'
    { $sel:setAsDefault:CreatePolicyVersion' :: Maybe Bool
setAsDefault =
        forall a. Maybe a
Prelude.Nothing,
      $sel:policyArn:CreatePolicyVersion' :: Text
policyArn = Text
pPolicyArn_,
      $sel:policyDocument:CreatePolicyVersion' :: Text
policyDocument = Text
pPolicyDocument_
    }

-- | Specifies whether to set this version as the policy\'s default version.
--
-- When this parameter is @true@, the new policy version becomes the
-- operative version. That is, it becomes the version that is in effect for
-- the IAM users, groups, and roles that the policy is attached to.
--
-- 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/.
createPolicyVersion_setAsDefault :: Lens.Lens' CreatePolicyVersion (Prelude.Maybe Prelude.Bool)
createPolicyVersion_setAsDefault :: Lens' CreatePolicyVersion (Maybe Bool)
createPolicyVersion_setAsDefault = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyVersion' {Maybe Bool
setAsDefault :: Maybe Bool
$sel:setAsDefault:CreatePolicyVersion' :: CreatePolicyVersion -> Maybe Bool
setAsDefault} -> Maybe Bool
setAsDefault) (\s :: CreatePolicyVersion
s@CreatePolicyVersion' {} Maybe Bool
a -> CreatePolicyVersion
s {$sel:setAsDefault:CreatePolicyVersion' :: Maybe Bool
setAsDefault = Maybe Bool
a} :: CreatePolicyVersion)

-- | The Amazon Resource Name (ARN) of the IAM policy to which you want to
-- add a new version.
--
-- 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/.
createPolicyVersion_policyArn :: Lens.Lens' CreatePolicyVersion Prelude.Text
createPolicyVersion_policyArn :: Lens' CreatePolicyVersion Text
createPolicyVersion_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyVersion' {Text
policyArn :: Text
$sel:policyArn:CreatePolicyVersion' :: CreatePolicyVersion -> Text
policyArn} -> Text
policyArn) (\s :: CreatePolicyVersion
s@CreatePolicyVersion' {} Text
a -> CreatePolicyVersion
s {$sel:policyArn:CreatePolicyVersion' :: Text
policyArn = Text
a} :: CreatePolicyVersion)

-- | The JSON policy document that you want to use as the content for this
-- new version of the policy.
--
-- You must provide policies in JSON format in IAM. However, for
-- CloudFormation templates formatted in YAML, you can provide the policy
-- in JSON or YAML format. CloudFormation always converts a YAML policy to
-- JSON format before submitting it to IAM.
--
-- The maximum length of the policy document that you can pass in this
-- operation, including whitespace, is listed below. To view the maximum
-- character counts of a managed policy with no whitespaces, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_iam-quotas.html#reference_iam-quotas-entity-length IAM and STS character quotas>.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
-- this parameter is a string of characters consisting of the following:
--
-- -   Any printable ASCII character ranging from the space character
--     (@\\u0020@) through the end of the ASCII character range
--
-- -   The printable characters in the Basic Latin and Latin-1 Supplement
--     character set (through @\\u00FF@)
--
-- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
--     carriage return (@\\u000D@)
createPolicyVersion_policyDocument :: Lens.Lens' CreatePolicyVersion Prelude.Text
createPolicyVersion_policyDocument :: Lens' CreatePolicyVersion Text
createPolicyVersion_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyVersion' {Text
policyDocument :: Text
$sel:policyDocument:CreatePolicyVersion' :: CreatePolicyVersion -> Text
policyDocument} -> Text
policyDocument) (\s :: CreatePolicyVersion
s@CreatePolicyVersion' {} Text
a -> CreatePolicyVersion
s {$sel:policyDocument:CreatePolicyVersion' :: Text
policyDocument = Text
a} :: CreatePolicyVersion)

instance Core.AWSRequest CreatePolicyVersion where
  type
    AWSResponse CreatePolicyVersion =
      CreatePolicyVersionResponse
  request :: (Service -> Service)
-> CreatePolicyVersion -> Request CreatePolicyVersion
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 CreatePolicyVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreatePolicyVersion)))
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
"CreatePolicyVersionResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe PolicyVersion -> Int -> CreatePolicyVersionResponse
CreatePolicyVersionResponse'
            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 CreatePolicyVersion where
  hashWithSalt :: Int -> CreatePolicyVersion -> Int
hashWithSalt Int
_salt CreatePolicyVersion' {Maybe Bool
Text
policyDocument :: Text
policyArn :: Text
setAsDefault :: Maybe Bool
$sel:policyDocument:CreatePolicyVersion' :: CreatePolicyVersion -> Text
$sel:policyArn:CreatePolicyVersion' :: CreatePolicyVersion -> Text
$sel:setAsDefault:CreatePolicyVersion' :: CreatePolicyVersion -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
setAsDefault
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyDocument

instance Prelude.NFData CreatePolicyVersion where
  rnf :: CreatePolicyVersion -> ()
rnf CreatePolicyVersion' {Maybe Bool
Text
policyDocument :: Text
policyArn :: Text
setAsDefault :: Maybe Bool
$sel:policyDocument:CreatePolicyVersion' :: CreatePolicyVersion -> Text
$sel:policyArn:CreatePolicyVersion' :: CreatePolicyVersion -> Text
$sel:setAsDefault:CreatePolicyVersion' :: CreatePolicyVersion -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
setAsDefault
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
policyDocument

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

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

instance Data.ToQuery CreatePolicyVersion where
  toQuery :: CreatePolicyVersion -> QueryString
toQuery CreatePolicyVersion' {Maybe Bool
Text
policyDocument :: Text
policyArn :: Text
setAsDefault :: Maybe Bool
$sel:policyDocument:CreatePolicyVersion' :: CreatePolicyVersion -> Text
$sel:policyArn:CreatePolicyVersion' :: CreatePolicyVersion -> Text
$sel:setAsDefault:CreatePolicyVersion' :: CreatePolicyVersion -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreatePolicyVersion" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"SetAsDefault" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
setAsDefault,
        ByteString
"PolicyArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyArn,
        ByteString
"PolicyDocument" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyDocument
      ]

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

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

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

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

instance Prelude.NFData CreatePolicyVersionResponse where
  rnf :: CreatePolicyVersionResponse -> ()
rnf CreatePolicyVersionResponse' {Int
Maybe PolicyVersion
httpStatus :: Int
policyVersion :: Maybe PolicyVersion
$sel:httpStatus:CreatePolicyVersionResponse' :: CreatePolicyVersionResponse -> Int
$sel:policyVersion:CreatePolicyVersionResponse' :: CreatePolicyVersionResponse -> 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