{-# 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.DeviceFarm.CreateVPCEConfiguration
-- 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 configuration record in Device Farm for your Amazon Virtual
-- Private Cloud (VPC) endpoint.
module Amazonka.DeviceFarm.CreateVPCEConfiguration
  ( -- * Creating a Request
    CreateVPCEConfiguration (..),
    newCreateVPCEConfiguration,

    -- * Request Lenses
    createVPCEConfiguration_vpceConfigurationDescription,
    createVPCEConfiguration_vpceConfigurationName,
    createVPCEConfiguration_vpceServiceName,
    createVPCEConfiguration_serviceDnsName,

    -- * Destructuring the Response
    CreateVPCEConfigurationResponse (..),
    newCreateVPCEConfigurationResponse,

    -- * Response Lenses
    createVPCEConfigurationResponse_vpceConfiguration,
    createVPCEConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateVPCEConfiguration' smart constructor.
data CreateVPCEConfiguration = CreateVPCEConfiguration'
  { -- | An optional description that provides details about your VPC endpoint
    -- configuration.
    CreateVPCEConfiguration -> Maybe Text
vpceConfigurationDescription :: Prelude.Maybe Prelude.Text,
    -- | The friendly name you give to your VPC endpoint configuration, to manage
    -- your configurations more easily.
    CreateVPCEConfiguration -> Text
vpceConfigurationName :: Prelude.Text,
    -- | The name of the VPC endpoint service running in your AWS account that
    -- you want Device Farm to test.
    CreateVPCEConfiguration -> Text
vpceServiceName :: Prelude.Text,
    -- | The DNS name of the service running in your VPC that you want Device
    -- Farm to test.
    CreateVPCEConfiguration -> Text
serviceDnsName :: Prelude.Text
  }
  deriving (CreateVPCEConfiguration -> CreateVPCEConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVPCEConfiguration -> CreateVPCEConfiguration -> Bool
$c/= :: CreateVPCEConfiguration -> CreateVPCEConfiguration -> Bool
== :: CreateVPCEConfiguration -> CreateVPCEConfiguration -> Bool
$c== :: CreateVPCEConfiguration -> CreateVPCEConfiguration -> Bool
Prelude.Eq, ReadPrec [CreateVPCEConfiguration]
ReadPrec CreateVPCEConfiguration
Int -> ReadS CreateVPCEConfiguration
ReadS [CreateVPCEConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVPCEConfiguration]
$creadListPrec :: ReadPrec [CreateVPCEConfiguration]
readPrec :: ReadPrec CreateVPCEConfiguration
$creadPrec :: ReadPrec CreateVPCEConfiguration
readList :: ReadS [CreateVPCEConfiguration]
$creadList :: ReadS [CreateVPCEConfiguration]
readsPrec :: Int -> ReadS CreateVPCEConfiguration
$creadsPrec :: Int -> ReadS CreateVPCEConfiguration
Prelude.Read, Int -> CreateVPCEConfiguration -> ShowS
[CreateVPCEConfiguration] -> ShowS
CreateVPCEConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVPCEConfiguration] -> ShowS
$cshowList :: [CreateVPCEConfiguration] -> ShowS
show :: CreateVPCEConfiguration -> String
$cshow :: CreateVPCEConfiguration -> String
showsPrec :: Int -> CreateVPCEConfiguration -> ShowS
$cshowsPrec :: Int -> CreateVPCEConfiguration -> ShowS
Prelude.Show, forall x. Rep CreateVPCEConfiguration x -> CreateVPCEConfiguration
forall x. CreateVPCEConfiguration -> Rep CreateVPCEConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateVPCEConfiguration x -> CreateVPCEConfiguration
$cfrom :: forall x. CreateVPCEConfiguration -> Rep CreateVPCEConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'CreateVPCEConfiguration' 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:
--
-- 'vpceConfigurationDescription', 'createVPCEConfiguration_vpceConfigurationDescription' - An optional description that provides details about your VPC endpoint
-- configuration.
--
-- 'vpceConfigurationName', 'createVPCEConfiguration_vpceConfigurationName' - The friendly name you give to your VPC endpoint configuration, to manage
-- your configurations more easily.
--
-- 'vpceServiceName', 'createVPCEConfiguration_vpceServiceName' - The name of the VPC endpoint service running in your AWS account that
-- you want Device Farm to test.
--
-- 'serviceDnsName', 'createVPCEConfiguration_serviceDnsName' - The DNS name of the service running in your VPC that you want Device
-- Farm to test.
newCreateVPCEConfiguration ::
  -- | 'vpceConfigurationName'
  Prelude.Text ->
  -- | 'vpceServiceName'
  Prelude.Text ->
  -- | 'serviceDnsName'
  Prelude.Text ->
  CreateVPCEConfiguration
newCreateVPCEConfiguration :: Text -> Text -> Text -> CreateVPCEConfiguration
newCreateVPCEConfiguration
  Text
pVpceConfigurationName_
  Text
pVpceServiceName_
  Text
pServiceDnsName_ =
    CreateVPCEConfiguration'
      { $sel:vpceConfigurationDescription:CreateVPCEConfiguration' :: Maybe Text
vpceConfigurationDescription =
          forall a. Maybe a
Prelude.Nothing,
        $sel:vpceConfigurationName:CreateVPCEConfiguration' :: Text
vpceConfigurationName = Text
pVpceConfigurationName_,
        $sel:vpceServiceName:CreateVPCEConfiguration' :: Text
vpceServiceName = Text
pVpceServiceName_,
        $sel:serviceDnsName:CreateVPCEConfiguration' :: Text
serviceDnsName = Text
pServiceDnsName_
      }

-- | An optional description that provides details about your VPC endpoint
-- configuration.
createVPCEConfiguration_vpceConfigurationDescription :: Lens.Lens' CreateVPCEConfiguration (Prelude.Maybe Prelude.Text)
createVPCEConfiguration_vpceConfigurationDescription :: Lens' CreateVPCEConfiguration (Maybe Text)
createVPCEConfiguration_vpceConfigurationDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVPCEConfiguration' {Maybe Text
vpceConfigurationDescription :: Maybe Text
$sel:vpceConfigurationDescription:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Maybe Text
vpceConfigurationDescription} -> Maybe Text
vpceConfigurationDescription) (\s :: CreateVPCEConfiguration
s@CreateVPCEConfiguration' {} Maybe Text
a -> CreateVPCEConfiguration
s {$sel:vpceConfigurationDescription:CreateVPCEConfiguration' :: Maybe Text
vpceConfigurationDescription = Maybe Text
a} :: CreateVPCEConfiguration)

