{-# 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.UpdateCloudFrontOriginAccessIdentity
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Update an origin access identity.
module Amazonka.CloudFront.UpdateCloudFrontOriginAccessIdentity
  ( -- * Creating a Request
    UpdateCloudFrontOriginAccessIdentity (..),
    newUpdateCloudFrontOriginAccessIdentity,

    -- * Request Lenses
    updateCloudFrontOriginAccessIdentity_ifMatch,
    updateCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig,
    updateCloudFrontOriginAccessIdentity_id,

    -- * Destructuring the Response
    UpdateCloudFrontOriginAccessIdentityResponse (..),
    newUpdateCloudFrontOriginAccessIdentityResponse,

    -- * Response Lenses
    updateCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity,
    updateCloudFrontOriginAccessIdentityResponse_eTag,
    updateCloudFrontOriginAccessIdentityResponse_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 update an origin access identity.
--
-- /See:/ 'newUpdateCloudFrontOriginAccessIdentity' smart constructor.
data UpdateCloudFrontOriginAccessIdentity = UpdateCloudFrontOriginAccessIdentity'
  { -- | The value of the @ETag@ header that you received when retrieving the
    -- identity\'s configuration. For example: @E2QWRUHAPOMQZL@.
    UpdateCloudFrontOriginAccessIdentity -> Maybe Text
ifMatch :: Prelude.Maybe Prelude.Text,
    -- | The identity\'s configuration information.
    UpdateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig,
    -- | The identity\'s id.
    UpdateCloudFrontOriginAccessIdentity -> Text
id :: Prelude.Text
  }
  deriving (UpdateCloudFrontOriginAccessIdentity
-> UpdateCloudFrontOriginAccessIdentity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCloudFrontOriginAccessIdentity
-> UpdateCloudFrontOriginAccessIdentity -> Bool
$c/= :: UpdateCloudFrontOriginAccessIdentity
-> UpdateCloudFrontOriginAccessIdentity -> Bool
== :: UpdateCloudFrontOriginAccessIdentity
-> UpdateCloudFrontOriginAccessIdentity -> Bool
$c== :: UpdateCloudFrontOriginAccessIdentity
-> UpdateCloudFrontOriginAccessIdentity -> Bool
Prelude.Eq, ReadPrec [UpdateCloudFrontOriginAccessIdentity]
ReadPrec UpdateCloudFrontOriginAccessIdentity
Int -> ReadS UpdateCloudFrontOriginAccessIdentity
ReadS [UpdateCloudFrontOriginAccessIdentity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCloudFrontOriginAccessIdentity]
$creadListPrec :: ReadPrec [UpdateCloudFrontOriginAccessIdentity]
readPrec :: ReadPrec UpdateCloudFrontOriginAccessIdentity
$creadPrec :: ReadPrec UpdateCloudFrontOriginAccessIdentity
readList :: ReadS [UpdateCloudFrontOriginAccessIdentity]
$creadList :: ReadS [UpdateCloudFrontOriginAccessIdentity]
readsPrec :: Int -> ReadS UpdateCloudFrontOriginAccessIdentity
$creadsPrec :: Int -> ReadS UpdateCloudFrontOriginAccessIdentity
Prelude.Read, Int -> UpdateCloudFrontOriginAccessIdentity -> ShowS
[UpdateCloudFrontOriginAccessIdentity] -> ShowS
UpdateCloudFrontOriginAccessIdentity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCloudFrontOriginAccessIdentity] -> ShowS
$cshowList :: [UpdateCloudFrontOriginAccessIdentity] -> ShowS
show :: UpdateCloudFrontOriginAccessIdentity -> String
$cshow :: UpdateCloudFrontOriginAccessIdentity -> String
showsPrec :: Int -> UpdateCloudFrontOriginAccessIdentity -> ShowS
$cshowsPrec :: Int -> UpdateCloudFrontOriginAccessIdentity -> ShowS
Prelude.Show, forall x.
Rep UpdateCloudFrontOriginAccessIdentity x
-> UpdateCloudFrontOriginAccessIdentity
forall x.
UpdateCloudFrontOriginAccessIdentity
-> Rep UpdateCloudFrontOriginAccessIdentity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCloudFrontOriginAccessIdentity x
-> UpdateCloudFrontOriginAccessIdentity
$cfrom :: forall x.
UpdateCloudFrontOriginAccessIdentity
-> Rep UpdateCloudFrontOriginAccessIdentity x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCloudFrontOriginAccessIdentity' 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:
--
-- 'ifMatch', 'updateCloudFrontOriginAccessIdentity_ifMatch' - The value of the @ETag@ header that you received when retrieving the
-- identity\'s configuration. For example: @E2QWRUHAPOMQZL@.
--
-- 'cloudFrontOriginAccessIdentityConfig', 'updateCloudFrontOriginAccessIdentity_cloudFrontOriginAccessIdentityConfig' - The identity\'s configuration information.
--
-- 'id', 'updateCloudFrontOriginAccessIdentity_id' - The identity\'s id.
newUpdateCloudFrontOriginAccessIdentity ::
  -- | 'cloudFrontOriginAccessIdentityConfig'
  CloudFrontOriginAccessIdentityConfig ->
  -- | 'id'
  Prelude.Text ->
  UpdateCloudFrontOriginAccessIdentity
newUpdateCloudFrontOriginAccessIdentity :: CloudFrontOriginAccessIdentityConfig
-> Text -> UpdateCloudFrontOriginAccessIdentity
newUpdateCloudFrontOriginAccessIdentity
  CloudFrontOriginAccessIdentityConfig
pCloudFrontOriginAccessIdentityConfig_
  Text
pId_ =
    UpdateCloudFrontOriginAccessIdentity'
      { $sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: Maybe Text
ifMatch =
          forall a. Maybe a
Prelude.Nothing,
        $sel:cloudFrontOriginAccessIdentityConfig:UpdateCloudFrontOriginAccessIdentity' :: CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig =
          CloudFrontOriginAccessIdentityConfig
pCloudFrontOriginAccessIdentityConfig_,
        $sel:id:UpdateCloudFrontOriginAccessIdentity' :: Text
id = Text
pId_
      }

-- | The value of the @ETag@ header that you received when retrieving the
-- identity\'s configuration. For example: @E2QWRUHAPOMQZL@.
updateCloudFrontOriginAccessIdentity_ifMatch :: Lens.Lens' UpdateCloudFrontOriginAccessIdentity (Prelude.Maybe Prelude.Text)
updateCloudFrontOriginAccessIdentity_ifMatch :: Lens' UpdateCloudFrontOriginAccessIdentity (Maybe Text)
updateCloudFrontOriginAccessIdentity_ifMatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCloudFrontOriginAccessIdentity' {Maybe Text
ifMatch :: Maybe Text
$sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Maybe Text
ifMatch} -> Maybe Text
ifMatch) (\s :: UpdateCloudFrontOriginAccessIdentity
s@UpdateCloudFrontOriginAccessIdentity' {} Maybe Text
a -> UpdateCloudFrontOriginAccessIdentity
s {$sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: Maybe Text
ifMatch = Maybe Text
a} :: UpdateCloudFrontOriginAccessIdentity)

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

