{-# 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.GetVPCEConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about the configuration settings for your Amazon
-- Virtual Private Cloud (VPC) endpoint.
module Amazonka.DeviceFarm.GetVPCEConfiguration
  ( -- * Creating a Request
    GetVPCEConfiguration (..),
    newGetVPCEConfiguration,

    -- * Request Lenses
    getVPCEConfiguration_arn,

    -- * Destructuring the Response
    GetVPCEConfigurationResponse (..),
    newGetVPCEConfigurationResponse,

    -- * Response Lenses
    getVPCEConfigurationResponse_vpceConfiguration,
    getVPCEConfigurationResponse_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:/ 'newGetVPCEConfiguration' smart constructor.
data GetVPCEConfiguration = GetVPCEConfiguration'
  { -- | The Amazon Resource Name (ARN) of the VPC endpoint configuration you
    -- want to describe.
    GetVPCEConfiguration -> Text
arn :: Prelude.Text
  }
  deriving (GetVPCEConfiguration -> GetVPCEConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetVPCEConfiguration -> GetVPCEConfiguration -> Bool
$c/= :: GetVPCEConfiguration -> GetVPCEConfiguration -> Bool
== :: GetVPCEConfiguration -> GetVPCEConfiguration -> Bool
$c== :: GetVPCEConfiguration -> GetVPCEConfiguration -> Bool
Prelude.Eq, ReadPrec [GetVPCEConfiguration]
ReadPrec GetVPCEConfiguration
Int -> ReadS GetVPCEConfiguration
ReadS [GetVPCEConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetVPCEConfiguration]
$creadListPrec :: ReadPrec [GetVPCEConfiguration]
readPrec :: ReadPrec GetVPCEConfiguration
$creadPrec :: ReadPrec GetVPCEConfiguration
readList :: ReadS [GetVPCEConfiguration]
$creadList :: ReadS [GetVPCEConfiguration]
readsPrec :: Int -> ReadS GetVPCEConfiguration
$creadsPrec :: Int -> ReadS GetVPCEConfiguration
Prelude.Read, Int -> GetVPCEConfiguration -> ShowS
[GetVPCEConfiguration] -> ShowS
GetVPCEConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetVPCEConfiguration] -> ShowS
$cshowList :: [GetVPCEConfiguration] -> ShowS
show :: GetVPCEConfiguration -> String
$cshow :: GetVPCEConfiguration -> String
showsPrec :: Int -> GetVPCEConfiguration -> ShowS
$cshowsPrec :: Int -> GetVPCEConfiguration -> ShowS
Prelude.Show, forall x. Rep GetVPCEConfiguration x -> GetVPCEConfiguration
forall x. GetVPCEConfiguration -> Rep GetVPCEConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetVPCEConfiguration x -> GetVPCEConfiguration
$cfrom :: forall x. GetVPCEConfiguration -> Rep GetVPCEConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'GetVPCEConfiguration' 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:
--
-- 'arn', 'getVPCEConfiguration_arn' - The Amazon Resource Name (ARN) of the VPC endpoint configuration you
-- want to describe.
newGetVPCEConfiguration ::
  -- | 'arn'
  Prelude.Text ->
  GetVPCEConfiguration
newGetVPCEConfiguration :: Text -> GetVPCEConfiguration
newGetVPCEConfiguration Text
pArn_ =
  GetVPCEConfiguration' {$sel:arn:GetVPCEConfiguration' :: Text
arn = Text
pArn_}

-- | The Amazon Resource Name (ARN) of the VPC endpoint configuration you
-- want to describe.
getVPCEConfiguration_arn :: Lens.Lens' GetVPCEConfiguration Prelude.Text
getVPCEConfiguration_arn :: Lens' GetVPCEConfiguration Text
getVPCEConfiguration_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVPCEConfiguration' {Text
arn :: Text
$sel:arn:GetVPCEConfiguration' :: GetVPCEConfiguration -> Text
arn} -> Text
arn) (\s :: GetVPCEConfiguration
s@GetVPCEConfiguration' {} Text
a -> GetVPCEConfiguration
s {$sel:arn:GetVPCEConfiguration' :: Text
arn = Text
a} :: GetVPCEConfiguration)

instance Core.AWSRequest GetVPCEConfiguration where
  type
    AWSResponse GetVPCEConfiguration =
      GetVPCEConfigurationResponse
  request :: (Service -> Service)
-> GetVPCEConfiguration -> Request GetVPCEConfiguration
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 GetVPCEConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetVPCEConfiguration)))
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 -> GetVPCEConfigurationResponse
GetVPCEConfigurationResponse'
            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 GetVPCEConfiguration where
  hashWithSalt :: Int -> GetVPCEConfiguration -> Int
hashWithSalt Int
_salt GetVPCEConfiguration' {Text
arn :: Text
$sel:arn:GetVPCEConfiguration' :: GetVPCEConfiguration -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn

instance Prelude.NFData GetVPCEConfiguration where
  rnf :: GetVPCEConfiguration -> ()
rnf GetVPCEConfiguration' {Text
arn :: Text
$sel:arn:GetVPCEConfiguration' :: GetVPCEConfiguration -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
arn

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

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

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

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

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

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

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

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