{-# 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.KinesisAnalyticsV2.DeleteApplicationVpcConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes a VPC configuration from a Kinesis Data Analytics application.
module Amazonka.KinesisAnalyticsV2.DeleteApplicationVpcConfiguration
  ( -- * Creating a Request
    DeleteApplicationVpcConfiguration (..),
    newDeleteApplicationVpcConfiguration,

    -- * Request Lenses
    deleteApplicationVpcConfiguration_conditionalToken,
    deleteApplicationVpcConfiguration_currentApplicationVersionId,
    deleteApplicationVpcConfiguration_applicationName,
    deleteApplicationVpcConfiguration_vpcConfigurationId,

    -- * Destructuring the Response
    DeleteApplicationVpcConfigurationResponse (..),
    newDeleteApplicationVpcConfigurationResponse,

    -- * Response Lenses
    deleteApplicationVpcConfigurationResponse_applicationARN,
    deleteApplicationVpcConfigurationResponse_applicationVersionId,
    deleteApplicationVpcConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteApplicationVpcConfiguration' smart constructor.
data DeleteApplicationVpcConfiguration = DeleteApplicationVpcConfiguration'
  { -- | A value you use to implement strong concurrency for application updates.
    -- You must provide the @CurrentApplicationVersionId@ or the
    -- @ConditionalToken@. You get the application\'s current
    -- @ConditionalToken@ using DescribeApplication. For better concurrency
    -- support, use the @ConditionalToken@ parameter instead of
    -- @CurrentApplicationVersionId@.
    DeleteApplicationVpcConfiguration -> Maybe Text
conditionalToken :: Prelude.Maybe Prelude.Text,
    -- | The current application version ID. You must provide the
    -- @CurrentApplicationVersionId@ or the @ConditionalToken@. You can
    -- retrieve the application version ID using DescribeApplication. For
    -- better concurrency support, use the @ConditionalToken@ parameter instead
    -- of @CurrentApplicationVersionId@.
    DeleteApplicationVpcConfiguration -> Maybe Natural
currentApplicationVersionId :: Prelude.Maybe Prelude.Natural,
    -- | The name of an existing application.
    DeleteApplicationVpcConfiguration -> Text
applicationName :: Prelude.Text,
    -- | The ID of the VPC configuration to delete.
    DeleteApplicationVpcConfiguration -> Text
vpcConfigurationId :: Prelude.Text
  }
  deriving (DeleteApplicationVpcConfiguration
-> DeleteApplicationVpcConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteApplicationVpcConfiguration
-> DeleteApplicationVpcConfiguration -> Bool
$c/= :: DeleteApplicationVpcConfiguration
-> DeleteApplicationVpcConfiguration -> Bool
== :: DeleteApplicationVpcConfiguration
-> DeleteApplicationVpcConfiguration -> Bool
$c== :: DeleteApplicationVpcConfiguration
-> DeleteApplicationVpcConfiguration -> Bool
Prelude.Eq, ReadPrec [DeleteApplicationVpcConfiguration]
ReadPrec DeleteApplicationVpcConfiguration
Int -> ReadS DeleteApplicationVpcConfiguration
ReadS [DeleteApplicationVpcConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteApplicationVpcConfiguration]
$creadListPrec :: ReadPrec [DeleteApplicationVpcConfiguration]
readPrec :: ReadPrec DeleteApplicationVpcConfiguration
$creadPrec :: ReadPrec DeleteApplicationVpcConfiguration
readList :: ReadS [DeleteApplicationVpcConfiguration]
$creadList :: ReadS [DeleteApplicationVpcConfiguration]
readsPrec :: Int -> ReadS DeleteApplicationVpcConfiguration
$creadsPrec :: Int -> ReadS DeleteApplicationVpcConfiguration
Prelude.Read, Int -> DeleteApplicationVpcConfiguration -> ShowS
[DeleteApplicationVpcConfiguration] -> ShowS
DeleteApplicationVpcConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteApplicationVpcConfiguration] -> ShowS
$cshowList :: [DeleteApplicationVpcConfiguration] -> ShowS
show :: DeleteApplicationVpcConfiguration -> String
$cshow :: DeleteApplicationVpcConfiguration -> String
showsPrec :: Int -> DeleteApplicationVpcConfiguration -> ShowS
$cshowsPrec :: Int -> DeleteApplicationVpcConfiguration -> ShowS
Prelude.Show, forall x.
Rep DeleteApplicationVpcConfiguration x
-> DeleteApplicationVpcConfiguration
forall x.
DeleteApplicationVpcConfiguration
-> Rep DeleteApplicationVpcConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteApplicationVpcConfiguration x
-> DeleteApplicationVpcConfiguration
$cfrom :: forall x.
DeleteApplicationVpcConfiguration
-> Rep DeleteApplicationVpcConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DeleteApplicationVpcConfiguration' 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:
--
-- 'conditionalToken', 'deleteApplicationVpcConfiguration_conditionalToken' - A value you use to implement strong concurrency for application updates.
-- You must provide the @CurrentApplicationVersionId@ or the
-- @ConditionalToken@. You get the application\'s current
-- @ConditionalToken@ using DescribeApplication. For better concurrency
-- support, use the @ConditionalToken@ parameter instead of
-- @CurrentApplicationVersionId@.
--
-- 'currentApplicationVersionId', 'deleteApplicationVpcConfiguration_currentApplicationVersionId' - The current application version ID. You must provide the
-- @CurrentApplicationVersionId@ or the @ConditionalToken@. You can
-- retrieve the application version ID using DescribeApplication. For
-- better concurrency support, use the @ConditionalToken@ parameter instead
-- of @CurrentApplicationVersionId@.
--
-- 'applicationName', 'deleteApplicationVpcConfiguration_applicationName' - The name of an existing application.
--
-- 'vpcConfigurationId', 'deleteApplicationVpcConfiguration_vpcConfigurationId' - The ID of the VPC configuration to delete.
newDeleteApplicationVpcConfiguration ::
  -- | 'applicationName'
  Prelude.Text ->
  -- | 'vpcConfigurationId'
  Prelude.Text ->
  DeleteApplicationVpcConfiguration
newDeleteApplicationVpcConfiguration :: Text -> Text -> DeleteApplicationVpcConfiguration
newDeleteApplicationVpcConfiguration
  Text
pApplicationName_
  Text
pVpcConfigurationId_ =
    DeleteApplicationVpcConfiguration'
      { $sel:conditionalToken:DeleteApplicationVpcConfiguration' :: Maybe Text
conditionalToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:currentApplicationVersionId:DeleteApplicationVpcConfiguration' :: Maybe Natural
currentApplicationVersionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:applicationName:DeleteApplicationVpcConfiguration' :: Text
applicationName = Text
pApplicationName_,
        $sel:vpcConfigurationId:DeleteApplicationVpcConfiguration' :: Text
vpcConfigurationId =
          Text
pVpcConfigurationId_
      }

-- | A value you use to implement strong concurrency for application updates.
-- You must provide the @CurrentApplicationVersionId@ or the
-- @ConditionalToken@. You get the application\'s current
-- @ConditionalToken@ using DescribeApplication. For better concurrency
-- support, use the @ConditionalToken@ parameter instead of
-- @CurrentApplicationVersionId@.
deleteApplicationVpcConfiguration_conditionalToken :: Lens.Lens' DeleteApplicationVpcConfiguration (Prelude.Maybe Prelude.Text)
deleteApplicationVpcConfiguration_conditionalToken :: Lens' DeleteApplicationVpcConfiguration (Maybe Text)
deleteApplicationVpcConfiguration_conditionalToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplicationVpcConfiguration' {Maybe Text
conditionalToken :: Maybe Text
$sel:conditionalToken:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Text
conditionalToken} -> Maybe Text
conditionalToken) (\s :: DeleteApplicationVpcConfiguration
s@DeleteApplicationVpcConfiguration' {} Maybe Text
a -> DeleteApplicationVpcConfiguration
s {$sel:conditionalToken:DeleteApplicationVpcConfiguration' :: Maybe Text
conditionalToken = Maybe Text
a} :: DeleteApplicationVpcConfiguration)