-- | The friendly name you give to your VPC endpoint configuration, to manage
-- your configurations more easily.
createVPCEConfiguration_vpceConfigurationName :: Lens.Lens' CreateVPCEConfiguration Prelude.Text
createVPCEConfiguration_vpceConfigurationName :: Lens' CreateVPCEConfiguration Text
createVPCEConfiguration_vpceConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVPCEConfiguration' {Text
vpceConfigurationName :: Text
$sel:vpceConfigurationName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
vpceConfigurationName} -> Text
vpceConfigurationName) (\s :: CreateVPCEConfiguration
s@CreateVPCEConfiguration' {} Text
a -> CreateVPCEConfiguration
s {$sel:vpceConfigurationName:CreateVPCEConfiguration' :: Text
vpceConfigurationName = Text
a} :: CreateVPCEConfiguration)

-- | The name of the VPC endpoint service running in your AWS account that
-- you want Device Farm to test.
createVPCEConfiguration_vpceServiceName :: Lens.Lens' CreateVPCEConfiguration Prelude.Text
createVPCEConfiguration_vpceServiceName :: Lens' CreateVPCEConfiguration Text
createVPCEConfiguration_vpceServiceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVPCEConfiguration' {Text
vpceServiceName :: Text
$sel:vpceServiceName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
vpceServiceName} -> Text
vpceServiceName) (\s :: CreateVPCEConfiguration
s@CreateVPCEConfiguration' {} Text
a -> CreateVPCEConfiguration
s {$sel:vpceServiceName:CreateVPCEConfiguration' :: Text
vpceServiceName = Text
a} :: CreateVPCEConfiguration)

