{-# 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.DetachClassicLinkVpc
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- 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/.
--
-- Unlinks (detaches) a linked EC2-Classic instance from a VPC. After the
-- instance has been unlinked, the VPC security groups are no longer
-- associated with it. An instance is automatically unlinked from a VPC
-- when it\'s stopped.
module Amazonka.EC2.DetachClassicLinkVpc
  ( -- * Creating a Request
    DetachClassicLinkVpc (..),
    newDetachClassicLinkVpc,

    -- * Request Lenses
    detachClassicLinkVpc_dryRun,
    detachClassicLinkVpc_instanceId,
    detachClassicLinkVpc_vpcId,

    -- * Destructuring the Response
    DetachClassicLinkVpcResponse (..),
    newDetachClassicLinkVpcResponse,

    -- * Response Lenses
    detachClassicLinkVpcResponse_return,
    detachClassicLinkVpcResponse_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:/ 'newDetachClassicLinkVpc' smart constructor.
data DetachClassicLinkVpc = DetachClassicLinkVpc'
  { -- | 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@.
    DetachClassicLinkVpc -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the instance to unlink from the VPC.
    DetachClassicLinkVpc -> Text
instanceId :: Prelude.Text,
    -- | The ID of the VPC to which the instance is linked.
    DetachClassicLinkVpc -> Text
vpcId :: Prelude.Text
  }
  deriving (DetachClassicLinkVpc -> DetachClassicLinkVpc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachClassicLinkVpc -> DetachClassicLinkVpc -> Bool
$c/= :: DetachClassicLinkVpc -> DetachClassicLinkVpc -> Bool
== :: DetachClassicLinkVpc -> DetachClassicLinkVpc -> Bool
$c== :: DetachClassicLinkVpc -> DetachClassicLinkVpc -> Bool
Prelude.Eq, ReadPrec [DetachClassicLinkVpc]
ReadPrec DetachClassicLinkVpc
Int -> ReadS DetachClassicLinkVpc
ReadS [DetachClassicLinkVpc]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachClassicLinkVpc]
$creadListPrec :: ReadPrec [DetachClassicLinkVpc]
readPrec :: ReadPrec DetachClassicLinkVpc
$creadPrec :: ReadPrec DetachClassicLinkVpc
readList :: ReadS [DetachClassicLinkVpc]
$creadList :: ReadS [DetachClassicLinkVpc]
readsPrec :: Int -> ReadS DetachClassicLinkVpc
$creadsPrec :: Int -> ReadS DetachClassicLinkVpc
Prelude.Read, Int -> DetachClassicLinkVpc -> ShowS
[DetachClassicLinkVpc] -> ShowS
DetachClassicLinkVpc -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachClassicLinkVpc] -> ShowS
$cshowList :: [DetachClassicLinkVpc] -> ShowS
show :: DetachClassicLinkVpc -> String
$cshow :: DetachClassicLinkVpc -> String
showsPrec :: Int -> DetachClassicLinkVpc -> ShowS
$cshowsPrec :: Int -> DetachClassicLinkVpc -> ShowS
Prelude.Show, forall x. Rep DetachClassicLinkVpc x -> DetachClassicLinkVpc
forall x. DetachClassicLinkVpc -> Rep DetachClassicLinkVpc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachClassicLinkVpc x -> DetachClassicLinkVpc
$cfrom :: forall x. DetachClassicLinkVpc -> Rep DetachClassicLinkVpc x
Prelude.Generic)

-- |
-- Create a value of 'DetachClassicLinkVpc' 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', 'detachClassicLinkVpc_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@.
--
-- 'instanceId', 'detachClassicLinkVpc_instanceId' - The ID of the instance to unlink from the VPC.
--
-- 'vpcId', 'detachClassicLinkVpc_vpcId' - The ID of the VPC to which the instance is linked.
newDetachClassicLinkVpc ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'vpcId'
  Prelude.Text ->
  DetachClassicLinkVpc
