{-# 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 #-}
module Amazonka.Route53.DeleteVPCAssociationAuthorization
(
DeleteVPCAssociationAuthorization (..),
newDeleteVPCAssociationAuthorization,
deleteVPCAssociationAuthorization_hostedZoneId,
deleteVPCAssociationAuthorization_vpc,
DeleteVPCAssociationAuthorizationResponse (..),
newDeleteVPCAssociationAuthorizationResponse,
deleteVPCAssociationAuthorizationResponse_httpStatus,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Route53.Types
data DeleteVPCAssociationAuthorization = DeleteVPCAssociationAuthorization'
{
DeleteVPCAssociationAuthorization -> ResourceId
hostedZoneId :: ResourceId,
DeleteVPCAssociationAuthorization -> VPC
vpc :: VPC
}
deriving (DeleteVPCAssociationAuthorization
-> DeleteVPCAssociationAuthorization -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVPCAssociationAuthorization
-> DeleteVPCAssociationAuthorization -> Bool
$c/= :: DeleteVPCAssociationAuthorization
-> DeleteVPCAssociationAuthorization -> Bool
== :: DeleteVPCAssociationAuthorization
-> DeleteVPCAssociationAuthorization -> Bool
$c== :: DeleteVPCAssociationAuthorization
-> DeleteVPCAssociationAuthorization -> Bool
Prelude.Eq, ReadPrec [DeleteVPCAssociationAuthorization]
ReadPrec DeleteVPCAssociationAuthorization
Int -> ReadS DeleteVPCAssociationAuthorization
ReadS [DeleteVPCAssociationAuthorization]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVPCAssociationAuthorization]
$creadListPrec :: ReadPrec [DeleteVPCAssociationAuthorization]
readPrec :: ReadPrec DeleteVPCAssociationAuthorization
$creadPrec :: ReadPrec DeleteVPCAssociationAuthorization
readList :: ReadS [DeleteVPCAssociationAuthorization]
$creadList :: ReadS [DeleteVPCAssociationAuthorization]
readsPrec :: Int -> ReadS DeleteVPCAssociationAuthorization
$creadsPrec :: Int -> ReadS DeleteVPCAssociationAuthorization
Prelude.Read, Int -> DeleteVPCAssociationAuthorization -> ShowS
[DeleteVPCAssociationAuthorization] -> ShowS
DeleteVPCAssociationAuthorization -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVPCAssociationAuthorization] -> ShowS
$cshowList :: [DeleteVPCAssociationAuthorization] -> ShowS
show :: DeleteVPCAssociationAuthorization -> String
$cshow :: DeleteVPCAssociationAuthorization -> String
showsPrec :: Int -> DeleteVPCAssociationAuthorization -> ShowS
$cshowsPrec :: Int -> DeleteVPCAssociationAuthorization -> ShowS
Prelude.Show, forall x.
Rep DeleteVPCAssociationAuthorization x
-> DeleteVPCAssociationAuthorization
forall x.
DeleteVPCAssociationAuthorization
-> Rep DeleteVPCAssociationAuthorization x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteVPCAssociationAuthorization x
-> DeleteVPCAssociationAuthorization
$cfrom :: forall x.
DeleteVPCAssociationAuthorization
-> Rep DeleteVPCAssociationAuthorization x
Prelude.Generic)
newDeleteVPCAssociationAuthorization ::
ResourceId ->
VPC ->
DeleteVPCAssociationAuthorization
newDeleteVPCAssociationAuthorization :: ResourceId -> VPC -> DeleteVPCAssociationAuthorization
newDeleteVPCAssociationAuthorization
ResourceId
pHostedZoneId_
VPC
pVPC_ =
DeleteVPCAssociationAuthorization'
{ $sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: ResourceId
hostedZoneId =
ResourceId
pHostedZoneId_,
$sel:vpc:DeleteVPCAssociationAuthorization' :: VPC
vpc = VPC
pVPC_
}
deleteVPCAssociationAuthorization_hostedZoneId :: Lens.Lens' DeleteVPCAssociationAuthorization ResourceId
deleteVPCAssociationAuthorization_hostedZoneId :: Lens' DeleteVPCAssociationAuthorization ResourceId
deleteVPCAssociationAuthorization_hostedZoneId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVPCAssociationAuthorization' {ResourceId
hostedZoneId :: ResourceId
$sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> ResourceId
hostedZoneId} -> ResourceId
hostedZoneId) (\s :: DeleteVPCAssociationAuthorization
s@DeleteVPCAssociationAuthorization' {} ResourceId
a -> DeleteVPCAssociationAuthorization
s {$sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: ResourceId
hostedZoneId = ResourceId
a} :: DeleteVPCAssociationAuthorization)
deleteVPCAssociationAuthorization_vpc :: Lens.Lens' DeleteVPCAssociationAuthorization VPC
deleteVPCAssociationAuthorization_vpc :: Lens' DeleteVPCAssociationAuthorization VPC
deleteVPCAssociationAuthorization_vpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVPCAssociationAuthorization' {VPC
vpc :: VPC
$sel:vpc:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> VPC
vpc} -> VPC
vpc) (\s :: DeleteVPCAssociationAuthorization
s@DeleteVPCAssociationAuthorization' {} VPC
a -> DeleteVPCAssociationAuthorization
s {$sel:vpc:DeleteVPCAssociationAuthorization' :: VPC
vpc = VPC
a} :: DeleteVPCAssociationAuthorization)
instance
Core.AWSRequest
DeleteVPCAssociationAuthorization
where
type
AWSResponse DeleteVPCAssociationAuthorization =
DeleteVPCAssociationAuthorizationResponse
request :: (Service -> Service)
-> DeleteVPCAssociationAuthorization
-> Request DeleteVPCAssociationAuthorization
request Service -> Service
overrides =
forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteVPCAssociationAuthorization
-> ClientResponse ClientBody
-> m (Either
Error
(ClientResponse (AWSResponse DeleteVPCAssociationAuthorization)))
response =
forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
( \Int
s ResponseHeaders
h ()
x ->
Int -> DeleteVPCAssociationAuthorizationResponse
DeleteVPCAssociationAuthorizationResponse'
forall (f :: * -> *) a b. Functor 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
DeleteVPCAssociationAuthorization
where
hashWithSalt :: Int -> DeleteVPCAssociationAuthorization -> Int
hashWithSalt
Int
_salt
DeleteVPCAssociationAuthorization' {ResourceId
VPC
vpc :: VPC
hostedZoneId :: ResourceId
$sel:vpc:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> VPC
$sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> ResourceId
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ResourceId
hostedZoneId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` VPC
vpc
instance
Prelude.NFData
DeleteVPCAssociationAuthorization
where
rnf :: DeleteVPCAssociationAuthorization -> ()
rnf DeleteVPCAssociationAuthorization' {ResourceId
VPC
vpc :: VPC
hostedZoneId :: ResourceId
$sel:vpc:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> VPC
$sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> ResourceId
..} =
forall a. NFData a => a -> ()
Prelude.rnf ResourceId
hostedZoneId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VPC
vpc
instance
Data.ToElement
DeleteVPCAssociationAuthorization
where
toElement :: DeleteVPCAssociationAuthorization -> Element
toElement =
forall a. ToXML a => Name -> a -> Element
Data.mkElement
Name
"{https://route53.amazonaws.com/doc/2013-04-01/}DeleteVPCAssociationAuthorizationRequest"
instance
Data.ToHeaders
DeleteVPCAssociationAuthorization
where
toHeaders :: DeleteVPCAssociationAuthorization -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance
Data.ToPath
DeleteVPCAssociationAuthorization
where
toPath :: DeleteVPCAssociationAuthorization -> ByteString
toPath DeleteVPCAssociationAuthorization' {ResourceId
VPC
vpc :: VPC
hostedZoneId :: ResourceId
$sel:vpc:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> VPC
$sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> ResourceId
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"/2013-04-01/hostedzone/",
forall a. ToByteString a => a -> ByteString
Data.toBS ResourceId
hostedZoneId,
ByteString
"/deauthorizevpcassociation"
]
instance
Data.ToQuery
DeleteVPCAssociationAuthorization
where
toQuery :: DeleteVPCAssociationAuthorization -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToXML DeleteVPCAssociationAuthorization where
toXML :: DeleteVPCAssociationAuthorization -> XML
toXML DeleteVPCAssociationAuthorization' {ResourceId
VPC
vpc :: VPC
hostedZoneId :: ResourceId
$sel:vpc:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> VPC
$sel:hostedZoneId:DeleteVPCAssociationAuthorization' :: DeleteVPCAssociationAuthorization -> ResourceId
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat [Name
"VPC" forall a. ToXML a => Name -> a -> XML
Data.@= VPC
vpc]
data DeleteVPCAssociationAuthorizationResponse = DeleteVPCAssociationAuthorizationResponse'
{
DeleteVPCAssociationAuthorizationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DeleteVPCAssociationAuthorizationResponse
-> DeleteVPCAssociationAuthorizationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVPCAssociationAuthorizationResponse
-> DeleteVPCAssociationAuthorizationResponse -> Bool
$c/= :: DeleteVPCAssociationAuthorizationResponse
-> DeleteVPCAssociationAuthorizationResponse -> Bool
== :: DeleteVPCAssociationAuthorizationResponse
-> DeleteVPCAssociationAuthorizationResponse -> Bool
$c== :: DeleteVPCAssociationAuthorizationResponse
-> DeleteVPCAssociationAuthorizationResponse -> Bool
Prelude.Eq, ReadPrec [DeleteVPCAssociationAuthorizationResponse]
ReadPrec DeleteVPCAssociationAuthorizationResponse
Int -> ReadS DeleteVPCAssociationAuthorizationResponse
ReadS [DeleteVPCAssociationAuthorizationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVPCAssociationAuthorizationResponse]
$creadListPrec :: ReadPrec [DeleteVPCAssociationAuthorizationResponse]
readPrec :: ReadPrec DeleteVPCAssociationAuthorizationResponse
$creadPrec :: ReadPrec DeleteVPCAssociationAuthorizationResponse
readList :: ReadS [DeleteVPCAssociationAuthorizationResponse]
$creadList :: ReadS [DeleteVPCAssociationAuthorizationResponse]
readsPrec :: Int -> ReadS DeleteVPCAssociationAuthorizationResponse
$creadsPrec :: Int -> ReadS DeleteVPCAssociationAuthorizationResponse
Prelude.Read, Int -> DeleteVPCAssociationAuthorizationResponse -> ShowS
[DeleteVPCAssociationAuthorizationResponse] -> ShowS
DeleteVPCAssociationAuthorizationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVPCAssociationAuthorizationResponse] -> ShowS
$cshowList :: [DeleteVPCAssociationAuthorizationResponse] -> ShowS
show :: DeleteVPCAssociationAuthorizationResponse -> String
$cshow :: DeleteVPCAssociationAuthorizationResponse -> String
showsPrec :: Int -> DeleteVPCAssociationAuthorizationResponse -> ShowS
$cshowsPrec :: Int -> DeleteVPCAssociationAuthorizationResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteVPCAssociationAuthorizationResponse x
-> DeleteVPCAssociationAuthorizationResponse
forall x.
DeleteVPCAssociationAuthorizationResponse
-> Rep DeleteVPCAssociationAuthorizationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteVPCAssociationAuthorizationResponse x
-> DeleteVPCAssociationAuthorizationResponse
$cfrom :: forall x.
DeleteVPCAssociationAuthorizationResponse
-> Rep DeleteVPCAssociationAuthorizationResponse x
Prelude.Generic)
newDeleteVPCAssociationAuthorizationResponse ::
Prelude.Int ->
DeleteVPCAssociationAuthorizationResponse
newDeleteVPCAssociationAuthorizationResponse :: Int -> DeleteVPCAssociationAuthorizationResponse
newDeleteVPCAssociationAuthorizationResponse
Int
pHttpStatus_ =
DeleteVPCAssociationAuthorizationResponse'
{ $sel:httpStatus:DeleteVPCAssociationAuthorizationResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
deleteVPCAssociationAuthorizationResponse_httpStatus :: Lens.Lens' DeleteVPCAssociationAuthorizationResponse Prelude.Int
deleteVPCAssociationAuthorizationResponse_httpStatus :: Lens' DeleteVPCAssociationAuthorizationResponse Int
deleteVPCAssociationAuthorizationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVPCAssociationAuthorizationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteVPCAssociationAuthorizationResponse' :: DeleteVPCAssociationAuthorizationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteVPCAssociationAuthorizationResponse
s@DeleteVPCAssociationAuthorizationResponse' {} Int
a -> DeleteVPCAssociationAuthorizationResponse
s {$sel:httpStatus:DeleteVPCAssociationAuthorizationResponse' :: Int
httpStatus = Int
a} :: DeleteVPCAssociationAuthorizationResponse)
instance
Prelude.NFData
DeleteVPCAssociationAuthorizationResponse
where
rnf :: DeleteVPCAssociationAuthorizationResponse -> ()
rnf DeleteVPCAssociationAuthorizationResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteVPCAssociationAuthorizationResponse' :: DeleteVPCAssociationAuthorizationResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus