{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.EC2.Types.SecurityGroupRule
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.EC2.Types.SecurityGroupRule where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.ReferencedSecurityGroup
import Amazonka.EC2.Types.Tag
import qualified Amazonka.Prelude as Prelude

-- | Describes a security group rule.
--
-- /See:/ 'newSecurityGroupRule' smart constructor.
data SecurityGroupRule = SecurityGroupRule'
  { -- | The IPv4 CIDR range.
    SecurityGroupRule -> Maybe Text
cidrIpv4 :: Prelude.Maybe Prelude.Text,
    -- | The IPv6 CIDR range.
    SecurityGroupRule -> Maybe Text
cidrIpv6 :: Prelude.Maybe Prelude.Text,
    -- | The security group rule description.
    SecurityGroupRule -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The start of port range for the TCP and UDP protocols, or an
    -- ICMP\/ICMPv6 type. A value of -1 indicates all ICMP\/ICMPv6 types. If
    -- you specify all ICMP\/ICMPv6 types, you must specify all codes.
    SecurityGroupRule -> Maybe Int
fromPort :: Prelude.Maybe Prelude.Int,
    -- | The ID of the security group.
    SecurityGroupRule -> Maybe Text
groupId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services account that owns the security group.
    SecurityGroupRule -> Maybe Text
groupOwnerId :: Prelude.Maybe Prelude.Text,
    -- | The IP protocol name (@tcp@, @udp@, @icmp@, @icmpv6@) or number (see
    -- <http://www.iana.org/assignments/protocol-numbers/protocol-numbers.xhtml Protocol Numbers>).
    --
    -- Use @-1@ to specify all protocols.
    SecurityGroupRule -> Maybe Text
ipProtocol :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the security group rule is an outbound rule.
    SecurityGroupRule -> Maybe Bool
isEgress :: Prelude.Maybe Prelude.Bool,
    -- | The ID of the prefix list.
    SecurityGroupRule -> Maybe Text
prefixListId :: Prelude.Maybe Prelude.Text,
    -- | Describes the security group that is referenced in the rule.
    SecurityGroupRule -> Maybe ReferencedSecurityGroup
referencedGroupInfo :: Prelude.Maybe ReferencedSecurityGroup,
    -- | The ID of the security group rule.
    SecurityGroupRule -> Maybe Text
securityGroupRuleId :: Prelude.Maybe Prelude.Text,
    -- | The tags applied to the security group rule.
    SecurityGroupRule -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The end of port range for the TCP and UDP protocols, or an ICMP\/ICMPv6
    -- code. A value of @-1@ indicates all ICMP\/ICMPv6 codes. If you specify
    -- all ICMP\/ICMPv6 types, you must specify all codes.
    SecurityGroupRule -> Maybe Int
toPort :: Prelude.Maybe Prelude.Int
  }
  deriving (SecurityGroupRule -> SecurityGroupRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecurityGroupRule -> SecurityGroupRule -> Bool
$c/= :: SecurityGroupRule -> SecurityGroupRule -> Bool
== :: SecurityGroupRule -> SecurityGroupRule -> Bool
$c== :: SecurityGroupRule -> SecurityGroupRule -> Bool
Prelude.Eq, ReadPrec [SecurityGroupRule]
ReadPrec SecurityGroupRule
Int -> ReadS SecurityGroupRule
ReadS [SecurityGroupRule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SecurityGroupRule]
$creadListPrec :: ReadPrec [SecurityGroupRule]
readPrec :: ReadPrec SecurityGroupRule
$creadPrec :: ReadPrec SecurityGroupRule
readList :: ReadS [SecurityGroupRule]
$creadList :: ReadS [SecurityGroupRule]
readsPrec :: Int -> ReadS SecurityGroupRule
$creadsPrec :: Int -> ReadS SecurityGroupRule
Prelude.Read, Int -> SecurityGroupRule -> ShowS
[SecurityGroupRule] -> ShowS
SecurityGroupRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecurityGroupRule] -> ShowS
$cshowList :: [SecurityGroupRule] -> ShowS
show :: SecurityGroupRule -> String
$cshow :: SecurityGroupRule -> String
showsPrec :: Int -> SecurityGroupRule -> ShowS
$cshowsPrec :: Int -> SecurityGroupRule -> ShowS
Prelude.Show, forall x. Rep SecurityGroupRule x -> SecurityGroupRule
forall x. SecurityGroupRule -> Rep SecurityGroupRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecurityGroupRule x -> SecurityGroupRule
$cfrom :: forall x. SecurityGroupRule -> Rep SecurityGroupRule x
Prelude.Generic)

-- |
-- Create a value of 'SecurityGroupRule' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'cidrIpv4', 'securityGroupRule_cidrIpv4' - The IPv4 CIDR range.
--
-- 'cidrIpv6', 'securityGroupRule_cidrIpv6' - The IPv6 CIDR range.
--
-- 'description', 'securityGroupRule_description' - The security group rule description.
--
-- 'fromPort', 'securityGroupRule_fromPort' - The start of port range for the TCP and UDP protocols, or an
-- ICMP\/ICMPv6 type. A value of -1 indicates all ICMP\/ICMPv6 types. If
-- you specify all ICMP\/ICMPv6 types, you must specify all codes.
--
-- 'groupId', 'securityGroupRule_groupId' - The ID of the security group.
--
-- 'groupOwnerId', 'securityGroupRule_groupOwnerId' - The ID of the Amazon Web Services account that owns the security group.
--
-- 'ipProtocol', 'securityGroupRule_ipProtocol' - The IP protocol name (@tcp@, @udp@, @icmp@, @icmpv6@) or number (see
-- <http://www.iana.org/assignments/protocol-numbers/protocol-numbers.xhtml Protocol Numbers>).
--
-- Use @-1@ to specify all protocols.
--
-- 'isEgress', 'securityGroupRule_isEgress' - Indicates whether the security group rule is an outbound rule.
--
-- 'prefixListId', 'securityGroupRule_prefixListId' - The ID of the prefix list.
--
-- 'referencedGroupInfo', 'securityGroupRule_referencedGroupInfo' - Describes the security group that is referenced in the rule.
--
-- 'securityGroupRuleId', 'securityGroupRule_securityGroupRuleId' - The ID of the security group rule.
--
-- 'tags', 'securityGroupRule_tags' - The tags applied to the security group rule.
--
-- 'toPort', 'securityGroupRule_toPort' - The end of port range for the TCP and UDP protocols, or an ICMP\/ICMPv6
-- code. A value of @-1@ indicates all ICMP\/ICMPv6 codes. If you specify
-- all ICMP\/ICMPv6 types, you must specify all codes.
newSecurityGroupRule ::
  SecurityGroupRule
newSecurityGroupRule :: SecurityGroupRule
newSecurityGroupRule =
  SecurityGroupRule'
    { $sel:cidrIpv4:SecurityGroupRule' :: Maybe Text
cidrIpv4 = forall a. Maybe a
Prelude.Nothing,
      $sel:cidrIpv6:SecurityGroupRule' :: Maybe Text
cidrIpv6 = forall a. Maybe a
Prelude.Nothing,
      $sel:description:SecurityGroupRule' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:fromPort:SecurityGroupRule' :: Maybe Int
fromPort = forall a. Maybe a
Prelude.Nothing,
      $sel:groupId:SecurityGroupRule' :: Maybe Text
groupId = forall a. Maybe a
Prelude.Nothing,
      $sel:groupOwnerId:SecurityGroupRule' :: Maybe Text
groupOwnerId = forall a. Maybe a
Prelude.Nothing,
      $sel:ipProtocol:SecurityGroupRule' :: Maybe Text
ipProtocol = forall a. Maybe a
Prelude.Nothing,
      $sel:isEgress:SecurityGroupRule' :: Maybe Bool
isEgress = forall a. Maybe a
Prelude.Nothing,
      $sel:prefixListId:SecurityGroupRule' :: Maybe Text
prefixListId = forall a. Maybe a
Prelude.Nothing,
      $sel:referencedGroupInfo:SecurityGroupRule' :: Maybe ReferencedSecurityGroup
referencedGroupInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupRuleId:SecurityGroupRule' :: Maybe Text
securityGroupRuleId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:SecurityGroupRule' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:toPort:SecurityGroupRule' :: Maybe Int
toPort = forall a. Maybe a
Prelude.Nothing
    }

-- | The IPv4 CIDR range.
securityGroupRule_cidrIpv4 :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_cidrIpv4 :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_cidrIpv4 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
cidrIpv4 :: Maybe Text
$sel:cidrIpv4:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
cidrIpv4} -> Maybe Text
cidrIpv4) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:cidrIpv4:SecurityGroupRule' :: Maybe Text
cidrIpv4 = Maybe Text
a} :: SecurityGroupRule)

