{-# 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.IoT.CreatePolicy
-- 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 an IoT policy.
--
-- The created policy is the default version for the policy. This operation
-- creates a policy version with a version identifier of __1__ and sets
-- __1__ as the policy\'s default version.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions CreatePolicy>
-- action.
module Amazonka.IoT.CreatePolicy
  ( -- * Creating a Request
    CreatePolicy (..),
    newCreatePolicy,

    -- * Request Lenses
    createPolicy_tags,
    createPolicy_policyName,
    createPolicy_policyDocument,

    -- * Destructuring the Response
    CreatePolicyResponse (..),
    newCreatePolicyResponse,

    -- * Response Lenses
    createPolicyResponse_policyArn,
    createPolicyResponse_policyDocument,
    createPolicyResponse_policyName,
    createPolicyResponse_policyVersionId,
    createPolicyResponse_httpStatus,
  )
where

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

-- | The input for the CreatePolicy operation.
--
-- /See:/ 'newCreatePolicy' smart constructor.
data CreatePolicy = CreatePolicy'
  { -- | Metadata which can be used to manage the policy.
    --
    -- For URI Request parameters use format: ...key1=value1&key2=value2...
    --
    -- For the CLI command-line parameter use format: &&tags
    -- \"key1=value1&key2=value2...\"
    --
    -- For the cli-input-json file use format: \"tags\":
    -- \"key1=value1&key2=value2...\"
    CreatePolicy -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The policy name.
    CreatePolicy -> Text
policyName :: Prelude.Text,
    -- | The JSON document that describes the policy. __policyDocument__ must
    -- have a minimum length of 1, with a maximum length of 2048, excluding
    -- whitespace.
    CreatePolicy -> Text
policyDocument :: Prelude.Text
  }
  deriving (CreatePolicy -> CreatePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePolicy -> CreatePolicy -> Bool
$c/= :: CreatePolicy -> CreatePolicy -> Bool
== :: CreatePolicy -> CreatePolicy -> Bool
$c== :: CreatePolicy -> CreatePolicy -> Bool
Prelude.Eq, ReadPrec [CreatePolicy]
ReadPrec CreatePolicy
Int -> ReadS CreatePolicy
ReadS [CreatePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePolicy]
$creadListPrec :: ReadPrec [CreatePolicy]
readPrec :: ReadPrec CreatePolicy
$creadPrec :: ReadPrec CreatePolicy
readList :: ReadS [CreatePolicy]
$creadList :: ReadS [CreatePolicy]
readsPrec :: Int -> ReadS CreatePolicy
$creadsPrec :: Int -> ReadS CreatePolicy
Prelude.Read, Int -> CreatePolicy -> ShowS
[CreatePolicy] -> ShowS
CreatePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePolicy] -> ShowS
$cshowList :: [CreatePolicy] -> ShowS
show :: CreatePolicy -> String
$cshow :: CreatePolicy -> String
showsPrec :: Int -> CreatePolicy -> ShowS
$cshowsPrec :: Int -> CreatePolicy -> ShowS
Prelude.Show, forall x. Rep CreatePolicy x -> CreatePolicy
forall x. CreatePolicy -> Rep CreatePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePolicy x -> CreatePolicy
$cfrom :: forall x. CreatePolicy -> Rep CreatePolicy x
Prelude.Generic)

-- |
-- Create a value of 'CreatePolicy' 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:
--
-- 'tags', 'createPolicy_tags' - Metadata which can be used to manage the policy.
--
-- For URI Request parameters use format: ...key1=value1&key2=value2...
--
-- For the CLI command-line parameter use format: &&tags
-- \"key1=value1&key2=value2...\"
--
-- For the cli-input-json file use format: \"tags\":
-- \"key1=value1&key2=value2...\"
--
-- 'policyName', 'createPolicy_policyName' - The policy name.
--
-- 'policyDocument', 'createPolicy_policyDocument' - The JSON document that describes the policy. __policyDocument__ must
-- have a minimum length of 1, with a maximum length of 2048, excluding
-- whitespace.
newCreatePolicy ::
  -- | 'policyName'
  Prelude.Text ->
  -- | 'policyDocument'
  Prelude.Text ->
  CreatePolicy