-- | The DNS name of the service running in your VPC that you want Device
-- Farm to test.
createVPCEConfiguration_serviceDnsName :: Lens.Lens' CreateVPCEConfiguration Prelude.Text
createVPCEConfiguration_serviceDnsName :: Lens' CreateVPCEConfiguration Text
createVPCEConfiguration_serviceDnsName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVPCEConfiguration' {Text
serviceDnsName :: Text
$sel:serviceDnsName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
serviceDnsName} -> Text
serviceDnsName) (\s :: CreateVPCEConfiguration
s@CreateVPCEConfiguration' {} Text
a -> CreateVPCEConfiguration
s {$sel:serviceDnsName:CreateVPCEConfiguration' :: Text
serviceDnsName = Text
a} :: CreateVPCEConfiguration)

instance Core.AWSRequest CreateVPCEConfiguration where
  type
    AWSResponse CreateVPCEConfiguration =
      CreateVPCEConfigurationResponse
  request :: (Service -> Service)
-> CreateVPCEConfiguration -> Request CreateVPCEConfiguration
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 CreateVPCEConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateVPCEConfiguration)))
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 VPCEConfiguration -> Int -> CreateVPCEConfigurationResponse
CreateVPCEConfigurationResponse'
            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
"vpceConfiguration")
            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 CreateVPCEConfiguration where
  hashWithSalt :: Int -> CreateVPCEConfiguration -> Int
hashWithSalt Int
_salt CreateVPCEConfiguration' {Maybe Text
Text
serviceDnsName :: Text
vpceServiceName :: Text
vpceConfigurationName :: Text
vpceConfigurationDescription :: Maybe Text
$sel:serviceDnsName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceServiceName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceConfigurationName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceConfigurationDescription:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpceConfigurationDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpceConfigurationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpceServiceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serviceDnsName

instance Prelude.NFData CreateVPCEConfiguration where
  rnf :: CreateVPCEConfiguration -> ()
rnf CreateVPCEConfiguration' {Maybe Text
Text
serviceDnsName :: Text
vpceServiceName :: Text
vpceConfigurationName :: Text
vpceConfigurationDescription :: Maybe Text
$sel:serviceDnsName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceServiceName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceConfigurationName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceConfigurationDescription:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpceConfigurationDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpceConfigurationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpceServiceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serviceDnsName

instance Data.ToHeaders CreateVPCEConfiguration where
  toHeaders :: CreateVPCEConfiguration -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"DeviceFarm_20150623.CreateVPCEConfiguration" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateVPCEConfiguration where
  toJSON :: CreateVPCEConfiguration -> Value
toJSON CreateVPCEConfiguration' {Maybe Text
Text
serviceDnsName :: Text
vpceServiceName :: Text
vpceConfigurationName :: Text
vpceConfigurationDescription :: Maybe Text
$sel:serviceDnsName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceServiceName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceConfigurationName:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Text
$sel:vpceConfigurationDescription:CreateVPCEConfiguration' :: CreateVPCEConfiguration -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"vpceConfigurationDescription" 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 Text
vpceConfigurationDescription,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"vpceConfigurationName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vpceConfigurationName
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"vpceServiceName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vpceServiceName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"serviceDnsName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serviceDnsName)
          ]
      )

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

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