-- | The current application version ID. You must provide the
-- @CurrentApplicationVersionId@ or the @ConditionalToken@. You can
-- retrieve the application version ID using DescribeApplication. For
-- better concurrency support, use the @ConditionalToken@ parameter instead
-- of @CurrentApplicationVersionId@.
deleteApplicationVpcConfiguration_currentApplicationVersionId :: Lens.Lens' DeleteApplicationVpcConfiguration (Prelude.Maybe Prelude.Natural)
deleteApplicationVpcConfiguration_currentApplicationVersionId :: Lens' DeleteApplicationVpcConfiguration (Maybe Natural)
deleteApplicationVpcConfiguration_currentApplicationVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplicationVpcConfiguration' {Maybe Natural
currentApplicationVersionId :: Maybe Natural
$sel:currentApplicationVersionId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Natural
currentApplicationVersionId} -> Maybe Natural
currentApplicationVersionId) (\s :: DeleteApplicationVpcConfiguration
s@DeleteApplicationVpcConfiguration' {} Maybe Natural
a -> DeleteApplicationVpcConfiguration
s {$sel:currentApplicationVersionId:DeleteApplicationVpcConfiguration' :: Maybe Natural
currentApplicationVersionId = Maybe Natural
a} :: DeleteApplicationVpcConfiguration)