newCreatePolicy :: Text -> Text -> CreatePolicy
newCreatePolicy Text
pPolicyName_ Text
pPolicyDocument_ =
  CreatePolicy'
    { $sel:tags:CreatePolicy' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:CreatePolicy' :: Text
policyName = Text
pPolicyName_,
      $sel:policyDocument:CreatePolicy' :: Text
policyDocument = Text
pPolicyDocument_
    }

-- | Metadata which can be used to manage the policy.
--
-- For URI Request parameters use format: ...key1=value1&key2=value2...
--
-- For the CLI command-line parameter use format: &&tags
-- \"key1=value1&key2=value2...\"
--
-- For the cli-input-json file use format: \"tags\":
-- \"key1=value1&key2=value2...\"
createPolicy_tags :: Lens.Lens' CreatePolicy (Prelude.Maybe [Tag])
createPolicy_tags :: Lens' CreatePolicy (Maybe [Tag])
createPolicy_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicy' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreatePolicy' :: CreatePolicy -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreatePolicy
s@CreatePolicy' {} Maybe [Tag]
a -> CreatePolicy
s {$sel:tags:CreatePolicy' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreatePolicy) 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 policy name.
createPolicy_policyName :: Lens.Lens' CreatePolicy Prelude.Text
createPolicy_policyName :: Lens' CreatePolicy Text
createPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicy' {Text
policyName :: Text
$sel:policyName:CreatePolicy' :: CreatePolicy -> Text
policyName} -> Text
policyName) (\s :: CreatePolicy
s@CreatePolicy' {} Text
a -> CreatePolicy
s {$sel:policyName:CreatePolicy' :: Text
policyName = Text
a} :: CreatePolicy)

-- | The JSON document that describes the policy. __policyDocument__ must
-- have a minimum length of 1, with a maximum length of 2048, excluding
-- whitespace.
createPolicy_policyDocument :: Lens.Lens' CreatePolicy Prelude.Text
createPolicy_policyDocument :: Lens' CreatePolicy Text
createPolicy_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicy' {Text
policyDocument :: Text
$sel:policyDocument:CreatePolicy' :: CreatePolicy -> Text
policyDocument} -> Text
policyDocument) (\s :: CreatePolicy
s@CreatePolicy' {} Text
a -> CreatePolicy
s {$sel:policyDocument:CreatePolicy' :: Text
policyDocument = Text
a} :: CreatePolicy)

instance Core.AWSRequest CreatePolicy where
  type AWSResponse CreatePolicy = CreatePolicyResponse
  request :: (Service -> Service) -> CreatePolicy -> Request CreatePolicy
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreatePolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreatePolicy)))
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
-> Maybe Text
-> Maybe Text
-> Int
-> CreatePolicyResponse
CreatePolicyResponse'
            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
"policyArn")
            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
"policyDocument")
            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
"policyName")
            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
"policyVersionId")
            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 CreatePolicy where
  hashWithSalt :: Int -> CreatePolicy -> Int
hashWithSalt Int
_salt CreatePolicy' {Maybe [Tag]
Text
policyDocument :: Text
policyName :: Text
tags :: Maybe [Tag]
$sel:policyDocument:CreatePolicy' :: CreatePolicy -> Text
$sel:policyName:CreatePolicy' :: CreatePolicy -> Text
$sel:tags:CreatePolicy' :: CreatePolicy -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyDocument

instance Prelude.NFData CreatePolicy where
  rnf :: CreatePolicy -> ()
rnf CreatePolicy' {Maybe [Tag]
Text
policyDocument :: Text
policyName :: Text
tags :: Maybe [Tag]
$sel:policyDocument:CreatePolicy' :: CreatePolicy -> Text
$sel:policyName:CreatePolicy' :: CreatePolicy -> Text
$sel:tags:CreatePolicy' :: CreatePolicy -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyDocument

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

instance Data.ToJSON CreatePolicy where
  toJSON :: CreatePolicy -> Value