-- | /See:/ 'newCreateVPCEConfigurationResponse' smart constructor.
data CreateVPCEConfigurationResponse = CreateVPCEConfigurationResponse'
  { -- | An object that contains information about your VPC endpoint
    -- configuration.
    CreateVPCEConfigurationResponse -> Maybe VPCEConfiguration
vpceConfiguration :: Prelude.Maybe VPCEConfiguration,
    -- | The response's http status code.
    CreateVPCEConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateVPCEConfigurationResponse
-> CreateVPCEConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateVPCEConfigurationResponse
-> CreateVPCEConfigurationResponse -> Bool
$c/= :: CreateVPCEConfigurationResponse
-> CreateVPCEConfigurationResponse -> Bool
== :: CreateVPCEConfigurationResponse
-> CreateVPCEConfigurationResponse -> Bool
$c== :: CreateVPCEConfigurationResponse
-> CreateVPCEConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [CreateVPCEConfigurationResponse]
ReadPrec CreateVPCEConfigurationResponse
Int -> ReadS CreateVPCEConfigurationResponse
ReadS [CreateVPCEConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateVPCEConfigurationResponse]
$creadListPrec :: ReadPrec [CreateVPCEConfigurationResponse]
readPrec :: ReadPrec CreateVPCEConfigurationResponse
$creadPrec :: ReadPrec CreateVPCEConfigurationResponse
readList :: ReadS [CreateVPCEConfigurationResponse]
$creadList :: ReadS [CreateVPCEConfigurationResponse]
readsPrec :: Int -> ReadS CreateVPCEConfigurationResponse
$creadsPrec :: Int -> ReadS CreateVPCEConfigurationResponse
Prelude.Read, Int -> CreateVPCEConfigurationResponse -> ShowS
[CreateVPCEConfigurationResponse] -> ShowS
CreateVPCEConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateVPCEConfigurationResponse] -> ShowS
$cshowList :: [CreateVPCEConfigurationResponse] -> ShowS
show :: CreateVPCEConfigurationResponse -> String
$cshow :: CreateVPCEConfigurationResponse -> String
showsPrec :: Int -> CreateVPCEConfigurationResponse -> ShowS
$cshowsPrec :: Int -> CreateVPCEConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep CreateVPCEConfigurationResponse x
-> CreateVPCEConfigurationResponse
forall x.
CreateVPCEConfigurationResponse
-> Rep CreateVPCEConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateVPCEConfigurationResponse x
-> CreateVPCEConfigurationResponse
$cfrom :: forall x.
CreateVPCEConfigurationResponse
-> Rep CreateVPCEConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateVPCEConfigurationResponse' 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:
--
-- 'vpceConfiguration', 'createVPCEConfigurationResponse_vpceConfiguration' - An object that contains information about your VPC endpoint
-- configuration.
--
-- 'httpStatus', 'createVPCEConfigurationResponse_httpStatus' - The response's http status code.
newCreateVPCEConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateVPCEConfigurationResponse
newCreateVPCEConfigurationResponse :: Int -> CreateVPCEConfigurationResponse
newCreateVPCEConfigurationResponse Int
pHttpStatus_ =
  CreateVPCEConfigurationResponse'
    { $sel:vpceConfiguration:CreateVPCEConfigurationResponse' :: Maybe VPCEConfiguration
vpceConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateVPCEConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An object that contains information about your VPC endpoint
-- configuration.
createVPCEConfigurationResponse_vpceConfiguration :: Lens.Lens' CreateVPCEConfigurationResponse (Prelude.Maybe VPCEConfiguration)
createVPCEConfigurationResponse_vpceConfiguration :: Lens' CreateVPCEConfigurationResponse (Maybe VPCEConfiguration)
createVPCEConfigurationResponse_vpceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateVPCEConfigurationResponse' {Maybe VPCEConfiguration
vpceConfiguration :: Maybe VPCEConfiguration
$sel:vpceConfiguration:CreateVPCEConfigurationResponse' :: CreateVPCEConfigurationResponse -> Maybe VPCEConfiguration
vpceConfiguration} -> Maybe VPCEConfiguration
vpceConfiguration) (\s :: CreateVPCEConfigurationResponse
s@CreateVPCEConfigurationResponse' {} Maybe VPCEConfiguration
a -> CreateVPCEConfigurationResponse
s {$sel:vpceConfiguration:CreateVPCEConfigurationResponse' :: Maybe VPCEConfiguration
vpceConfiguration = Maybe VPCEConfiguration
a} :: CreateVPCEConfigurationResponse)

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

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