-- | The name of an existing application.
deleteApplicationVpcConfiguration_applicationName :: Lens.Lens' DeleteApplicationVpcConfiguration Prelude.Text
deleteApplicationVpcConfiguration_applicationName :: Lens' DeleteApplicationVpcConfiguration Text
deleteApplicationVpcConfiguration_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplicationVpcConfiguration' {Text
applicationName :: Text
$sel:applicationName:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
applicationName} -> Text
applicationName) (\s :: DeleteApplicationVpcConfiguration
s@DeleteApplicationVpcConfiguration' {} Text
a -> DeleteApplicationVpcConfiguration
s {$sel:applicationName:DeleteApplicationVpcConfiguration' :: Text
applicationName = Text
a} :: DeleteApplicationVpcConfiguration)

-- | The ID of the VPC configuration to delete.
deleteApplicationVpcConfiguration_vpcConfigurationId :: Lens.Lens' DeleteApplicationVpcConfiguration Prelude.Text
deleteApplicationVpcConfiguration_vpcConfigurationId :: Lens' DeleteApplicationVpcConfiguration Text
deleteApplicationVpcConfiguration_vpcConfigurationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplicationVpcConfiguration' {Text
vpcConfigurationId :: Text
$sel:vpcConfigurationId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
vpcConfigurationId} -> Text
vpcConfigurationId) (\s :: DeleteApplicationVpcConfiguration
s@DeleteApplicationVpcConfiguration' {} Text
a -> DeleteApplicationVpcConfiguration
s {$sel:vpcConfigurationId:DeleteApplicationVpcConfiguration' :: Text
vpcConfigurationId = Text
a} :: DeleteApplicationVpcConfiguration)

instance
  Core.AWSRequest
    DeleteApplicationVpcConfiguration
  where
  type
    AWSResponse DeleteApplicationVpcConfiguration =
      DeleteApplicationVpcConfigurationResponse
  request :: (Service -> Service)
-> DeleteApplicationVpcConfiguration
-> Request DeleteApplicationVpcConfiguration
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 DeleteApplicationVpcConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DeleteApplicationVpcConfiguration)))
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 Natural
-> Int
-> DeleteApplicationVpcConfigurationResponse
DeleteApplicationVpcConfigurationResponse'
            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
"ApplicationARN")
            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
"ApplicationVersionId")
            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
    DeleteApplicationVpcConfiguration
  where
  hashWithSalt :: Int -> DeleteApplicationVpcConfiguration -> Int
hashWithSalt
    Int
_salt
    DeleteApplicationVpcConfiguration' {Maybe Natural
Maybe Text
Text
vpcConfigurationId :: Text
applicationName :: Text
currentApplicationVersionId :: Maybe Natural
conditionalToken :: Maybe Text
$sel:vpcConfigurationId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
$sel:applicationName:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
$sel:currentApplicationVersionId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Natural
$sel:conditionalToken:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
conditionalToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
currentApplicationVersionId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcConfigurationId

instance
  Prelude.NFData
    DeleteApplicationVpcConfiguration
  where
  rnf :: DeleteApplicationVpcConfiguration -> ()
rnf DeleteApplicationVpcConfiguration' {Maybe Natural
Maybe Text
Text
vpcConfigurationId :: Text
applicationName :: Text
currentApplicationVersionId :: Maybe Natural
conditionalToken :: Maybe Text
$sel:vpcConfigurationId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
$sel:applicationName:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
$sel:currentApplicationVersionId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Natural
$sel:conditionalToken:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
conditionalToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
currentApplicationVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcConfigurationId

instance
  Data.ToHeaders
    DeleteApplicationVpcConfiguration
  where
  toHeaders :: DeleteApplicationVpcConfiguration -> 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
"KinesisAnalytics_20180523.DeleteApplicationVpcConfiguration" ::
                          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
    DeleteApplicationVpcConfiguration
  where
  toJSON :: DeleteApplicationVpcConfiguration -> Value
toJSON DeleteApplicationVpcConfiguration' {Maybe Natural
Maybe Text
Text
vpcConfigurationId :: Text
applicationName :: Text
currentApplicationVersionId :: Maybe Natural
conditionalToken :: Maybe Text
$sel:vpcConfigurationId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
$sel:applicationName:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Text
$sel:currentApplicationVersionId:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Natural
$sel:conditionalToken:DeleteApplicationVpcConfiguration' :: DeleteApplicationVpcConfiguration -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConditionalToken" 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
conditionalToken,
            (Key
"CurrentApplicationVersionId" 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 Natural
currentApplicationVersionId,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ApplicationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"VpcConfigurationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
vpcConfigurationId)
          ]
      )

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

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

-- | /See:/ 'newDeleteApplicationVpcConfigurationResponse' smart constructor.
data DeleteApplicationVpcConfigurationResponse = DeleteApplicationVpcConfigurationResponse'
  { -- | The ARN of the Kinesis Data Analytics application.
    DeleteApplicationVpcConfigurationResponse -> Maybe Text
applicationARN :: Prelude.Maybe Prelude.Text,
    -- | The updated version ID of the application.
    DeleteApplicationVpcConfigurationResponse -> Maybe Natural
applicationVersionId :: Prelude.Maybe Prelude.Natural,
    -- | The response's http status code.
    DeleteApplicationVpcConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteApplicationVpcConfigurationResponse
-> DeleteApplicationVpcConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteApplicationVpcConfigurationResponse
-> DeleteApplicationVpcConfigurationResponse -> Bool
$c/= :: DeleteApplicationVpcConfigurationResponse
-> DeleteApplicationVpcConfigurationResponse -> Bool
== :: DeleteApplicationVpcConfigurationResponse
-> DeleteApplicationVpcConfigurationResponse -> Bool
$c== :: DeleteApplicationVpcConfigurationResponse
-> DeleteApplicationVpcConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteApplicationVpcConfigurationResponse]
ReadPrec DeleteApplicationVpcConfigurationResponse
Int -> ReadS DeleteApplicationVpcConfigurationResponse
ReadS [DeleteApplicationVpcConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteApplicationVpcConfigurationResponse]
$creadListPrec :: ReadPrec [DeleteApplicationVpcConfigurationResponse]
readPrec :: ReadPrec DeleteApplicationVpcConfigurationResponse
$creadPrec :: ReadPrec DeleteApplicationVpcConfigurationResponse
readList :: ReadS [DeleteApplicationVpcConfigurationResponse]
$creadList :: ReadS [DeleteApplicationVpcConfigurationResponse]
readsPrec :: Int -> ReadS DeleteApplicationVpcConfigurationResponse
$creadsPrec :: Int -> ReadS DeleteApplicationVpcConfigurationResponse
Prelude.Read, Int -> DeleteApplicationVpcConfigurationResponse -> ShowS
[DeleteApplicationVpcConfigurationResponse] -> ShowS
DeleteApplicationVpcConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteApplicationVpcConfigurationResponse] -> ShowS
$cshowList :: [DeleteApplicationVpcConfigurationResponse] -> ShowS
show :: DeleteApplicationVpcConfigurationResponse -> String
$cshow :: DeleteApplicationVpcConfigurationResponse -> String
showsPrec :: Int -> DeleteApplicationVpcConfigurationResponse -> ShowS
$cshowsPrec :: Int -> DeleteApplicationVpcConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteApplicationVpcConfigurationResponse x
-> DeleteApplicationVpcConfigurationResponse
forall x.
DeleteApplicationVpcConfigurationResponse
-> Rep DeleteApplicationVpcConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteApplicationVpcConfigurationResponse x
-> DeleteApplicationVpcConfigurationResponse
$cfrom :: forall x.
DeleteApplicationVpcConfigurationResponse
-> Rep DeleteApplicationVpcConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteApplicationVpcConfigurationResponse' 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:
--
-- 'applicationARN', 'deleteApplicationVpcConfigurationResponse_applicationARN' - The ARN of the Kinesis Data Analytics application.
--
-- 'applicationVersionId', 'deleteApplicationVpcConfigurationResponse_applicationVersionId' - The updated version ID of the application.
--
-- 'httpStatus', 'deleteApplicationVpcConfigurationResponse_httpStatus' - The response's http status code.
newDeleteApplicationVpcConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteApplicationVpcConfigurationResponse
newDeleteApplicationVpcConfigurationResponse :: Int -> DeleteApplicationVpcConfigurationResponse
newDeleteApplicationVpcConfigurationResponse
  Int
pHttpStatus_ =
    DeleteApplicationVpcConfigurationResponse'
      { $sel:applicationARN:DeleteApplicationVpcConfigurationResponse' :: Maybe Text
applicationARN =
          forall a. Maybe a
Prelude.Nothing,
        $sel:applicationVersionId:DeleteApplicationVpcConfigurationResponse' :: Maybe Natural
applicationVersionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DeleteApplicationVpcConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The ARN of the Kinesis Data Analytics application.
deleteApplicationVpcConfigurationResponse_applicationARN :: Lens.Lens' DeleteApplicationVpcConfigurationResponse (Prelude.Maybe Prelude.Text)
deleteApplicationVpcConfigurationResponse_applicationARN :: Lens' DeleteApplicationVpcConfigurationResponse (Maybe Text)
deleteApplicationVpcConfigurationResponse_applicationARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplicationVpcConfigurationResponse' {Maybe Text
applicationARN :: Maybe Text
$sel:applicationARN:DeleteApplicationVpcConfigurationResponse' :: DeleteApplicationVpcConfigurationResponse -> Maybe Text
applicationARN} -> Maybe Text
applicationARN) (\s :: DeleteApplicationVpcConfigurationResponse
s@DeleteApplicationVpcConfigurationResponse' {} Maybe Text
a -> DeleteApplicationVpcConfigurationResponse
s {$sel:applicationARN:DeleteApplicationVpcConfigurationResponse' :: Maybe Text
applicationARN = Maybe Text
a} :: DeleteApplicationVpcConfigurationResponse)

-- | The updated version ID of the application.
deleteApplicationVpcConfigurationResponse_applicationVersionId :: Lens.Lens' DeleteApplicationVpcConfigurationResponse (Prelude.Maybe Prelude.Natural)
deleteApplicationVpcConfigurationResponse_applicationVersionId :: Lens' DeleteApplicationVpcConfigurationResponse (Maybe Natural)
deleteApplicationVpcConfigurationResponse_applicationVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteApplicationVpcConfigurationResponse' {Maybe Natural
applicationVersionId :: Maybe Natural
$sel:applicationVersionId:DeleteApplicationVpcConfigurationResponse' :: DeleteApplicationVpcConfigurationResponse -> Maybe Natural
applicationVersionId} -> Maybe Natural
applicationVersionId) (\s :: DeleteApplicationVpcConfigurationResponse
s@DeleteApplicationVpcConfigurationResponse' {} Maybe Natural
a -> DeleteApplicationVpcConfigurationResponse
s {$sel:applicationVersionId:DeleteApplicationVpcConfigurationResponse' :: Maybe Natural
applicationVersionId = Maybe Natural
a} :: DeleteApplicationVpcConfigurationResponse)

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

instance
  Prelude.NFData
    DeleteApplicationVpcConfigurationResponse
  where
  rnf :: DeleteApplicationVpcConfigurationResponse -> ()
rnf DeleteApplicationVpcConfigurationResponse' {Int
Maybe Natural
Maybe Text
httpStatus :: Int
applicationVersionId :: Maybe Natural
applicationARN :: Maybe Text
$sel:httpStatus:DeleteApplicationVpcConfigurationResponse' :: DeleteApplicationVpcConfigurationResponse -> Int
$sel:applicationVersionId:DeleteApplicationVpcConfigurationResponse' :: DeleteApplicationVpcConfigurationResponse -> Maybe Natural
$sel:applicationARN:DeleteApplicationVpcConfigurationResponse' :: DeleteApplicationVpcConfigurationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationARN
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
applicationVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus