module Stratosphere.ResourceProperties.SecurityGroupIngressRule where
import Control.Lens
import Data.Aeson
import Data.Aeson.Types
import Data.Text
import GHC.Generics
import Stratosphere.Values
data SecurityGroupIngressRule =
SecurityGroupIngressRule
{ _securityGroupIngressRuleCidrIp :: Maybe (Val Text)
, _securityGroupIngressRuleFromPort :: Maybe (Val Integer')
, _securityGroupIngressRuleIpProtocol :: Val Text
, _securityGroupIngressRuleSourceSecurityGroupId :: Maybe (Val Text)
, _securityGroupIngressRuleSourceSecurityGroupName :: Maybe (Val Text)
, _securityGroupIngressRuleSourceSecurityGroupOwnerId :: Maybe (Val Text)
, _securityGroupIngressRuleToPort :: Maybe (Val Integer')
} deriving (Show, Generic)
instance ToJSON SecurityGroupIngressRule where
toJSON = genericToJSON defaultOptions { fieldLabelModifier = Prelude.drop 25, omitNothingFields = True }
instance FromJSON SecurityGroupIngressRule where
parseJSON = genericParseJSON defaultOptions { fieldLabelModifier = Prelude.drop 25, omitNothingFields = True }
securityGroupIngressRule
:: Val Text
-> SecurityGroupIngressRule
securityGroupIngressRule ipProtocolarg =
SecurityGroupIngressRule
{ _securityGroupIngressRuleCidrIp = Nothing
, _securityGroupIngressRuleFromPort = Nothing
, _securityGroupIngressRuleIpProtocol = ipProtocolarg
, _securityGroupIngressRuleSourceSecurityGroupId = Nothing
, _securityGroupIngressRuleSourceSecurityGroupName = Nothing
, _securityGroupIngressRuleSourceSecurityGroupOwnerId = Nothing
, _securityGroupIngressRuleToPort = Nothing
}
sgirCidrIp :: Lens' SecurityGroupIngressRule (Maybe (Val Text))
sgirCidrIp = lens _securityGroupIngressRuleCidrIp (\s a -> s { _securityGroupIngressRuleCidrIp = a })
sgirFromPort :: Lens' SecurityGroupIngressRule (Maybe (Val Integer'))
sgirFromPort = lens _securityGroupIngressRuleFromPort (\s a -> s { _securityGroupIngressRuleFromPort = a })
sgirIpProtocol :: Lens' SecurityGroupIngressRule (Val Text)
sgirIpProtocol = lens _securityGroupIngressRuleIpProtocol (\s a -> s { _securityGroupIngressRuleIpProtocol = a })
sgirSourceSecurityGroupId :: Lens' SecurityGroupIngressRule (Maybe (Val Text))
sgirSourceSecurityGroupId = lens _securityGroupIngressRuleSourceSecurityGroupId (\s a -> s { _securityGroupIngressRuleSourceSecurityGroupId = a })
sgirSourceSecurityGroupName :: Lens' SecurityGroupIngressRule (Maybe (Val Text))
sgirSourceSecurityGroupName = lens _securityGroupIngressRuleSourceSecurityGroupName (\s a -> s { _securityGroupIngressRuleSourceSecurityGroupName = a })
sgirSourceSecurityGroupOwnerId :: Lens' SecurityGroupIngressRule (Maybe (Val Text))
sgirSourceSecurityGroupOwnerId = lens _securityGroupIngressRuleSourceSecurityGroupOwnerId (\s a -> s { _securityGroupIngressRuleSourceSecurityGroupOwnerId = a })
sgirToPort :: Lens' SecurityGroupIngressRule (Maybe (Val Integer'))
sgirToPort = lens _securityGroupIngressRuleToPort (\s a -> s { _securityGroupIngressRuleToPort = a })