{-# 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.CloudFront.CreateCloudFrontOriginAccessIdentity
-- 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 origin access identity. If you\'re using Amazon S3 for
-- your origin, you can use an origin access identity to require users to
-- access your content using a CloudFront URL instead of the Amazon S3 URL.
-- For more information about how to use origin access identities, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/PrivateContent.html Serving Private Content through CloudFront>
-- in the /Amazon CloudFront Developer Guide/.
module Amazonka.CloudFront.CreateCloudFrontOriginAccessIdentity
  ( -- * Creating a Request
    CreateCloudFrontOriginAccessIdentity (..),
    newCreateCloudFrontOriginAccessIdentity,

    -- * Request Lenses
    createCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig,

    -- * Destructuring the Response
    CreateCloudFrontOriginAccessIdentityResponse (..),
    newCreateCloudFrontOriginAccessIdentityResponse,

    -- * Response Lenses
    createCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity,
    createCloudFrontOriginAccessIdentityResponse_eTag,
    createCloudFrontOriginAccessIdentityResponse_location,
    createCloudFrontOriginAccessIdentityResponse_httpStatus,
  )
where

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

-- | The request to create a new origin access identity (OAI). An origin
-- access identity is a special CloudFront user that you can associate with
-- Amazon S3 origins, so that you can secure all or just some of your
-- Amazon S3 content. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudFront/latest/DeveloperGuide/private-content-restricting-access-to-s3.html Restricting Access to Amazon S3 Content by Using an Origin Access Identity>
-- in the /Amazon CloudFront Developer Guide/.
--
-- /See:/ 'newCreateCloudFrontOriginAccessIdentity' smart constructor.
data CreateCloudFrontOriginAccessIdentity = CreateCloudFrontOriginAccessIdentity'
  { -- | The current configuration information for the identity.
    CreateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
  }
  deriving (CreateCloudFrontOriginAccessIdentity
-> CreateCloudFrontOriginAccessIdentity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCloudFrontOriginAccessIdentity
-> CreateCloudFrontOriginAccessIdentity -> Bool
$c/= :: CreateCloudFrontOriginAccessIdentity
-> CreateCloudFrontOriginAccessIdentity -> Bool
== :: CreateCloudFrontOriginAccessIdentity
-> CreateCloudFrontOriginAccessIdentity -> Bool
$c== :: CreateCloudFrontOriginAccessIdentity
-> CreateCloudFrontOriginAccessIdentity -> Bool
Prelude.Eq, ReadPrec [CreateCloudFrontOriginAccessIdentity]
ReadPrec CreateCloudFrontOriginAccessIdentity
Int -> ReadS CreateCloudFrontOriginAccessIdentity
ReadS [CreateCloudFrontOriginAccessIdentity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCloudFrontOriginAccessIdentity]
$creadListPrec :: ReadPrec [CreateCloudFrontOriginAccessIdentity]
readPrec :: ReadPrec CreateCloudFrontOriginAccessIdentity
$creadPrec :: ReadPrec CreateCloudFrontOriginAccessIdentity
readList :: ReadS [CreateCloudFrontOriginAccessIdentity]
$creadList :: ReadS [CreateCloudFrontOriginAccessIdentity]
readsPrec :: Int -> ReadS CreateCloudFrontOriginAccessIdentity
$creadsPrec :: Int -> ReadS CreateCloudFrontOriginAccessIdentity
Prelude.Read, Int -> CreateCloudFrontOriginAccessIdentity -> ShowS
[CreateCloudFrontOriginAccessIdentity] -> ShowS
CreateCloudFrontOriginAccessIdentity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCloudFrontOriginAccessIdentity] -> ShowS
$cshowList :: [CreateCloudFrontOriginAccessIdentity] -> ShowS
show :: CreateCloudFrontOriginAccessIdentity -> String
$cshow :: CreateCloudFrontOriginAccessIdentity -> String
showsPrec :: Int -> CreateCloudFrontOriginAccessIdentity -> ShowS
$cshowsPrec :: Int -> CreateCloudFrontOriginAccessIdentity -> ShowS
Prelude.Show, forall x.
Rep CreateCloudFrontOriginAccessIdentity x
-> CreateCloudFrontOriginAccessIdentity
forall x.
CreateCloudFrontOriginAccessIdentity
-> Rep CreateCloudFrontOriginAccessIdentity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCloudFrontOriginAccessIdentity x
-> CreateCloudFrontOriginAccessIdentity
$cfrom :: forall x.
CreateCloudFrontOriginAccessIdentity
-> Rep CreateCloudFrontOriginAccessIdentity x
Prelude.Generic)

