{-# 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.AttachClassicLinkVpc
-- 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/.
--
-- Links an EC2-Classic instance to a ClassicLink-enabled VPC through one
-- or more of the VPC\'s security groups. You cannot link an EC2-Classic
-- instance to more than one VPC at a time. You can only link an instance
-- that\'s in the @running@ state. An instance is automatically unlinked
-- from a VPC when it\'s stopped - you can link it to the VPC again when
-- you restart it.
--
-- After you\'ve linked an instance, you cannot change the VPC security
-- groups that are associated with it. To change the security groups, you
-- must first unlink the instance, and then link it again.
--
-- Linking your instance to a VPC is sometimes referred to as /attaching/
-- your instance.
module Amazonka.EC2.AttachClassicLinkVpc
  ( -- * Creating a Request
    AttachClassicLinkVpc (..),
    newAttachClassicLinkVpc,

    -- * Request Lenses
    attachClassicLinkVpc_dryRun,
    attachClassicLinkVpc_groups,
    attachClassicLinkVpc_instanceId,
    attachClassicLinkVpc_vpcId,

    -- * Destructuring the Response
    AttachClassicLinkVpcResponse (..),
    newAttachClassicLinkVpcResponse,

    -- * Response Lenses
    attachClassicLinkVpcResponse_return,
    attachClassicLinkVpcResponse_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:/ 'newAttachClassicLinkVpc' smart constructor.
data AttachClassicLinkVpc = AttachClassicLinkVpc'
  { -- | 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@.
    AttachClassicLinkVpc -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of one or more of the VPC\'s security groups. You cannot specify
    -- security groups from a different VPC.
    AttachClassicLinkVpc -> [Text]
groups :: [Prelude.Text],
    -- | The ID of an EC2-Classic instance to link to the ClassicLink-enabled
    -- VPC.
    AttachClassicLinkVpc -> Text
instanceId :: Prelude.Text,
    -- | The ID of a ClassicLink-enabled VPC.
    AttachClassicLinkVpc -> Text
vpcId :: Prelude.Text
  }
  deriving (AttachClassicLinkVpc -> AttachClassicLinkVpc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachClassicLinkVpc -> AttachClassicLinkVpc -> Bool
$c/= :: AttachClassicLinkVpc -> AttachClassicLinkVpc -> Bool
== :: AttachClassicLinkVpc -> AttachClassicLinkVpc -> Bool
$c== :: AttachClassicLinkVpc -> AttachClassicLinkVpc -> Bool
Prelude.Eq, ReadPrec [AttachClassicLinkVpc]
ReadPrec AttachClassicLinkVpc
Int -> ReadS AttachClassicLinkVpc
ReadS [AttachClassicLinkVpc]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachClassicLinkVpc]
$creadListPrec :: ReadPrec [AttachClassicLinkVpc]
readPrec :: ReadPrec AttachClassicLinkVpc
$creadPrec :: ReadPrec AttachClassicLinkVpc
readList :: ReadS [AttachClassicLinkVpc]
$creadList :: ReadS [AttachClassicLinkVpc]
readsPrec :: Int -> ReadS AttachClassicLinkVpc
$creadsPrec :: Int -> ReadS AttachClassicLinkVpc
Prelude.Read, Int -> AttachClassicLinkVpc -> ShowS
[AttachClassicLinkVpc] -> ShowS
AttachClassicLinkVpc -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachClassicLinkVpc] -> ShowS
$cshowList :: [AttachClassicLinkVpc] -> ShowS
show :: AttachClassicLinkVpc -> String
$cshow :: AttachClassicLinkVpc -> String
showsPrec :: Int -> AttachClassicLinkVpc -> ShowS
$cshowsPrec :: Int -> AttachClassicLinkVpc -> ShowS
Prelude.Show, forall x. Rep AttachClassicLinkVpc x -> AttachClassicLinkVpc
forall x. AttachClassicLinkVpc -> Rep AttachClassicLinkVpc x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachClassicLinkVpc x -> AttachClassicLinkVpc
$cfrom :: forall x. AttachClassicLinkVpc -> Rep AttachClassicLinkVpc x
Prelude.Generic)

-- |
-- Create a value of 'AttachClassicLinkVpc' 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', 'attachClassicLinkVpc_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@.
--
-- 'groups', 'attachClassicLinkVpc_groups' - The ID of one or more of the VPC\'s security groups. You cannot specify
-- security groups from a different VPC.
--
-- 'instanceId', 'attachClassicLinkVpc_instanceId' - The ID of an EC2-Classic instance to link to the ClassicLink-enabled
-- VPC.
--
-- 'vpcId', 'attachClassicLinkVpc_vpcId' - The ID of a ClassicLink-enabled VPC.
newAttachClassicLinkVpc ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'vpcId'
  Prelude.Text ->
  AttachClassicLinkVpc
newAttachClassicLinkVpc :: Text -> Text -> AttachClassicLinkVpc
newAttachClassicLinkVpc Text
pInstanceId_ Text
pVpcId_ =
  AttachClassicLinkVpc'
    { $sel:dryRun:AttachClassicLinkVpc' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:AttachClassicLinkVpc' :: [Text]
groups = forall a. Monoid a => a
Prelude.mempty,
      $sel:instanceId:AttachClassicLinkVpc' :: Text
instanceId = Text
pInstanceId_,
      $sel:vpcId:AttachClassicLinkVpc' :: 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@.
attachClassicLinkVpc_dryRun :: Lens.Lens' AttachClassicLinkVpc (Prelude.Maybe Prelude.Bool)
attachClassicLinkVpc_dryRun :: Lens' AttachClassicLinkVpc (Maybe Bool)
attachClassicLinkVpc_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachClassicLinkVpc' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: AttachClassicLinkVpc
s@AttachClassicLinkVpc' {} Maybe Bool
a -> AttachClassicLinkVpc
s {$sel:dryRun:AttachClassicLinkVpc' :: Maybe Bool
dryRun = Maybe Bool
a} :: AttachClassicLinkVpc)

-- | The ID of one or more of the VPC\'s security groups. You cannot specify
-- security groups from a different VPC.
attachClassicLinkVpc_groups :: Lens.Lens' AttachClassicLinkVpc [Prelude.Text]
attachClassicLinkVpc_groups :: Lens' AttachClassicLinkVpc [Text]
attachClassicLinkVpc_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachClassicLinkVpc' {[Text]
groups :: [Text]
$sel:groups:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> [Text]
groups} -> [Text]
groups) (\s :: AttachClassicLinkVpc
s@AttachClassicLinkVpc' {} [Text]
a -> AttachClassicLinkVpc
s {$sel:groups:AttachClassicLinkVpc' :: [Text]
groups = [Text]
a} :: AttachClassicLinkVpc) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The ID of an EC2-Classic instance to link to the ClassicLink-enabled
-- VPC.
attachClassicLinkVpc_instanceId :: Lens.Lens' AttachClassicLinkVpc Prelude.Text
attachClassicLinkVpc_instanceId :: Lens' AttachClassicLinkVpc Text
attachClassicLinkVpc_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachClassicLinkVpc' {Text
instanceId :: Text
$sel:instanceId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
instanceId} -> Text
instanceId) (\s :: AttachClassicLinkVpc
s@AttachClassicLinkVpc' {} Text
a -> AttachClassicLinkVpc
s {$sel:instanceId:AttachClassicLinkVpc' :: Text
instanceId = Text
a} :: AttachClassicLinkVpc)

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

instance Core.AWSRequest AttachClassicLinkVpc where
  type
    AWSResponse AttachClassicLinkVpc =
      AttachClassicLinkVpcResponse
  request :: (Service -> Service)
-> AttachClassicLinkVpc -> Request AttachClassicLinkVpc
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 AttachClassicLinkVpc
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AttachClassicLinkVpc)))
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 -> AttachClassicLinkVpcResponse
AttachClassicLinkVpcResponse'
            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 AttachClassicLinkVpc where
  hashWithSalt :: Int -> AttachClassicLinkVpc -> Int