newDetachClassicLinkVpc :: Text -> Text -> DetachClassicLinkVpc
newDetachClassicLinkVpc Text
pInstanceId_ Text
pVpcId_ =
  DetachClassicLinkVpc'
    { $sel:dryRun:DetachClassicLinkVpc' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceId:DetachClassicLinkVpc' :: Text
instanceId = Text
pInstanceId_,
      $sel:vpcId:DetachClassicLinkVpc' :: 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@.
detachClassicLinkVpc_dryRun :: Lens.Lens' DetachClassicLinkVpc (Prelude.Maybe Prelude.Bool)
detachClassicLinkVpc_dryRun :: Lens' DetachClassicLinkVpc (Maybe Bool)
detachClassicLinkVpc_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachClassicLinkVpc' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: DetachClassicLinkVpc
s@DetachClassicLinkVpc' {} Maybe Bool
a -> DetachClassicLinkVpc
s {$sel:dryRun:DetachClassicLinkVpc' :: Maybe Bool
dryRun = Maybe Bool
a} :: DetachClassicLinkVpc)

-- | The ID of the instance to unlink from the VPC.
detachClassicLinkVpc_instanceId :: Lens.Lens' DetachClassicLinkVpc Prelude.Text
detachClassicLinkVpc_instanceId :: Lens' DetachClassicLinkVpc Text
detachClassicLinkVpc_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachClassicLinkVpc' {Text
instanceId :: Text
$sel:instanceId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
instanceId} -> Text
instanceId) (\s :: DetachClassicLinkVpc
s@DetachClassicLinkVpc' {} Text
a -> DetachClassicLinkVpc
s {$sel:instanceId:DetachClassicLinkVpc' :: Text
instanceId = Text
a} :: DetachClassicLinkVpc)

-- | The ID of the VPC to which the instance is linked.
detachClassicLinkVpc_vpcId :: Lens.Lens' DetachClassicLinkVpc Prelude.Text
detachClassicLinkVpc_vpcId :: Lens' DetachClassicLinkVpc Text
detachClassicLinkVpc_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachClassicLinkVpc' {Text
vpcId :: Text
$sel:vpcId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
vpcId} -> Text
vpcId) (\s :: DetachClassicLinkVpc
s@DetachClassicLinkVpc' {} Text
a -> DetachClassicLinkVpc
s {$sel:vpcId:DetachClassicLinkVpc' :: Text
vpcId = Text
a} :: DetachClassicLinkVpc)

instance Core.AWSRequest DetachClassicLinkVpc where
  type
    AWSResponse DetachClassicLinkVpc =
      DetachClassicLinkVpcResponse
  request :: (Service -> Service)
-> DetachClassicLinkVpc -> Request DetachClassicLinkVpc
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 DetachClassicLinkVpc
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DetachClassicLinkVpc)))
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 -> DetachClassicLinkVpcResponse
DetachClassicLinkVpcResponse'
            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 DetachClassicLinkVpc where
  hashWithSalt :: Int -> DetachClassicLinkVpc -> Int
hashWithSalt Int
_salt DetachClassicLinkVpc' {Maybe Bool
Text
vpcId :: Text
instanceId :: Text
dryRun :: Maybe Bool
$sel:vpcId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
$sel:instanceId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
$sel:dryRun:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> 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
instanceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vpcId

instance Prelude.NFData DetachClassicLinkVpc where
  rnf :: DetachClassicLinkVpc -> ()
rnf DetachClassicLinkVpc' {Maybe Bool
Text
vpcId :: Text
instanceId :: Text
dryRun :: Maybe Bool
$sel:vpcId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
$sel:instanceId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
$sel:dryRun:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> 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
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vpcId

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

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

instance Data.ToQuery DetachClassicLinkVpc where
  toQuery :: DetachClassicLinkVpc -> QueryString
toQuery DetachClassicLinkVpc' {Maybe Bool
Text
vpcId :: Text
instanceId :: Text
dryRun :: Maybe Bool
$sel:vpcId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
$sel:instanceId:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Text
$sel:dryRun:DetachClassicLinkVpc' :: DetachClassicLinkVpc -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DetachClassicLinkVpc" :: 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
"InstanceId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
instanceId,
        ByteString
"VpcId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
vpcId
      ]

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

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

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

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

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