-- | The IPv6 CIDR range.
securityGroupRule_cidrIpv6 :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_cidrIpv6 :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_cidrIpv6 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
cidrIpv6 :: Maybe Text
$sel:cidrIpv6:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
cidrIpv6} -> Maybe Text
cidrIpv6) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:cidrIpv6:SecurityGroupRule' :: Maybe Text
cidrIpv6 = Maybe Text
a} :: SecurityGroupRule)

-- | The security group rule description.
securityGroupRule_description :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_description :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
description :: Maybe Text
$sel:description:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
description} -> Maybe Text
description) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:description:SecurityGroupRule' :: Maybe Text
description = Maybe Text
a} :: SecurityGroupRule)

-- | The start of port range for the TCP and UDP protocols, or an
-- ICMP\/ICMPv6 type. A value of -1 indicates all ICMP\/ICMPv6 types. If
-- you specify all ICMP\/ICMPv6 types, you must specify all codes.
securityGroupRule_fromPort :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Int)
securityGroupRule_fromPort :: Lens' SecurityGroupRule (Maybe Int)
securityGroupRule_fromPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Int
fromPort :: Maybe Int
$sel:fromPort:SecurityGroupRule' :: SecurityGroupRule -> Maybe Int
fromPort} -> Maybe Int
fromPort) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Int
a -> SecurityGroupRule
s {$sel:fromPort:SecurityGroupRule' :: Maybe Int
fromPort = Maybe Int
a} :: SecurityGroupRule)

