{-# 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.ModifyVpcTenancy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modifies the instance tenancy attribute of the specified VPC. You can
-- change the instance tenancy attribute of a VPC to @default@ only. You
-- cannot change the instance tenancy attribute to @dedicated@.
--
-- After you modify the tenancy of the VPC, any new instances that you
-- launch into the VPC have a tenancy of @default@, unless you specify
-- otherwise during launch. The tenancy of any existing instances in the
-- VPC is not affected.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/dedicated-instance.html Dedicated Instances>
-- in the /Amazon Elastic Compute Cloud User Guide/.
module Amazonka.EC2.ModifyVpcTenancy
  ( -- * Creating a Request
    ModifyVpcTenancy (..),
    newModifyVpcTenancy,

    -- * Request Lenses
    modifyVpcTenancy_dryRun,
    modifyVpcTenancy_vpcId,
    modifyVpcTenancy_instanceTenancy,

    -- * Destructuring the Response
    ModifyVpcTenancyResponse (..),
    newModifyVpcTenancyResponse,

    -- * Response Lenses
    modifyVpcTenancyResponse_returnValue,
    modifyVpcTenancyResponse_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:/ 'newModifyVpcTenancy' smart constructor.
data ModifyVpcTenancy = ModifyVpcTenancy'
  { -- | 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@.
    ModifyVpcTenancy -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the VPC.
    ModifyVpcTenancy -> Text
vpcId :: Prelude.Text,
    -- | The instance tenancy attribute for the VPC.
    ModifyVpcTenancy -> VpcTenancy
instanceTenancy :: VpcTenancy
  }
  deriving (ModifyVpcTenancy -> ModifyVpcTenancy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyVpcTenancy -> ModifyVpcTenancy -> Bool
$c/= :: ModifyVpcTenancy -> ModifyVpcTenancy -> Bool
== :: ModifyVpcTenancy -> ModifyVpcTenancy -> Bool
$c== :: ModifyVpcTenancy -> ModifyVpcTenancy -> Bool
Prelude.Eq, ReadPrec [ModifyVpcTenancy]
ReadPrec ModifyVpcTenancy
Int -> ReadS ModifyVpcTenancy
ReadS [ModifyVpcTenancy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyVpcTenancy]
$creadListPrec :: ReadPrec [ModifyVpcTenancy]
readPrec :: ReadPrec ModifyVpcTenancy
$creadPrec :: ReadPrec ModifyVpcTenancy
readList :: ReadS [ModifyVpcTenancy]
$creadList :: ReadS [ModifyVpcTenancy]
readsPrec :: Int -> ReadS ModifyVpcTenancy
$creadsPrec :: Int -> ReadS ModifyVpcTenancy
Prelude.Read, Int -> ModifyVpcTenancy -> ShowS
[ModifyVpcTenancy] -> ShowS
ModifyVpcTenancy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyVpcTenancy] -> ShowS
$cshowList :: [ModifyVpcTenancy] -> ShowS
show :: ModifyVpcTenancy -> String
$cshow :: ModifyVpcTenancy -> String
showsPrec :: Int -> ModifyVpcTenancy -> ShowS
$cshowsPrec :: Int -> ModifyVpcTenancy -> ShowS
Prelude.Show, forall x. Rep ModifyVpcTenancy x -> ModifyVpcTenancy
forall x. ModifyVpcTenancy -> Rep ModifyVpcTenancy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyVpcTenancy x -> ModifyVpcTenancy
$cfrom :: forall x. ModifyVpcTenancy -> Rep ModifyVpcTenancy x
Prelude.Generic)

-- |
-- Create a value of 'ModifyVpcTenancy' 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', 'modifyVpcTenancy_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', 'modifyVpcTenancy_vpcId' - The ID of the VPC.
--
-- 'instanceTenancy', 'modifyVpcTenancy_instanceTenancy' - The instance tenancy attribute for the VPC.
newModifyVpcTenancy ::
  -- | 'vpcId'
  Prelude.Text ->
  -- | 'instanceTenancy'
  VpcTenancy ->
  ModifyVpcTenancy
newModifyVpcTenancy :: Text -> VpcTenancy -> ModifyVpcTenancy
newModifyVpcTenancy Text
pVpcId_ VpcTenancy
pInstanceTenancy_ =
  ModifyVpcTenancy'
    { $sel:dryRun:ModifyVpcTenancy' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:ModifyVpcTenancy' :: Text
vpcId = Text
pVpcId_,
      $sel:instanceTenancy:ModifyVpcTenancy' :: VpcTenancy
instanceTenancy = VpcTenancy
pInstanceTenancy_
    }

-- | 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@.
modifyVpcTenancy_dryRun :: Lens.Lens' ModifyVpcTenancy (Prelude.Maybe Prelude.Bool)
modifyVpcTenancy_dryRun :: Lens' ModifyVpcTenancy (Maybe Bool)
modifyVpcTenancy_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVpcTenancy' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ModifyVpcTenancy' :: ModifyVpcTenancy -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ModifyVpcTenancy
s@ModifyVpcTenancy' {} Maybe Bool
a -> ModifyVpcTenancy
s {$sel:dryRun:ModifyVpcTenancy' :: Maybe Bool
dryRun = Maybe Bool
a} :: ModifyVpcTenancy)

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

-- | The instance tenancy attribute for the VPC.
modifyVpcTenancy_instanceTenancy :: Lens.Lens' ModifyVpcTenancy VpcTenancy
modifyVpcTenancy_instanceTenancy :: Lens' ModifyVpcTenancy VpcTenancy
modifyVpcTenancy_instanceTenancy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyVpcTenancy' {VpcTenancy
instanceTenancy :: VpcTenancy
$sel:instanceTenancy:ModifyVpcTenancy' :: ModifyVpcTenancy -> VpcTenancy
instanceTenancy} -> VpcTenancy
instanceTenancy) (\s :: ModifyVpcTenancy
s@ModifyVpcTenancy' {} VpcTenancy
a -> ModifyVpcTenancy
s {$sel:instanceTenancy:ModifyVpcTenancy' :: VpcTenancy
instanceTenancy = VpcTenancy
a} :: ModifyVpcTenancy)

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

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

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

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

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

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

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

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

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

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