hashWithSalt Int
_salt AttachClassicLinkVpc' {[Text]
Maybe Bool
Text
vpcId :: Text
instanceId :: Text
groups :: [Text]
dryRun :: Maybe Bool
$sel:vpcId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
$sel:instanceId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
$sel:groups:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> [Text]
$sel:dryRun:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> 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]
groups
      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 AttachClassicLinkVpc where
  rnf :: AttachClassicLinkVpc -> ()
rnf AttachClassicLinkVpc' {[Text]
Maybe Bool
Text
vpcId :: Text
instanceId :: Text
groups :: [Text]
dryRun :: Maybe Bool
$sel:vpcId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
$sel:instanceId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
$sel:groups:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> [Text]
$sel:dryRun:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> 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]
groups
      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 AttachClassicLinkVpc where
  toHeaders :: AttachClassicLinkVpc -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AttachClassicLinkVpc where
  toQuery :: AttachClassicLinkVpc -> QueryString
toQuery AttachClassicLinkVpc' {[Text]
Maybe Bool
Text
vpcId :: Text
instanceId :: Text
groups :: [Text]
dryRun :: Maybe Bool
$sel:vpcId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
$sel:instanceId:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Text
$sel:groups:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> [Text]
$sel:dryRun:AttachClassicLinkVpc' :: AttachClassicLinkVpc -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AttachClassicLinkVpc" :: 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,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"SecurityGroupId" [Text]
groups,
        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:/ 'newAttachClassicLinkVpcResponse' smart constructor.
data AttachClassicLinkVpcResponse = AttachClassicLinkVpcResponse'
  { -- | Returns @true@ if the request succeeds; otherwise, it returns an error.
    AttachClassicLinkVpcResponse -> Maybe Bool
return' :: Prelude.Maybe Prelude.Bool,
    -- | The response's http status code.
    AttachClassicLinkVpcResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AttachClassicLinkVpcResponse
-> AttachClassicLinkVpcResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachClassicLinkVpcResponse
-> AttachClassicLinkVpcResponse -> Bool
$c/= :: AttachClassicLinkVpcResponse
-> AttachClassicLinkVpcResponse -> Bool
== :: AttachClassicLinkVpcResponse
-> AttachClassicLinkVpcResponse -> Bool
$c== :: AttachClassicLinkVpcResponse
-> AttachClassicLinkVpcResponse -> Bool
Prelude.Eq, ReadPrec [AttachClassicLinkVpcResponse]
ReadPrec AttachClassicLinkVpcResponse
Int -> ReadS AttachClassicLinkVpcResponse
ReadS [AttachClassicLinkVpcResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachClassicLinkVpcResponse]
$creadListPrec :: ReadPrec [AttachClassicLinkVpcResponse]
readPrec :: ReadPrec AttachClassicLinkVpcResponse
$creadPrec :: ReadPrec AttachClassicLinkVpcResponse
readList :: ReadS [AttachClassicLinkVpcResponse]
$creadList :: ReadS [AttachClassicLinkVpcResponse]
readsPrec :: Int -> ReadS AttachClassicLinkVpcResponse
$creadsPrec :: Int -> ReadS AttachClassicLinkVpcResponse
Prelude.Read, Int -> AttachClassicLinkVpcResponse -> ShowS
[AttachClassicLinkVpcResponse] -> ShowS
AttachClassicLinkVpcResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachClassicLinkVpcResponse] -> ShowS
$cshowList :: [AttachClassicLinkVpcResponse] -> ShowS
show :: AttachClassicLinkVpcResponse -> String
$cshow :: AttachClassicLinkVpcResponse -> String
showsPrec :: Int -> AttachClassicLinkVpcResponse -> ShowS
$cshowsPrec :: Int -> AttachClassicLinkVpcResponse -> ShowS
Prelude.Show, forall x.
Rep AttachClassicLinkVpcResponse x -> AttachClassicLinkVpcResponse
forall x.
AttachClassicLinkVpcResponse -> Rep AttachClassicLinkVpcResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachClassicLinkVpcResponse x -> AttachClassicLinkVpcResponse
$cfrom :: forall x.
AttachClassicLinkVpcResponse -> Rep AttachClassicLinkVpcResponse x
Prelude.Generic)

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

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

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

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