toJSON CreatePolicy' {Maybe [Tag]
Text
policyDocument :: Text
policyName :: Text
tags :: Maybe [Tag]
$sel:policyDocument:CreatePolicy' :: CreatePolicy -> Text
$sel:policyName:CreatePolicy' :: CreatePolicy -> Text
$sel:tags:CreatePolicy' :: CreatePolicy -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"policyDocument" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
policyDocument)
          ]
      )

instance Data.ToPath CreatePolicy where
  toPath :: CreatePolicy -> ByteString
toPath CreatePolicy' {Maybe [Tag]
Text
policyDocument :: Text
policyName :: Text
tags :: Maybe [Tag]
$sel:policyDocument:CreatePolicy' :: CreatePolicy -> Text
$sel:policyName:CreatePolicy' :: CreatePolicy -> Text
$sel:tags:CreatePolicy' :: CreatePolicy -> Maybe [Tag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/policies/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
policyName]

instance Data.ToQuery CreatePolicy where
  toQuery :: CreatePolicy -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | The output from the CreatePolicy operation.
--
-- /See:/ 'newCreatePolicyResponse' smart constructor.
data CreatePolicyResponse = CreatePolicyResponse'
  { -- | The policy ARN.
    CreatePolicyResponse -> Maybe Text
policyArn :: Prelude.Maybe Prelude.Text,
    -- | The JSON document that describes the policy.
    CreatePolicyResponse -> Maybe Text
policyDocument :: Prelude.Maybe Prelude.Text,
    -- | The policy name.
    CreatePolicyResponse -> Maybe Text
policyName :: Prelude.Maybe Prelude.Text,
    -- | The policy version ID.
    CreatePolicyResponse -> Maybe Text
policyVersionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreatePolicyResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreatePolicyResponse -> CreatePolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePolicyResponse -> CreatePolicyResponse -> Bool
$c/= :: CreatePolicyResponse -> CreatePolicyResponse -> Bool
== :: CreatePolicyResponse -> CreatePolicyResponse -> Bool
$c== :: CreatePolicyResponse -> CreatePolicyResponse -> Bool
Prelude.Eq, ReadPrec [CreatePolicyResponse]
ReadPrec CreatePolicyResponse
Int -> ReadS CreatePolicyResponse
ReadS [CreatePolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreatePolicyResponse]
$creadListPrec :: ReadPrec [CreatePolicyResponse]
readPrec :: ReadPrec CreatePolicyResponse
$creadPrec :: ReadPrec CreatePolicyResponse
readList :: ReadS [CreatePolicyResponse]
$creadList :: ReadS [CreatePolicyResponse]
readsPrec :: Int -> ReadS CreatePolicyResponse
$creadsPrec :: Int -> ReadS CreatePolicyResponse
Prelude.Read, Int -> CreatePolicyResponse -> ShowS
[CreatePolicyResponse] -> ShowS
CreatePolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePolicyResponse] -> ShowS
$cshowList :: [CreatePolicyResponse] -> ShowS
show :: CreatePolicyResponse -> String
$cshow :: CreatePolicyResponse -> String
showsPrec :: Int -> CreatePolicyResponse -> ShowS
$cshowsPrec :: Int -> CreatePolicyResponse -> ShowS
Prelude.Show, forall x. Rep CreatePolicyResponse x -> CreatePolicyResponse
forall x. CreatePolicyResponse -> Rep CreatePolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePolicyResponse x -> CreatePolicyResponse
$cfrom :: forall x. CreatePolicyResponse -> Rep CreatePolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreatePolicyResponse' 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', 'createPolicyResponse_policyArn' - The policy ARN.
--
-- 'policyDocument', 'createPolicyResponse_policyDocument' - The JSON document that describes the policy.
--
-- 'policyName', 'createPolicyResponse_policyName' - The policy name.
--
-- 'policyVersionId', 'createPolicyResponse_policyVersionId' - The policy version ID.
--
-- 'httpStatus', 'createPolicyResponse_httpStatus' - The response's http status code.
newCreatePolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreatePolicyResponse
newCreatePolicyResponse :: Int -> CreatePolicyResponse
newCreatePolicyResponse Int
pHttpStatus_ =
  CreatePolicyResponse'
    { $sel:policyArn:CreatePolicyResponse' :: Maybe Text
policyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:policyDocument:CreatePolicyResponse' :: Maybe Text
policyDocument = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:CreatePolicyResponse' :: Maybe Text
policyName = forall a. Maybe a
Prelude.Nothing,
      $sel:policyVersionId:CreatePolicyResponse' :: Maybe Text
policyVersionId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreatePolicyResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The policy ARN.
createPolicyResponse_policyArn :: Lens.Lens' CreatePolicyResponse (Prelude.Maybe Prelude.Text)
createPolicyResponse_policyArn :: Lens' CreatePolicyResponse (Maybe Text)
createPolicyResponse_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyResponse' {Maybe Text
policyArn :: Maybe Text
$sel:policyArn:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
policyArn} -> Maybe Text
policyArn) (\s :: CreatePolicyResponse
s@CreatePolicyResponse' {} Maybe Text
a -> CreatePolicyResponse
s {$sel:policyArn:CreatePolicyResponse' :: Maybe Text
policyArn = Maybe Text
a} :: CreatePolicyResponse)

-- | The JSON document that describes the policy.
createPolicyResponse_policyDocument :: Lens.Lens' CreatePolicyResponse (Prelude.Maybe Prelude.Text)
createPolicyResponse_policyDocument :: Lens' CreatePolicyResponse (Maybe Text)
createPolicyResponse_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyResponse' {Maybe Text
policyDocument :: Maybe Text
$sel:policyDocument:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
policyDocument} -> Maybe Text
policyDocument) (\s :: CreatePolicyResponse
s@CreatePolicyResponse' {} Maybe Text
a -> CreatePolicyResponse
s {$sel:policyDocument:CreatePolicyResponse' :: Maybe Text
policyDocument = Maybe Text
a} :: CreatePolicyResponse)

-- | The policy name.
createPolicyResponse_policyName :: Lens.Lens' CreatePolicyResponse (Prelude.Maybe Prelude.Text)
createPolicyResponse_policyName :: Lens' CreatePolicyResponse (Maybe Text)
createPolicyResponse_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyResponse' {Maybe Text
policyName :: Maybe Text
$sel:policyName:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
policyName} -> Maybe Text
policyName) (\s :: CreatePolicyResponse
s@CreatePolicyResponse' {} Maybe Text
a -> CreatePolicyResponse
s {$sel:policyName:CreatePolicyResponse' :: Maybe Text
policyName = Maybe Text
a} :: CreatePolicyResponse)

-- | The policy version ID.
createPolicyResponse_policyVersionId :: Lens.Lens' CreatePolicyResponse (Prelude.Maybe Prelude.Text)
createPolicyResponse_policyVersionId :: Lens' CreatePolicyResponse (Maybe Text)
createPolicyResponse_policyVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreatePolicyResponse' {Maybe Text
policyVersionId :: Maybe Text
$sel:policyVersionId:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
policyVersionId} -> Maybe Text
policyVersionId) (\s :: CreatePolicyResponse
s@CreatePolicyResponse' {} Maybe Text
a -> CreatePolicyResponse
s {$sel:policyVersionId:CreatePolicyResponse' :: Maybe Text
policyVersionId = Maybe Text
a} :: CreatePolicyResponse)

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

instance Prelude.NFData CreatePolicyResponse where
  rnf :: CreatePolicyResponse -> ()
rnf CreatePolicyResponse' {Int
Maybe Text
httpStatus :: Int
policyVersionId :: Maybe Text
policyName :: Maybe Text
policyDocument :: Maybe Text
policyArn :: Maybe Text
$sel:httpStatus:CreatePolicyResponse' :: CreatePolicyResponse -> Int
$sel:policyVersionId:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
$sel:policyName:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
$sel:policyDocument:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
$sel:policyArn:CreatePolicyResponse' :: CreatePolicyResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyDocument
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus