{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Network.AWS.Route53.DisassociateVPCFromHostedZone
(
disassociateVPCFromHostedZone
, DisassociateVPCFromHostedZone
, dvfhzComment
, dvfhzHostedZoneId
, dvfhzVPC
, disassociateVPCFromHostedZoneResponse
, DisassociateVPCFromHostedZoneResponse
, dvfhzrsResponseStatus
, dvfhzrsChangeInfo
) where
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.Route53.Types
import Network.AWS.Route53.Types.Product
data DisassociateVPCFromHostedZone = DisassociateVPCFromHostedZone'
{ _dvfhzComment :: !(Maybe Text)
, _dvfhzHostedZoneId :: !ResourceId
, _dvfhzVPC :: !VPC
} deriving (Eq, Read, Show, Data, Typeable, Generic)
disassociateVPCFromHostedZone
:: ResourceId
-> VPC
-> DisassociateVPCFromHostedZone
disassociateVPCFromHostedZone pHostedZoneId_ pVPC_ =
DisassociateVPCFromHostedZone'
{ _dvfhzComment = Nothing
, _dvfhzHostedZoneId = pHostedZoneId_
, _dvfhzVPC = pVPC_
}
dvfhzComment :: Lens' DisassociateVPCFromHostedZone (Maybe Text)
dvfhzComment = lens _dvfhzComment (\ s a -> s{_dvfhzComment = a})
dvfhzHostedZoneId :: Lens' DisassociateVPCFromHostedZone ResourceId
dvfhzHostedZoneId = lens _dvfhzHostedZoneId (\ s a -> s{_dvfhzHostedZoneId = a})
dvfhzVPC :: Lens' DisassociateVPCFromHostedZone VPC
dvfhzVPC = lens _dvfhzVPC (\ s a -> s{_dvfhzVPC = a})
instance AWSRequest DisassociateVPCFromHostedZone
where
type Rs DisassociateVPCFromHostedZone =
DisassociateVPCFromHostedZoneResponse
request = postXML route53
response
= receiveXML
(\ s h x ->
DisassociateVPCFromHostedZoneResponse' <$>
(pure (fromEnum s)) <*> (x .@ "ChangeInfo"))
instance Hashable DisassociateVPCFromHostedZone where
instance NFData DisassociateVPCFromHostedZone where
instance ToElement DisassociateVPCFromHostedZone
where
toElement
= mkElement
"{https://route53.amazonaws.com/doc/2013-04-01/}DisassociateVPCFromHostedZoneRequest"
instance ToHeaders DisassociateVPCFromHostedZone
where
toHeaders = const mempty
instance ToPath DisassociateVPCFromHostedZone where
toPath DisassociateVPCFromHostedZone'{..}
= mconcat
["/2013-04-01/hostedzone/", toBS _dvfhzHostedZoneId,
"/disassociatevpc"]
instance ToQuery DisassociateVPCFromHostedZone where
toQuery = const mempty
instance ToXML DisassociateVPCFromHostedZone where
toXML DisassociateVPCFromHostedZone'{..}
= mconcat
["Comment" @= _dvfhzComment, "VPC" @= _dvfhzVPC]
data DisassociateVPCFromHostedZoneResponse = DisassociateVPCFromHostedZoneResponse'
{ _dvfhzrsResponseStatus :: !Int
, _dvfhzrsChangeInfo :: !ChangeInfo
} deriving (Eq, Read, Show, Data, Typeable, Generic)
disassociateVPCFromHostedZoneResponse
:: Int
-> ChangeInfo
-> DisassociateVPCFromHostedZoneResponse
disassociateVPCFromHostedZoneResponse pResponseStatus_ pChangeInfo_ =
DisassociateVPCFromHostedZoneResponse'
{ _dvfhzrsResponseStatus = pResponseStatus_
, _dvfhzrsChangeInfo = pChangeInfo_
}
dvfhzrsResponseStatus :: Lens' DisassociateVPCFromHostedZoneResponse Int
dvfhzrsResponseStatus = lens _dvfhzrsResponseStatus (\ s a -> s{_dvfhzrsResponseStatus = a})
dvfhzrsChangeInfo :: Lens' DisassociateVPCFromHostedZoneResponse ChangeInfo
dvfhzrsChangeInfo = lens _dvfhzrsChangeInfo (\ s a -> s{_dvfhzrsChangeInfo = a})
instance NFData DisassociateVPCFromHostedZoneResponse
where