-- | The identity\'s id.
updateCloudFrontOriginAccessIdentity_id :: Lens.Lens' UpdateCloudFrontOriginAccessIdentity Prelude.Text
updateCloudFrontOriginAccessIdentity_id :: Lens' UpdateCloudFrontOriginAccessIdentity Text
updateCloudFrontOriginAccessIdentity_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCloudFrontOriginAccessIdentity' {Text
id :: Text
$sel:id:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Text
id} -> Text
id) (\s :: UpdateCloudFrontOriginAccessIdentity
s@UpdateCloudFrontOriginAccessIdentity' {} Text
a -> UpdateCloudFrontOriginAccessIdentity
s {$sel:id:UpdateCloudFrontOriginAccessIdentity' :: Text
id = Text
a} :: UpdateCloudFrontOriginAccessIdentity)

instance
  Core.AWSRequest
    UpdateCloudFrontOriginAccessIdentity
  where
  type
    AWSResponse UpdateCloudFrontOriginAccessIdentity =
      UpdateCloudFrontOriginAccessIdentityResponse
  request :: (Service -> Service)
-> UpdateCloudFrontOriginAccessIdentity
-> Request UpdateCloudFrontOriginAccessIdentity
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.putXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateCloudFrontOriginAccessIdentity
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse UpdateCloudFrontOriginAccessIdentity)))
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
-> Int
-> UpdateCloudFrontOriginAccessIdentityResponse
UpdateCloudFrontOriginAccessIdentityResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    UpdateCloudFrontOriginAccessIdentity
  where
  hashWithSalt :: Int -> UpdateCloudFrontOriginAccessIdentity -> Int
hashWithSalt
    Int
_salt
    UpdateCloudFrontOriginAccessIdentity' {Maybe Text
Text
CloudFrontOriginAccessIdentityConfig
id :: Text
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
ifMatch :: Maybe Text
$sel:id:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Text
$sel:cloudFrontOriginAccessIdentityConfig:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
$sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ifMatch
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance
  Prelude.NFData
    UpdateCloudFrontOriginAccessIdentity
  where
  rnf :: UpdateCloudFrontOriginAccessIdentity -> ()
