{-# 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.EC2.DisableVpcClassicLink
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disables ClassicLink for a VPC. You cannot disable ClassicLink for a VPC
-- that has EC2-Classic instances linked to it.
--
-- We are retiring EC2-Classic. We recommend that you migrate from
-- EC2-Classic to a VPC. For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/vpc-migrate.html Migrate from EC2-Classic to a VPC>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.DisableVpcClassicLink
  ( -- * Creating a Request
    DisableVpcClassicLink (..),
    newDisableVpcClassicLink,

    -- * Request Lenses
    disableVpcClassicLink_dryRun,
    disableVpcClassicLink_vpcId,

    -- * Destructuring the Response
    DisableVpcClassicLinkResponse (..),
    newDisableVpcClassicLinkResponse,

    -- * Response Lenses
    disableVpcClassicLinkResponse_return,
    disableVpcClassicLinkResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDisableVpcClassicLink' smart constructor.
data DisableVpcClassicLink = DisableVpcClassicLink'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    DisableVpcClassicLink -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the VPC.
    DisableVpcClassicLink -> Text
vpcId :: Prelude.Text
  }
  deriving (DisableVpcClassicLink -> DisableVpcClassicLink -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableVpcClassicLink -> DisableVpcClassicLink -> Bool
$c/= :: DisableVpcClassicLink -> DisableVpcClassicLink -> Bool
== :: DisableVpcClassicLink -> DisableVpcClassicLink -> Bool
$c== :: DisableVpcClassicLink -> DisableVpcClassicLink -> Bool
Prelude.Eq, ReadPrec [DisableVpcClassicLink]
ReadPrec DisableVpcClassicLink
Int -> ReadS DisableVpcClassicLink
ReadS [DisableVpcClassicLink]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableVpcClassicLink]
$creadListPrec :: ReadPrec [DisableVpcClassicLink]
readPrec :: ReadPrec DisableVpcClassicLink
$creadPrec :: ReadPrec DisableVpcClassicLink
readList :: ReadS [DisableVpcClassicLink]
$creadList :: ReadS [DisableVpcClassicLink]
readsPrec :: Int -> ReadS DisableVpcClassicLink
$creadsPrec :: Int -> ReadS DisableVpcClassicLink
Prelude.Read, Int -> DisableVpcClassicLink -> ShowS
[DisableVpcClassicLink] -> ShowS
DisableVpcClassicLink -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableVpcClassicLink] -> ShowS
$cshowList :: [DisableVpcClassicLink] -> ShowS
show :: DisableVpcClassicLink -> String
$cshow :: DisableVpcClassicLink -> String
showsPrec :: Int -> DisableVpcClassicLink -> ShowS
$cshowsPrec :: Int -> DisableVpcClassicLink -> ShowS
Prelude.Show, forall x. Rep DisableVpcClassicLink x -> DisableVpcClassicLink
forall x. DisableVpcClassicLink -> Rep DisableVpcClassicLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisableVpcClassicLink x -> DisableVpcClassicLink
$cfrom :: forall x. DisableVpcClassicLink -> Rep DisableVpcClassicLink x
Prelude.Generic)

-- |
-- Create a value of 'DisableVpcClassicLink' 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:
--
-- 'dryRun', 'disableVpcClassicLink_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'vpcId', 'disableVpcClassicLink_vpcId' - The ID of the VPC.
newDisableVpcClassicLink ::
  -- | 'vpcId'
  Prelude.Text ->
  DisableVpcClassicLink
newDisableVpcClassicLink :: Text -> DisableVpcClassicLink
newDisableVpcClassicLink Text
pVpcId_ =
  DisableVpcClassicLink'
    { $sel:dryRun:DisableVpcClassicLink' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:DisableVpcClassicLink' :: Text
vpcId = Text
pVpcId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
disableVpcClassicLink_dryRun :: Lens.Lens' DisableVpcClassicLink (Prelude.Maybe Prelude.Bool)
disableVpcClassicLink_dryRun :: Lens' DisableVpcClassicLink (Maybe Bool)
disableVpcClassicLink_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableVpcClassicLink' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DisableVpcClassicLink' :: DisableVpcClassicLink -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DisableVpcClassicLink
s@DisableVpcClassicLink' {} Maybe Bool
a -> DisableVpcClassicLink
s {$sel:dryRun:DisableVpcClassicLink' :: Maybe Bool
dryRun = Maybe Bool
a} :: DisableVpcClassicLink)

-- | The ID of the VPC.
disableVpcClassicLink_vpcId :: Lens.Lens' DisableVpcClassicLink Prelude.Text
disableVpcClassicLink_vpcId :: Lens' DisableVpcClassicLink Text
disableVpcClassicLink_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableVpcClassicLink' {Text
vpcId :: Text
$sel:vpcId:DisableVpcClassicLink' :: DisableVpcClassicLink -> Text
vpcId} -> Text
vpcId) (\s :: DisableVpcClassicLink
s@DisableVpcClassicLink' {} Text
a -> DisableVpcClassicLink
s {$sel:vpcId:DisableVpcClassicLink' :: Text
vpcId = Text
a} :: DisableVpcClassicLink)

instance Core.AWSRequest DisableVpcClassicLink where
  type
    AWSResponse DisableVpcClassicLink =
      DisableVpcClassicLinkResponse
  request :: (Service -> Service)
-> DisableVpcClassicLink -> Request DisableVpcClassicLink
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DisableVpcClassicLink
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisableVpcClassicLink)))
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 Bool -> Int -> DisableVpcClassicLinkResponse
DisableVpcClassicLinkResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"return")
            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 DisableVpcClassicLink where
  hashWithSalt :: Int -> DisableVpcClassicLink -> Int
