module Stratosphere.Resources.SubnetRouteTableAssociation where
import Control.Lens
import Data.Aeson
import Data.Aeson.Types
import Data.Text
import GHC.Generics
import Stratosphere.Values
data SubnetRouteTableAssociation =
SubnetRouteTableAssociation
{ _subnetRouteTableAssociationRouteTableId :: Val Text
, _subnetRouteTableAssociationSubnetId :: Val Text
} deriving (Show, Generic)
instance ToJSON SubnetRouteTableAssociation where
toJSON = genericToJSON defaultOptions { fieldLabelModifier = Prelude.drop 28, omitNothingFields = True }
instance FromJSON SubnetRouteTableAssociation where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = Prelude.drop 28, omitNothingFields = True }
subnetRouteTableAssociation
:: Val Text
-> Val Text
-> SubnetRouteTableAssociation
subnetRouteTableAssociation routeTableIdarg subnetIdarg =
SubnetRouteTableAssociation
{ _subnetRouteTableAssociationRouteTableId = routeTableIdarg
, _subnetRouteTableAssociationSubnetId = subnetIdarg
}
srtaRouteTableId :: Lens' SubnetRouteTableAssociation (Val Text)
srtaRouteTableId = lens _subnetRouteTableAssociationRouteTableId (\s a -> s { _subnetRouteTableAssociationRouteTableId = a })
srtaSubnetId :: Lens' SubnetRouteTableAssociation (Val Text)
srtaSubnetId = lens _subnetRouteTableAssociationSubnetId (\s a -> s { _subnetRouteTableAssociationSubnetId = a })