rnf UpdateCloudFrontOriginAccessIdentity' {Maybe Text
Text
CloudFrontOriginAccessIdentityConfig
id :: Text
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
ifMatch :: Maybe Text
$sel:id:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Text
$sel:cloudFrontOriginAccessIdentityConfig:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
$sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ifMatch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CloudFrontOriginAccessIdentityConfig
cloudFrontOriginAccessIdentityConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance
  Data.ToHeaders
    UpdateCloudFrontOriginAccessIdentity
  where
  toHeaders :: UpdateCloudFrontOriginAccessIdentity -> ResponseHeaders
toHeaders UpdateCloudFrontOriginAccessIdentity' {Maybe Text
Text
CloudFrontOriginAccessIdentityConfig
id :: Text
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
ifMatch :: Maybe Text
$sel:id:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Text
$sel:cloudFrontOriginAccessIdentityConfig:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
$sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [HeaderName
"If-Match" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
ifMatch]

instance
  Data.ToPath
    UpdateCloudFrontOriginAccessIdentity
  where
  toPath :: UpdateCloudFrontOriginAccessIdentity -> ByteString
toPath UpdateCloudFrontOriginAccessIdentity' {Maybe Text
Text
CloudFrontOriginAccessIdentityConfig
id :: Text
cloudFrontOriginAccessIdentityConfig :: CloudFrontOriginAccessIdentityConfig
ifMatch :: Maybe Text
$sel:id:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Text
$sel:cloudFrontOriginAccessIdentityConfig:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity
-> CloudFrontOriginAccessIdentityConfig
$sel:ifMatch:UpdateCloudFrontOriginAccessIdentity' :: UpdateCloudFrontOriginAccessIdentity -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2020-05-31/origin-access-identity/cloudfront/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
id,
        ByteString
"/config"
      ]

instance
  Data.ToQuery
    UpdateCloudFrontOriginAccessIdentity
  where
  toQuery :: UpdateCloudFrontOriginAccessIdentity -> 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:/ 'newUpdateCloudFrontOriginAccessIdentityResponse' smart constructor.
data UpdateCloudFrontOriginAccessIdentityResponse = UpdateCloudFrontOriginAccessIdentityResponse'
  { -- | The origin access identity\'s information.
    UpdateCloudFrontOriginAccessIdentityResponse
-> Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity :: Prelude.Maybe CloudFrontOriginAccessIdentity,
    -- | The current version of the configuration. For example: @E2QWRUHAPOMQZL@.
    UpdateCloudFrontOriginAccessIdentityResponse -> Maybe Text
eTag :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateCloudFrontOriginAccessIdentityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateCloudFrontOriginAccessIdentityResponse
-> UpdateCloudFrontOriginAccessIdentityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCloudFrontOriginAccessIdentityResponse
-> UpdateCloudFrontOriginAccessIdentityResponse -> Bool
$c/= :: UpdateCloudFrontOriginAccessIdentityResponse
-> UpdateCloudFrontOriginAccessIdentityResponse -> Bool
== :: UpdateCloudFrontOriginAccessIdentityResponse
-> UpdateCloudFrontOriginAccessIdentityResponse -> Bool
$c== :: UpdateCloudFrontOriginAccessIdentityResponse
-> UpdateCloudFrontOriginAccessIdentityResponse -> Bool
Prelude.Eq, ReadPrec [UpdateCloudFrontOriginAccessIdentityResponse]
ReadPrec UpdateCloudFrontOriginAccessIdentityResponse
Int -> ReadS UpdateCloudFrontOriginAccessIdentityResponse
ReadS [UpdateCloudFrontOriginAccessIdentityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCloudFrontOriginAccessIdentityResponse]
$creadListPrec :: ReadPrec [UpdateCloudFrontOriginAccessIdentityResponse]
readPrec :: ReadPrec UpdateCloudFrontOriginAccessIdentityResponse
$creadPrec :: ReadPrec UpdateCloudFrontOriginAccessIdentityResponse
readList :: ReadS [UpdateCloudFrontOriginAccessIdentityResponse]
$creadList :: ReadS [UpdateCloudFrontOriginAccessIdentityResponse]
readsPrec :: Int -> ReadS UpdateCloudFrontOriginAccessIdentityResponse
$creadsPrec :: Int -> ReadS UpdateCloudFrontOriginAccessIdentityResponse
Prelude.Read, Int -> UpdateCloudFrontOriginAccessIdentityResponse -> ShowS
[UpdateCloudFrontOriginAccessIdentityResponse] -> ShowS
UpdateCloudFrontOriginAccessIdentityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCloudFrontOriginAccessIdentityResponse] -> ShowS
$cshowList :: [UpdateCloudFrontOriginAccessIdentityResponse] -> ShowS
show :: UpdateCloudFrontOriginAccessIdentityResponse -> String
$cshow :: UpdateCloudFrontOriginAccessIdentityResponse -> String
showsPrec :: Int -> UpdateCloudFrontOriginAccessIdentityResponse -> ShowS
$cshowsPrec :: Int -> UpdateCloudFrontOriginAccessIdentityResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateCloudFrontOriginAccessIdentityResponse x
-> UpdateCloudFrontOriginAccessIdentityResponse
forall x.
UpdateCloudFrontOriginAccessIdentityResponse
-> Rep UpdateCloudFrontOriginAccessIdentityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCloudFrontOriginAccessIdentityResponse x
-> UpdateCloudFrontOriginAccessIdentityResponse
$cfrom :: forall x.
UpdateCloudFrontOriginAccessIdentityResponse
-> Rep UpdateCloudFrontOriginAccessIdentityResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCloudFrontOriginAccessIdentityResponse' 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', 'updateCloudFrontOriginAccessIdentityResponse_cloudFrontOriginAccessIdentity' - The origin access identity\'s information.
--
-- 'eTag', 'updateCloudFrontOriginAccessIdentityResponse_eTag' - The current version of the configuration. For example: @E2QWRUHAPOMQZL@.
--
-- 'httpStatus', 'updateCloudFrontOriginAccessIdentityResponse_httpStatus' - The response's http status code.
newUpdateCloudFrontOriginAccessIdentityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateCloudFrontOriginAccessIdentityResponse
newUpdateCloudFrontOriginAccessIdentityResponse :: Int -> UpdateCloudFrontOriginAccessIdentityResponse
newUpdateCloudFrontOriginAccessIdentityResponse
  Int