hashWithSalt Int
_salt DisableVpcClassicLink' {Maybe Bool
Text
vpcId :: Text
dryRun :: Maybe Bool
$sel:vpcId:DisableVpcClassicLink' :: DisableVpcClassicLink -> Text
$sel:dryRun:DisableVpcClassicLink' :: DisableVpcClassicLink -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcId

instance Prelude.NFData DisableVpcClassicLink where
  rnf :: DisableVpcClassicLink -> ()
rnf DisableVpcClassicLink' {Maybe Bool
Text
vpcId :: Text
dryRun :: Maybe Bool
$sel:vpcId:DisableVpcClassicLink' :: DisableVpcClassicLink -> Text
$sel:dryRun:DisableVpcClassicLink' :: DisableVpcClassicLink -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcId

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

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

instance Data.ToQuery DisableVpcClassicLink where
  toQuery :: DisableVpcClassicLink -> QueryString
toQuery DisableVpcClassicLink' {Maybe Bool
Text
vpcId :: Text
dryRun :: Maybe Bool
$sel:vpcId:DisableVpcClassicLink' :: DisableVpcClassicLink -> Text
$sel:dryRun:DisableVpcClassicLink' :: DisableVpcClassicLink -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DisableVpcClassicLink" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"VpcId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
vpcId
      ]

-- | /See:/ 'newDisableVpcClassicLinkResponse' smart constructor.
data DisableVpcClassicLinkResponse = DisableVpcClassicLinkResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    DisableVpcClassicLinkResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    DisableVpcClassicLinkResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisableVpcClassicLinkResponse
-> DisableVpcClassicLinkResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableVpcClassicLinkResponse
-> DisableVpcClassicLinkResponse -> Bool
$c/= :: DisableVpcClassicLinkResponse
-> DisableVpcClassicLinkResponse -> Bool
== :: DisableVpcClassicLinkResponse
-> DisableVpcClassicLinkResponse -> Bool
$c== :: DisableVpcClassicLinkResponse
-> DisableVpcClassicLinkResponse -> Bool
Prelude.Eq, ReadPrec [DisableVpcClassicLinkResponse]
ReadPrec DisableVpcClassicLinkResponse
Int -> ReadS DisableVpcClassicLinkResponse
ReadS [DisableVpcClassicLinkResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisableVpcClassicLinkResponse]
$creadListPrec :: ReadPrec [DisableVpcClassicLinkResponse]
readPrec :: ReadPrec DisableVpcClassicLinkResponse
$creadPrec :: ReadPrec DisableVpcClassicLinkResponse
readList :: ReadS [DisableVpcClassicLinkResponse]
$creadList :: ReadS [DisableVpcClassicLinkResponse]
readsPrec :: Int -> ReadS DisableVpcClassicLinkResponse
$creadsPrec :: Int -> ReadS DisableVpcClassicLinkResponse
Prelude.Read, Int -> DisableVpcClassicLinkResponse -> ShowS
[DisableVpcClassicLinkResponse] -> ShowS
DisableVpcClassicLinkResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableVpcClassicLinkResponse] -> ShowS
$cshowList :: [DisableVpcClassicLinkResponse] -> ShowS
show :: DisableVpcClassicLinkResponse -> String
$cshow :: DisableVpcClassicLinkResponse -> String
showsPrec :: Int -> DisableVpcClassicLinkResponse -> ShowS
$cshowsPrec :: Int -> DisableVpcClassicLinkResponse -> ShowS
Prelude.Show, forall x.
Rep DisableVpcClassicLinkResponse x
-> DisableVpcClassicLinkResponse
forall x.
DisableVpcClassicLinkResponse
-> Rep DisableVpcClassicLinkResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisableVpcClassicLinkResponse x
-> DisableVpcClassicLinkResponse
$cfrom :: forall x.
DisableVpcClassicLinkResponse
-> Rep DisableVpcClassicLinkResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisableVpcClassicLinkResponse' 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:
--
-- 'return'', 'disableVpcClassicLinkResponse_return' - Returns @true@ if the request succeeds; otherwise, it returns an error.
--
-- 'httpStatus', 'disableVpcClassicLinkResponse_httpStatus' - The response's http status code.
newDisableVpcClassicLinkResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisableVpcClassicLinkResponse
newDisableVpcClassicLinkResponse :: Int -> DisableVpcClassicLinkResponse
newDisableVpcClassicLinkResponse Int
pHttpStatus_ =
  DisableVpcClassicLinkResponse'
    { $sel:return':DisableVpcClassicLinkResponse' :: Maybe Bool
return' =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DisableVpcClassicLinkResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns @true@ if the request succeeds; otherwise, it returns an error.
disableVpcClassicLinkResponse_return :: Lens.Lens' DisableVpcClassicLinkResponse (Prelude.Maybe Prelude.Bool)
disableVpcClassicLinkResponse_return :: Lens' DisableVpcClassicLinkResponse (Maybe Bool)
disableVpcClassicLinkResponse_return = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisableVpcClassicLinkResponse' {Maybe Bool
return' :: Maybe Bool
$sel:return':DisableVpcClassicLinkResponse' :: DisableVpcClassicLinkResponse -> Maybe Bool
return'} -> Maybe Bool
return') (\s :: DisableVpcClassicLinkResponse
s@DisableVpcClassicLinkResponse' {} Maybe Bool
a -> DisableVpcClassicLinkResponse
s {$sel:return':DisableVpcClassicLinkResponse' :: Maybe Bool
return' = Maybe Bool
a} :: DisableVpcClassicLinkResponse)

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

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