-- |
-- Create a value of 'CreateCloudFrontOriginAccessIdentity' 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:
--
-- 'cloudFrontOriginAccessIdentityConfig', 'createCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig' - The current configuration information for the identity.
newCreateCloudFrontOriginAccessIdentity ::
  -- | 'cloudFrontOriginAccessIdentityConfig'
  CloudFrontOriginAccessIdentityConfig ->
  CreateCloudFrontOriginAccessIdentity
newCreateCloudFrontOriginAccessIdentity :: CloudFrontOriginAccessIdentityConfig
-> CreateCloudFrontOriginAccessIdentity
newCreateCloudFrontOriginAccessIdentity
  CloudFrontOriginAccessIdentityConfig
pCloudFrontOriginAccessIdentityConfig_ =
    CreateCloudFrontOriginAccessIdentity'
      { $sel:cloudFrontOriginAccessIdentityConfig:CreateCloudFrontOriginAccessIdentity' :: CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig =
          CloudFrontOriginAccessIdentityConfig
pCloudFrontOriginAccessIdentityConfig_
      }

-- | The current configuration information for the identity.
createCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig :: Lens.Lens' CreateCloudFrontOriginAccessIdentity CloudFrontOriginAccessIdentityConfig
createCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig :: Lens'
  CreateCloudFrontOriginAccessIdentity
  CloudFrontOriginAccessIdentityConfig
createCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCloudFrontOriginAccessIdentity' {CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
$sel:cloudFrontOriginAccessIdentityConfig:CreateCloudFrontOriginAccessIdentity' :: CreateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig} -> CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig) (\s :: CreateCloudFrontOriginAccessIdentity
s@CreateCloudFrontOriginAccessIdentity' {} CloudFrontOriginAccessIdentityConfig
a -> CreateCloudFrontOriginAccessIdentity
s {$sel:cloudFrontOriginAccessIdentityConfig:CreateCloudFrontOriginAccessIdentity' :: CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig = CloudFrontOriginAccessIdentityConfig
a} :: CreateCloudFrontOriginAccessIdentity)

instance
  Core.AWSRequest
    CreateCloudFrontOriginAccessIdentity
  where
  type
    AWSResponse CreateCloudFrontOriginAccessIdentity =
      CreateCloudFrontOriginAccessIdentityResponse
  request :: (Service -> Service)
-> CreateCloudFrontOriginAccessIdentity
-> Request CreateCloudFrontOriginAccessIdentity
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateCloudFrontOriginAccessIdentity
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse CreateCloudFrontOriginAccessIdentity)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe CloudFrontOriginAccessIdentity
-> Maybe Text
-> Maybe Text
-> Int
-> CreateCloudFrontOriginAccessIdentityResponse
CreateCloudFrontOriginAccessIdentityResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"ETag")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"Location")
            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
    CreateCloudFrontOriginAccessIdentity
  where
  hashWithSalt :: Int -> CreateCloudFrontOriginAccessIdentity -> Int
hashWithSalt
    Int
_salt
    CreateCloudFrontOriginAccessIdentity' {CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
$sel:cloudFrontOriginAccessIdentityConfig:CreateCloudFrontOriginAccessIdentity' :: CreateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig

instance
  Prelude.NFData
    CreateCloudFrontOriginAccessIdentity
  where
  rnf :: CreateCloudFrontOriginAccessIdentity -> ()
rnf CreateCloudFrontOriginAccessIdentity' {CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
$sel:cloudFrontOriginAccessIdentityConfig:CreateCloudFrontOriginAccessIdentity' :: CreateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig

instance
  Data.ToElement
    CreateCloudFrontOriginAccessIdentity
  where
  toElement :: CreateCloudFrontOriginAccessIdentity -> Element
toElement CreateCloudFrontOriginAccessIdentity' {CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
$sel:cloudFrontOriginAccessIdentityConfig:CreateCloudFrontOriginAccessIdentity' :: CreateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://cloudfront.amazonaws.com/doc/2020-05-31/}CloudFrontOriginAccessIdentityConfig"
      CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig

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

instance
  Data.ToPath
    CreateCloudFrontOriginAccessIdentity
  where
  toPath :: CreateCloudFrontOriginAccessIdentity -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/2020-05-31/origin-access-identity/cloudfront"

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