-- | The ID of the security group.
securityGroupRule_groupId :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_groupId :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
groupId :: Maybe Text
$sel:groupId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
groupId} -> Maybe Text
groupId) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:groupId:SecurityGroupRule' :: Maybe Text
groupId = Maybe Text
a} :: SecurityGroupRule)

-- | The ID of the Amazon Web Services account that owns the security group.
securityGroupRule_groupOwnerId :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_groupOwnerId :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_groupOwnerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
groupOwnerId :: Maybe Text
$sel:groupOwnerId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
groupOwnerId} -> Maybe Text
groupOwnerId) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:groupOwnerId:SecurityGroupRule' :: Maybe Text
groupOwnerId = Maybe Text
a} :: SecurityGroupRule)

-- | The IP protocol name (@tcp@, @udp@, @icmp@, @icmpv6@) or number (see
-- <http://www.iana.org/assignments/protocol-numbers/protocol-numbers.xhtml Protocol Numbers>).
--
-- Use @-1@ to specify all protocols.
securityGroupRule_ipProtocol :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_ipProtocol :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_ipProtocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
ipProtocol :: Maybe Text
$sel:ipProtocol:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
ipProtocol} -> Maybe Text
ipProtocol) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:ipProtocol:SecurityGroupRule' :: Maybe Text
ipProtocol = Maybe Text
a} :: SecurityGroupRule)