pHttpStatus_ =
    UpdateCloudFrontOriginAccessIdentityResponse'
      { $sel:cloudFrontOriginAccessIdentity:UpdateCloudFrontOriginAccessIdentityResponse' :: Maybe CloudFrontOriginAccessIdentity
cloudFrontOriginAccessIdentity =
          forall a. Maybe a
Prelude.Nothing,
        $sel:eTag:UpdateCloudFrontOriginAccessIdentityResponse' :: Maybe Text
eTag = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:UpdateCloudFrontOriginAccessIdentityResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

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

-- | The current version of the configuration. For example: @E2QWRUHAPOMQZL@.
updateCloudFrontOriginAccessIdentityResponse_eTag :: Lens.Lens' UpdateCloudFrontOriginAccessIdentityResponse (Prelude.Maybe Prelude.Text)
updateCloudFrontOriginAccessIdentityResponse_eTag :: Lens' UpdateCloudFrontOriginAccessIdentityResponse (Maybe Text)
updateCloudFrontOriginAccessIdentityResponse_eTag = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCloudFrontOriginAccessIdentityResponse' {Maybe Text
eTag :: Maybe Text
$sel:eTag:UpdateCloudFrontOriginAccessIdentityResponse' :: UpdateCloudFrontOriginAccessIdentityResponse -> Maybe Text
eTag} -> Maybe Text
eTag) (\s :: UpdateCloudFrontOriginAccessIdentityResponse
s@UpdateCloudFrontOriginAccessIdentityResponse' {} Maybe Text
a -> UpdateCloudFrontOriginAccessIdentityResponse
s {$sel:eTag:UpdateCloudFrontOriginAccessIdentityResponse' :: Maybe Text
eTag = Maybe Text
a} :: UpdateCloudFrontOriginAccessIdentityResponse)

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

instance
  Prelude.NFData
    UpdateCloudFrontOriginAccessIdentityResponse
  where
  rnf :: UpdateCloudFrontOriginAccessIdentityResponse -> ()
rnf UpdateCloudFrontOriginAccessIdentityResponse' {Int
Maybe Text
Maybe CloudFrontOriginAccessIdentity
httpStatus :: Int
eTag :: Maybe Text
cloudFrontOriginAccessIdentity :: Maybe CloudFrontOriginAccessIdentity
$sel:httpStatus:UpdateCloudFrontOriginAccessIdentityResponse' :: UpdateCloudFrontOriginAccessIdentityResponse -> Int
$sel:eTag:UpdateCloudFrontOriginAccessIdentityResponse' :: UpdateCloudFrontOriginAccessIdentityResponse -> Maybe Text
$sel:cloudFrontOriginAccessIdentity:UpdateCloudFrontOriginAccessIdentityResponse' :: UpdateCloudFrontOriginAccessIdentityResponse
-> 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 Int
httpStatus