module Stratosphere.ResourceProperties.PrivateIpAddressSpecification where
import Control.Lens
import Data.Aeson
import Data.Aeson.Types
import Data.Text
import GHC.Generics
import Stratosphere.Values
data PrivateIpAddressSpecification =
PrivateIpAddressSpecification
{ _privateIpAddressSpecificationPrivateIpAddress :: Val Text
, _privateIpAddressSpecificationPrimary :: Val Bool'
} deriving (Show, Generic)
instance ToJSON PrivateIpAddressSpecification where
toJSON = genericToJSON defaultOptions { fieldLabelModifier = Prelude.drop 30, omitNothingFields = True }
instance FromJSON PrivateIpAddressSpecification where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = Prelude.drop 30, omitNothingFields = True }
privateIpAddressSpecification
:: Val Text
-> Val Bool'
-> PrivateIpAddressSpecification
privateIpAddressSpecification privateIpAddressarg primaryarg =
PrivateIpAddressSpecification
{ _privateIpAddressSpecificationPrivateIpAddress = privateIpAddressarg
, _privateIpAddressSpecificationPrimary = primaryarg
}
piasPrivateIpAddress :: Lens' PrivateIpAddressSpecification (Val Text)
piasPrivateIpAddress = lens _privateIpAddressSpecificationPrivateIpAddress (\s a -> s { _privateIpAddressSpecificationPrivateIpAddress = a })
piasPrimary :: Lens' PrivateIpAddressSpecification (Val Bool')
piasPrimary = lens _privateIpAddressSpecificationPrimary (\s a -> s { _privateIpAddressSpecificationPrimary = a })