-- | Indicates whether the security group rule is an outbound rule.
securityGroupRule_isEgress :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Bool)
securityGroupRule_isEgress :: Lens' SecurityGroupRule (Maybe Bool)
securityGroupRule_isEgress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Bool
isEgress :: Maybe Bool
$sel:isEgress:SecurityGroupRule' :: SecurityGroupRule -> Maybe Bool
isEgress} -> Maybe Bool
isEgress) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Bool
a -> SecurityGroupRule
s {$sel:isEgress:SecurityGroupRule' :: Maybe Bool
isEgress = Maybe Bool
a} :: SecurityGroupRule)

-- | The ID of the prefix list.
securityGroupRule_prefixListId :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_prefixListId :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_prefixListId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
prefixListId :: Maybe Text
$sel:prefixListId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
prefixListId} -> Maybe Text
prefixListId) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:prefixListId:SecurityGroupRule' :: Maybe Text
prefixListId = Maybe Text
a} :: SecurityGroupRule)

-- | Describes the security group that is referenced in the rule.
securityGroupRule_referencedGroupInfo :: Lens.Lens' SecurityGroupRule (Prelude.Maybe ReferencedSecurityGroup)
securityGroupRule_referencedGroupInfo :: Lens' SecurityGroupRule (Maybe ReferencedSecurityGroup)
securityGroupRule_referencedGroupInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe ReferencedSecurityGroup
referencedGroupInfo :: Maybe ReferencedSecurityGroup
$sel:referencedGroupInfo:SecurityGroupRule' :: SecurityGroupRule -> Maybe ReferencedSecurityGroup
referencedGroupInfo} -> Maybe ReferencedSecurityGroup
referencedGroupInfo) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe ReferencedSecurityGroup
a -> SecurityGroupRule
s {$sel:referencedGroupInfo:SecurityGroupRule' :: Maybe ReferencedSecurityGroup
referencedGroupInfo = Maybe ReferencedSecurityGroup
a} :: SecurityGroupRule)

-- | The ID of the security group rule.
securityGroupRule_securityGroupRuleId :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Text)
securityGroupRule_securityGroupRuleId :: Lens' SecurityGroupRule (Maybe Text)
securityGroupRule_securityGroupRuleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Text
securityGroupRuleId :: Maybe Text
$sel:securityGroupRuleId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
securityGroupRuleId} -> Maybe Text
securityGroupRuleId) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Text
a -> SecurityGroupRule
s {$sel:securityGroupRuleId:SecurityGroupRule' :: Maybe Text
securityGroupRuleId = Maybe Text
a} :: SecurityGroupRule)

-- | The tags applied to the security group rule.
securityGroupRule_tags :: Lens.Lens' SecurityGroupRule (Prelude.Maybe [Tag])
securityGroupRule_tags :: Lens' SecurityGroupRule (Maybe [Tag])
securityGroupRule_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:SecurityGroupRule' :: SecurityGroupRule -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe [Tag]
a -> SecurityGroupRule
s {$sel:tags:SecurityGroupRule' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: SecurityGroupRule) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The end of port range for the TCP and UDP protocols, or an ICMP\/ICMPv6
-- code. A value of @-1@ indicates all ICMP\/ICMPv6 codes. If you specify
-- all ICMP\/ICMPv6 types, you must specify all codes.
securityGroupRule_toPort :: Lens.Lens' SecurityGroupRule (Prelude.Maybe Prelude.Int)
securityGroupRule_toPort :: Lens' SecurityGroupRule (Maybe Int)
securityGroupRule_toPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SecurityGroupRule' {Maybe Int
toPort :: Maybe Int
$sel:toPort:SecurityGroupRule' :: SecurityGroupRule -> Maybe Int
toPort} -> Maybe Int
toPort) (\s :: SecurityGroupRule
s@SecurityGroupRule' {} Maybe Int
a -> SecurityGroupRule
s {$sel:toPort:SecurityGroupRule' :: Maybe Int
toPort = Maybe Int
a} :: SecurityGroupRule)

instance Data.FromXML SecurityGroupRule where
  parseXML :: [Node] -> Either String SecurityGroupRule
parseXML [Node]
x =
    Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe ReferencedSecurityGroup
-> Maybe Text
-> Maybe [Tag]
-> Maybe Int
-> SecurityGroupRule
SecurityGroupRule'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"cidrIpv4")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"cidrIpv6")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"description")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"fromPort")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"groupId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"groupOwnerId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ipProtocol")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"isEgress")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"prefixListId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"referencedGroupInfo")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"securityGroupRuleId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"tagSet"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"item")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"toPort")

instance Prelude.Hashable SecurityGroupRule where
  hashWithSalt :: Int -> SecurityGroupRule -> Int
hashWithSalt Int
_salt SecurityGroupRule' {Maybe Bool
Maybe Int
Maybe [Tag]
Maybe Text
Maybe ReferencedSecurityGroup
toPort :: Maybe Int
tags :: Maybe [Tag]
securityGroupRuleId :: Maybe Text
referencedGroupInfo :: Maybe ReferencedSecurityGroup
prefixListId :: Maybe Text
isEgress :: Maybe Bool
ipProtocol :: Maybe Text
groupOwnerId :: Maybe Text
groupId :: Maybe Text
fromPort :: Maybe Int
description :: Maybe Text
cidrIpv6 :: Maybe Text
cidrIpv4 :: Maybe Text
$sel:toPort:SecurityGroupRule' :: SecurityGroupRule -> Maybe Int
$sel:tags:SecurityGroupRule' :: SecurityGroupRule -> Maybe [Tag]
$sel:securityGroupRuleId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:referencedGroupInfo:SecurityGroupRule' :: SecurityGroupRule -> Maybe ReferencedSecurityGroup
$sel:prefixListId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:isEgress:SecurityGroupRule' :: SecurityGroupRule -> Maybe Bool
$sel:ipProtocol:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:groupOwnerId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:groupId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:fromPort:SecurityGroupRule' :: SecurityGroupRule -> Maybe Int
$sel:description:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:cidrIpv6:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:cidrIpv4:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cidrIpv4
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cidrIpv6
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
fromPort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
groupOwnerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ipProtocol
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isEgress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
prefixListId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReferencedSecurityGroup
referencedGroupInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
securityGroupRuleId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
toPort

instance Prelude.NFData SecurityGroupRule where
  rnf :: SecurityGroupRule -> ()
rnf SecurityGroupRule' {Maybe Bool
Maybe Int
Maybe [Tag]
Maybe Text
Maybe ReferencedSecurityGroup
toPort :: Maybe Int
tags :: Maybe [Tag]
securityGroupRuleId :: Maybe Text
referencedGroupInfo :: Maybe ReferencedSecurityGroup
prefixListId :: Maybe Text
isEgress :: Maybe Bool
ipProtocol :: Maybe Text
groupOwnerId :: Maybe Text
groupId :: Maybe Text
fromPort :: Maybe Int
description :: Maybe Text
cidrIpv6 :: Maybe Text
cidrIpv4 :: Maybe Text
$sel:toPort:SecurityGroupRule' :: SecurityGroupRule -> Maybe Int
$sel:tags:SecurityGroupRule' :: SecurityGroupRule -> Maybe [Tag]
$sel:securityGroupRuleId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:referencedGroupInfo:SecurityGroupRule' :: SecurityGroupRule -> Maybe ReferencedSecurityGroup
$sel:prefixListId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:isEgress:SecurityGroupRule' :: SecurityGroupRule -> Maybe Bool
$sel:ipProtocol:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:groupOwnerId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:groupId:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:fromPort:SecurityGroupRule' :: SecurityGroupRule -> Maybe Int
$sel:description:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:cidrIpv6:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
$sel:cidrIpv4:SecurityGroupRule' :: SecurityGroupRule -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cidrIpv4
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cidrIpv6
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
fromPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupOwnerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ipProtocol
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isEgress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
prefixListId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReferencedSecurityGroup
referencedGroupInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityGroupRuleId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
toPort