module Stratosphere.Resources.VPC where
import Control.Lens
import Data.Aeson
import Data.Aeson.Types
import Data.Text
import GHC.Generics
import Stratosphere.Values
import Stratosphere.ResourceProperties.ResourceTag
data VPC =
VPC
{ _vPCCidrBlock :: Val Text
, _vPCEnableDnsSupport :: Maybe (Val Bool')
, _vPCEnableDnsHostnames :: Maybe (Val Bool')
, _vPCInstanceTenancy :: Maybe (Val Text)
, _vPCTags :: Maybe [ResourceTag]
} deriving (Show, Generic)
instance ToJSON VPC where
toJSON = genericToJSON defaultOptions { fieldLabelModifier = Prelude.drop 4, omitNothingFields = True }
instance FromJSON VPC where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = Prelude.drop 4, omitNothingFields = True }
vpc
:: Val Text
-> VPC
vpc cidrBlockarg =
VPC
{ _vPCCidrBlock = cidrBlockarg
, _vPCEnableDnsSupport = Nothing
, _vPCEnableDnsHostnames = Nothing
, _vPCInstanceTenancy = Nothing
, _vPCTags = Nothing
}
vpcCidrBlock :: Lens' VPC (Val Text)
vpcCidrBlock = lens _vPCCidrBlock (\s a -> s { _vPCCidrBlock = a })
vpcEnableDnsSupport :: Lens' VPC (Maybe (Val Bool'))
vpcEnableDnsSupport = lens _vPCEnableDnsSupport (\s a -> s { _vPCEnableDnsSupport = a })
vpcEnableDnsHostnames :: Lens' VPC (Maybe (Val Bool'))
vpcEnableDnsHostnames = lens _vPCEnableDnsHostnames (\s a -> s { _vPCEnableDnsHostnames = a })
vpcInstanceTenancy :: Lens' VPC (Maybe (Val Text))
vpcInstanceTenancy = lens _vPCInstanceTenancy (\s a -> s { _vPCInstanceTenancy = a })
vpcTags :: Lens' VPC (Maybe [ResourceTag])
vpcTags = lens _vPCTags (\s a -> s { _vPCTags = a })