-- | The returned result of the corresponding request.
--
-- /See:/ 'newCreateCloudFrontOriginAccessIdentityResponse' smart constructor.
data CreateCloudFrontOriginAccessIdentityResponse = CreateCloudFrontOriginAccessIdentityResponse'
  { -- | The origin access identity\'s information.
    CreateCloudFrontOriginAccessIdentityResponse
-> Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity :: Prelude.Maybe CloudFrontOriginAccessIdentity,
    -- | The current version of the origin access identity created.
    CreateCloudFrontOriginAccessIdentityResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | The fully qualified URI of the new origin access identity just created.
    CreateCloudFrontOriginAccessIdentityResponse -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateCloudFrontOriginAccessIdentityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateCloudFrontOriginAccessIdentityResponse
-> CreateCloudFrontOriginAccessIdentityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCloudFrontOriginAccessIdentityResponse
-> CreateCloudFrontOriginAccessIdentityResponse -> Bool
$c/= :: CreateCloudFrontOriginAccessIdentityResponse
-> CreateCloudFrontOriginAccessIdentityResponse -> Bool
== :: CreateCloudFrontOriginAccessIdentityResponse
-> CreateCloudFrontOriginAccessIdentityResponse -> Bool
$c== :: CreateCloudFrontOriginAccessIdentityResponse
-> CreateCloudFrontOriginAccessIdentityResponse -> Bool
Prelude.Eq, ReadPrec [CreateCloudFrontOriginAccessIdentityResponse]
ReadPrec CreateCloudFrontOriginAccessIdentityResponse
Int -> ReadS CreateCloudFrontOriginAccessIdentityResponse
ReadS [CreateCloudFrontOriginAccessIdentityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCloudFrontOriginAccessIdentityResponse]
$creadListPrec :: ReadPrec [CreateCloudFrontOriginAccessIdentityResponse]
readPrec :: ReadPrec CreateCloudFrontOriginAccessIdentityResponse
$creadPrec :: ReadPrec CreateCloudFrontOriginAccessIdentityResponse
readList :: ReadS [CreateCloudFrontOriginAccessIdentityResponse]
$creadList :: ReadS [CreateCloudFrontOriginAccessIdentityResponse]
readsPrec :: Int -> ReadS CreateCloudFrontOriginAccessIdentityResponse
$creadsPrec :: Int -> ReadS CreateCloudFrontOriginAccessIdentityResponse
Prelude.Read, Int -> CreateCloudFrontOriginAccessIdentityResponse -> ShowS
[CreateCloudFrontOriginAccessIdentityResponse] -> ShowS
CreateCloudFrontOriginAccessIdentityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCloudFrontOriginAccessIdentityResponse] -> ShowS
$cshowList :: [CreateCloudFrontOriginAccessIdentityResponse] -> ShowS
show :: CreateCloudFrontOriginAccessIdentityResponse -> String
$cshow :: CreateCloudFrontOriginAccessIdentityResponse -> String
showsPrec :: Int -> CreateCloudFrontOriginAccessIdentityResponse -> ShowS
$cshowsPrec :: Int -> CreateCloudFrontOriginAccessIdentityResponse -> ShowS
Prelude.Show, forall x.
Rep CreateCloudFrontOriginAccessIdentityResponse x
-> CreateCloudFrontOriginAccessIdentityResponse
forall x.
CreateCloudFrontOriginAccessIdentityResponse
-> Rep CreateCloudFrontOriginAccessIdentityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCloudFrontOriginAccessIdentityResponse x
-> CreateCloudFrontOriginAccessIdentityResponse
$cfrom :: forall x.
CreateCloudFrontOriginAccessIdentityResponse
-> Rep CreateCloudFrontOriginAccessIdentityResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateCloudFrontOriginAccessIdentityResponse' 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:
--
-- 'cloudFrontOriginAccessIdentity', 'createCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity' - The origin access identity\'s information.
--
-- 'eTag', 'createCloudFrontOriginAccessIdentityResponse_eTag' - The current version of the origin access identity created.
--
-- 'location', 'createCloudFrontOriginAccessIdentityResponse_location' - The fully qualified URI of the new origin access identity just created.
--
-- 'httpStatus', 'createCloudFrontOriginAccessIdentityResponse_httpStatus' - The response's http status code.
newCreateCloudFrontOriginAccessIdentityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCloudFrontOriginAccessIdentityResponse
newCreateCloudFrontOriginAccessIdentityResponse :: Int -> CreateCloudFrontOriginAccessIdentityResponse
newCreateCloudFrontOriginAccessIdentityResponse
  Int
pHttpStatus_ =
    CreateCloudFrontOriginAccessIdentityResponse'
      { $sel:cloudFrontOriginAccessIdentity:CreateCloudFrontOriginAccessIdentityResponse' :: Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity =
          forall a. Maybe a
Prelude.Nothing,
        $sel:eTag:CreateCloudFrontOriginAccessIdentityResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
        $sel:location:CreateCloudFrontOriginAccessIdentityResponse' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CreateCloudFrontOriginAccessIdentityResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The origin access identity\'s information.
createCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity :: Lens.Lens' CreateCloudFrontOriginAccessIdentityResponse (Prelude.Maybe CloudFrontOriginAccessIdentity)
createCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity :: Lens'
  CreateCloudFrontOriginAccessIdentityResponse
  (Maybe CloudFrontOriginAccessIdentity)
createCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCloudFrontOriginAccessIdentityResponse' {Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity :: Maybe CloudFrontOriginAccessIdentity
$sel:cloudFrontOriginAccessIdentity:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse
-> Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity} -> Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity) (\s :: CreateCloudFrontOriginAccessIdentityResponse
s@CreateCloudFrontOriginAccessIdentityResponse' {} Maybe CloudFrontOriginAccessIdentity
a -> CreateCloudFrontOriginAccessIdentityResponse
s {$sel:cloudFrontOriginAccessIdentity:CreateCloudFrontOriginAccessIdentityResponse' :: Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity = Maybe CloudFrontOriginAccessIdentity
a} :: CreateCloudFrontOriginAccessIdentityResponse)

-- | The current version of the origin access identity created.
createCloudFrontOriginAccessIdentityResponse_eTag :: Lens.Lens' CreateCloudFrontOriginAccessIdentityResponse (Prelude.Maybe Prelude.Text)
createCloudFrontOriginAccessIdentityResponse_eTag :: Lens' CreateCloudFrontOriginAccessIdentityResponse (Maybe Text)
createCloudFrontOriginAccessIdentityResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCloudFrontOriginAccessIdentityResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: CreateCloudFrontOriginAccessIdentityResponse
s@CreateCloudFrontOriginAccessIdentityResponse' {} Maybe Text
a -> CreateCloudFrontOriginAccessIdentityResponse
s {$sel:eTag:CreateCloudFrontOriginAccessIdentityResponse' :: Maybe Text
eTag = Maybe Text
a} :: CreateCloudFrontOriginAccessIdentityResponse)

-- | The fully qualified URI of the new origin access identity just created.
createCloudFrontOriginAccessIdentityResponse_location :: Lens.Lens' CreateCloudFrontOriginAccessIdentityResponse (Prelude.Maybe Prelude.Text)
createCloudFrontOriginAccessIdentityResponse_location :: Lens' CreateCloudFrontOriginAccessIdentityResponse (Maybe Text)
createCloudFrontOriginAccessIdentityResponse_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCloudFrontOriginAccessIdentityResponse' {Maybe Text
location :: Maybe Text
$sel:location:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse -> Maybe Text
location} -> Maybe Text
location) (\s :: CreateCloudFrontOriginAccessIdentityResponse
s@CreateCloudFrontOriginAccessIdentityResponse' {} Maybe Text
a -> CreateCloudFrontOriginAccessIdentityResponse
s {$sel:location:CreateCloudFrontOriginAccessIdentityResponse' :: Maybe Text
location = Maybe Text
a} :: CreateCloudFrontOriginAccessIdentityResponse)

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

instance
  Prelude.NFData
    CreateCloudFrontOriginAccessIdentityResponse
  where
  rnf :: CreateCloudFrontOriginAccessIdentityResponse -> ()
rnf CreateCloudFrontOriginAccessIdentityResponse' {Int
Maybe Text
Maybe CloudFrontOriginAccessIdentity
httpStatus :: Int
location :: Maybe Text
eTag :: Maybe Text
cloudFrontOriginAccessIdentity :: Maybe CloudFrontOriginAccessIdentity
$sel:httpStatus:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse -> Int
$sel:location:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse -> Maybe Text
$sel:eTag:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse -> Maybe Text
$sel:cloudFrontOriginAccessIdentity:CreateCloudFrontOriginAccessIdentityResponse' :: CreateCloudFrontOriginAccessIdentityResponse
-> Maybe CloudFrontOriginAccessIdentity
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eTag
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus