{-# 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.ELBV2.Types.LoadBalancerAttribute -- 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.ELBV2.Types.LoadBalancerAttribute where import qualified Amazonka.Core as Core import qualified Amazonka.Core.Lens.Internal as Lens import qualified Amazonka.Data as Data import qualified Amazonka.Prelude as Prelude -- | Information about a load balancer attribute. -- -- /See:/ 'newLoadBalancerAttribute' smart constructor. data LoadBalancerAttribute = LoadBalancerAttribute' { -- | The name of the attribute. -- -- The following attributes are supported by all load balancers: -- -- - @deletion_protection.enabled@ - Indicates whether deletion -- protection is enabled. The value is @true@ or @false@. The default -- is @false@. -- -- - @load_balancing.cross_zone.enabled@ - Indicates whether cross-zone -- load balancing is enabled. The possible values are @true@ and -- @false@. The default for Network Load Balancers and Gateway Load -- Balancers is @false@. The default for Application Load Balancers is -- @true@, and cannot be changed. -- -- The following attributes are supported by both Application Load -- Balancers and Network Load Balancers: -- -- - @access_logs.s3.enabled@ - Indicates whether access logs are -- enabled. The value is @true@ or @false@. The default is @false@. -- -- - @access_logs.s3.bucket@ - The name of the S3 bucket for the access -- logs. This attribute is required if access logs are enabled. The -- bucket must exist in the same region as the load balancer and have a -- bucket policy that grants Elastic Load Balancing permissions to -- write to the bucket. -- -- - @access_logs.s3.prefix@ - The prefix for the location in the S3 -- bucket for the access logs. -- -- - @ipv6.deny_all_igw_traffic@ - Blocks internet gateway (IGW) access -- to the load balancer. It is set to @false@ for internet-facing load -- balancers and @true@ for internal load balancers, preventing -- unintended access to your internal load balancer through an internet -- gateway. -- -- The following attributes are supported by only Application Load -- Balancers: -- -- - @idle_timeout.timeout_seconds@ - The idle timeout value, in seconds. -- The valid range is 1-4000 seconds. The default is 60 seconds. -- -- - @routing.http.desync_mitigation_mode@ - Determines how the load -- balancer handles requests that might pose a security risk to your -- application. The possible values are @monitor@, @defensive@, and -- @strictest@. The default is @defensive@. -- -- - @routing.http.drop_invalid_header_fields.enabled@ - Indicates -- whether HTTP headers with invalid header fields are removed by the -- load balancer (@true@) or routed to targets (@false@). The default -- is @false@. -- -- - @routing.http.preserve_host_header.enabled@ - Indicates whether the -- Application Load Balancer should preserve the @Host@ header in the -- HTTP request and send it to the target without any change. The -- possible values are @true@ and @false@. The default is @false@. -- -- - @routing.http.x_amzn_tls_version_and_cipher_suite.enabled@ - -- Indicates whether the two headers (@x-amzn-tls-version@ and -- @x-amzn-tls-cipher-suite@), which contain information about the -- negotiated TLS version and cipher suite, are added to the client -- request before sending it to the target. The @x-amzn-tls-version@ -- header has information about the TLS protocol version negotiated -- with the client, and the @x-amzn-tls-cipher-suite@ header has -- information about the cipher suite negotiated with the client. Both -- headers are in OpenSSL format. The possible values for the attribute -- are @true@ and @false@. The default is @false@. -- -- - @routing.http.xff_client_port.enabled@ - Indicates whether the -- @X-Forwarded-For@ header should preserve the source port that the -- client used to connect to the load balancer. The possible values are -- @true@ and @false@. The default is @false@. -- -- - @routing.http.xff_header_processing.mode@ - Enables you to modify, -- preserve, or remove the @X-Forwarded-For@ header in the HTTP request -- before the Application Load Balancer sends the request to the -- target. The possible values are @append@, @preserve@, and @remove@. -- The default is @append@. -- -- - If the value is @append@, the Application Load Balancer adds the -- client IP address (of the last hop) to the @X-Forwarded-For@ -- header in the HTTP request before it sends it to targets. -- -- - If the value is @preserve@ the Application Load Balancer -- preserves the @X-Forwarded-For@ header in the HTTP request, and -- sends it to targets without any change. -- -- - If the value is @remove@, the Application Load Balancer removes -- the @X-Forwarded-For@ header in the HTTP request before it sends -- it to targets. -- -- - @routing.http2.enabled@ - Indicates whether HTTP\/2 is enabled. The -- possible values are @true@ and @false@. The default is @true@. -- Elastic Load Balancing requires that message header names contain -- only alphanumeric characters and hyphens. -- -- - @waf.fail_open.enabled@ - Indicates whether to allow a WAF-enabled -- load balancer to route requests to targets if it is unable to -- forward the request to Amazon Web Services WAF. The possible values -- are @true@ and @false@. The default is @false@. LoadBalancerAttribute -> Maybe Text key :: Prelude.Maybe Prelude.Text, -- | The value of the attribute. LoadBalancerAttribute -> Maybe Text value :: Prelude.Maybe Prelude.Text } deriving (LoadBalancerAttribute -> LoadBalancerAttribute -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: LoadBalancerAttribute -> LoadBalancerAttribute -> Bool $c/= :: LoadBalancerAttribute -> LoadBalancerAttribute -> Bool == :: LoadBalancerAttribute -> LoadBalancerAttribute -> Bool $c== :: LoadBalancerAttribute -> LoadBalancerAttribute -> Bool Prelude.Eq, ReadPrec [LoadBalancerAttribute] ReadPrec LoadBalancerAttribute Int -> ReadS LoadBalancerAttribute ReadS [LoadBalancerAttribute] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [LoadBalancerAttribute] $creadListPrec :: ReadPrec [LoadBalancerAttribute] readPrec :: ReadPrec LoadBalancerAttribute $creadPrec :: ReadPrec LoadBalancerAttribute readList :: ReadS [LoadBalancerAttribute] $creadList :: ReadS [LoadBalancerAttribute] readsPrec :: Int -> ReadS LoadBalancerAttribute $creadsPrec :: Int -> ReadS LoadBalancerAttribute Prelude.Read, Int -> LoadBalancerAttribute -> ShowS [LoadBalancerAttribute] -> ShowS LoadBalancerAttribute -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [LoadBalancerAttribute] -> ShowS $cshowList :: [LoadBalancerAttribute] -> ShowS show :: LoadBalancerAttribute -> String $cshow :: LoadBalancerAttribute -> String showsPrec :: Int -> LoadBalancerAttribute -> ShowS $cshowsPrec :: Int -> LoadBalancerAttribute -> ShowS Prelude.Show, forall x. Rep LoadBalancerAttribute x -> LoadBalancerAttribute forall x. LoadBalancerAttribute -> Rep LoadBalancerAttribute x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep LoadBalancerAttribute x -> LoadBalancerAttribute $cfrom :: forall x. LoadBalancerAttribute -> Rep LoadBalancerAttribute x Prelude.Generic) -- | -- Create a value of 'LoadBalancerAttribute' 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: -- -- 'key', 'loadBalancerAttribute_key' - The name of the attribute. -- -- The following attributes are supported by all load balancers: -- -- - @deletion_protection.enabled@ - Indicates whether deletion -- protection is enabled. The value is @true@ or @false@. The default -- is @false@. -- -- - @load_balancing.cross_zone.enabled@ - Indicates whether cross-zone -- load balancing is enabled. The possible values are @true@ and -- @false@. The default for Network Load Balancers and Gateway Load -- Balancers is @false@. The default for Application Load Balancers is -- @true@, and cannot be changed. -- -- The following attributes are supported by both Application Load -- Balancers and Network Load Balancers: -- -- - @access_logs.s3.enabled@ - Indicates whether access logs are -- enabled. The value is @true@ or @false@. The default is @false@. -- -- - @access_logs.s3.bucket@ - The name of the S3 bucket for the access -- logs. This attribute is required if access logs are enabled. The -- bucket must exist in the same region as the load balancer and have a -- bucket policy that grants Elastic Load Balancing permissions to -- write to the bucket. -- -- - @access_logs.s3.prefix@ - The prefix for the location in the S3 -- bucket for the access logs. -- -- - @ipv6.deny_all_igw_traffic@ - Blocks internet gateway (IGW) access -- to the load balancer. It is set to @false@ for internet-facing load -- balancers and @true@ for internal load balancers, preventing -- unintended access to your internal load balancer through an internet -- gateway. -- -- The following attributes are supported by only Application Load -- Balancers: -- -- - @idle_timeout.timeout_seconds@ - The idle timeout value, in seconds. -- The valid range is 1-4000 seconds. The default is 60 seconds. -- -- - @routing.http.desync_mitigation_mode@ - Determines how the load -- balancer handles requests that might pose a security risk to your -- application. The possible values are @monitor@, @defensive@, and -- @strictest@. The default is @defensive@. -- -- - @routing.http.drop_invalid_header_fields.enabled@ - Indicates -- whether HTTP headers with invalid header fields are removed by the -- load balancer (@true@) or routed to targets (@false@). The default -- is @false@. -- -- - @routing.http.preserve_host_header.enabled@ - Indicates whether the -- Application Load Balancer should preserve the @Host@ header in the -- HTTP request and send it to the target without any change. The -- possible values are @true@ and @false@. The default is @false@. -- -- - @routing.http.x_amzn_tls_version_and_cipher_suite.enabled@ - -- Indicates whether the two headers (@x-amzn-tls-version@ and -- @x-amzn-tls-cipher-suite@), which contain information about the -- negotiated TLS version and cipher suite, are added to the client -- request before sending it to the target. The @x-amzn-tls-version@ -- header has information about the TLS protocol version negotiated -- with the client, and the @x-amzn-tls-cipher-suite@ header has -- information about the cipher suite negotiated with the client. Both -- headers are in OpenSSL format. The possible values for the attribute -- are @true@ and @false@. The default is @false@. -- -- - @routing.http.xff_client_port.enabled@ - Indicates whether the -- @X-Forwarded-For@ header should preserve the source port that the -- client used to connect to the load balancer. The possible values are -- @true@ and @false@. The default is @false@. -- -- - @routing.http.xff_header_processing.mode@ - Enables you to modify, -- preserve, or remove the @X-Forwarded-For@ header in the HTTP request -- before the Application Load Balancer sends the request to the -- target. The possible values are @append@, @preserve@, and @remove@. -- The default is @append@. -- -- - If the value is @append@, the Application Load Balancer adds the -- client IP address (of the last hop) to the @X-Forwarded-For@ -- header in the HTTP request before it sends it to targets. -- -- - If the value is @preserve@ the Application Load Balancer -- preserves the @X-Forwarded-For@ header in the HTTP request, and -- sends it to targets without any change. -- -- - If the value is @remove@, the Application Load Balancer removes -- the @X-Forwarded-For@ header in the HTTP request before it sends -- it to targets. -- -- - @routing.http2.enabled@ - Indicates whether HTTP\/2 is enabled. The -- possible values are @true@ and @false@. The default is @true@. -- Elastic Load Balancing requires that message header names contain -- only alphanumeric characters and hyphens. -- -- - @waf.fail_open.enabled@ - Indicates whether to allow a WAF-enabled -- load balancer to route requests to targets if it is unable to -- forward the request to Amazon Web Services WAF. The possible values -- are @true@ and @false@. The default is @false@. -- -- 'value', 'loadBalancerAttribute_value' - The value of the attribute. newLoadBalancerAttribute :: LoadBalancerAttribute newLoadBalancerAttribute :: LoadBalancerAttribute newLoadBalancerAttribute = LoadBalancerAttribute' { $sel:key:LoadBalancerAttribute' :: Maybe Text key = forall a. Maybe a Prelude.Nothing, $sel:value:LoadBalancerAttribute' :: Maybe Text value = forall a. Maybe a Prelude.Nothing } -- | The name of the attribute. -- -- The following attributes are supported by all load balancers: -- -- - @deletion_protection.enabled@ - Indicates whether deletion -- protection is enabled. The value is @true@ or @false@. The default -- is @false@. -- -- - @load_balancing.cross_zone.enabled@ - Indicates whether cross-zone -- load balancing is enabled. The possible values are @true@ and -- @false@. The default for Network Load Balancers and Gateway Load -- Balancers is @false@. The default for Application Load Balancers is -- @true@, and cannot be changed. -- -- The following attributes are supported by both Application Load -- Balancers and Network Load Balancers: -- -- - @access_logs.s3.enabled@ - Indicates whether access logs are -- enabled. The value is @true@ or @false@. The default is @false@. -- -- - @access_logs.s3.bucket@ - The name of the S3 bucket for the access -- logs. This attribute is required if access logs are enabled. The -- bucket must exist in the same region as the load balancer and have a -- bucket policy that grants Elastic Load Balancing permissions to -- write to the bucket. -- -- - @access_logs.s3.prefix@ - The prefix for the location in the S3 -- bucket for the access logs. -- -- - @ipv6.deny_all_igw_traffic@ - Blocks internet gateway (IGW) access -- to the load balancer. It is set to @false@ for internet-facing load -- balancers and @true@ for internal load balancers, preventing -- unintended access to your internal load balancer through an internet -- gateway. -- -- The following attributes are supported by only Application Load -- Balancers: -- -- - @idle_timeout.timeout_seconds@ - The idle timeout value, in seconds. -- The valid range is 1-4000 seconds. The default is 60 seconds. -- -- - @routing.http.desync_mitigation_mode@ - Determines how the load -- balancer handles requests that might pose a security risk to your -- application. The possible values are @monitor@, @defensive@, and -- @strictest@. The default is @defensive@. -- -- - @routing.http.drop_invalid_header_fields.enabled@ - Indicates -- whether HTTP headers with invalid header fields are removed by the -- load balancer (@true@) or routed to targets (@false@). The default -- is @false@. -- -- - @routing.http.preserve_host_header.enabled@ - Indicates whether the -- Application Load Balancer should preserve the @Host@ header in the -- HTTP request and send it to the target without any change. The -- possible values are @true@ and @false@. The default is @false@. -- -- - @routing.http.x_amzn_tls_version_and_cipher_suite.enabled@ - -- Indicates whether the two headers (@x-amzn-tls-version@ and -- @x-amzn-tls-cipher-suite@), which contain information about the -- negotiated TLS version and cipher suite, are added to the client -- request before sending it to the target. The @x-amzn-tls-version@ -- header has information about the TLS protocol version negotiated -- with the client, and the @x-amzn-tls-cipher-suite@ header has -- information about the cipher suite negotiated with the client. Both -- headers are in OpenSSL format. The possible values for the attribute -- are @true@ and @false@. The default is @false@. -- -- - @routing.http.xff_client_port.enabled@ - Indicates whether the -- @X-Forwarded-For@ header should preserve the source port that the -- client used to connect to the load balancer. The possible values are -- @true@ and @false@. The default is @false@. -- -- - @routing.http.xff_header_processing.mode@ - Enables you to modify, -- preserve, or remove the @X-Forwarded-For@ header in the HTTP request -- before the Application Load Balancer sends the request to the -- target. The possible values are @append@, @preserve@, and @remove@. -- The default is @append@. -- -- - If the value is @append@, the Application Load Balancer adds the -- client IP address (of the last hop) to the @X-Forwarded-For@ -- header in the HTTP request before it sends it to targets. -- -- - If the value is @preserve@ the Application Load Balancer -- preserves the @X-Forwarded-For@ header in the HTTP request, and -- sends it to targets without any change. -- -- - If the value is @remove@, the Application Load Balancer removes -- the @X-Forwarded-For@ header in the HTTP request before it sends -- it to targets. -- -- - @routing.http2.enabled@ - Indicates whether HTTP\/2 is enabled. The -- possible values are @true@ and @false@. The default is @true@. -- Elastic Load Balancing requires that message header names contain -- only alphanumeric characters and hyphens. -- -- - @waf.fail_open.enabled@ - Indicates whether to allow a WAF-enabled -- load balancer to route requests to targets if it is unable to -- forward the request to Amazon Web Services WAF. The possible values -- are @true@ and @false@. The default is @false@. loadBalancerAttribute_key :: Lens.Lens' LoadBalancerAttribute (Prelude.Maybe Prelude.Text) loadBalancerAttribute_key :: Lens' LoadBalancerAttribute (Maybe Text) loadBalancerAttribute_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b Lens.lens (\LoadBalancerAttribute' {Maybe Text key :: Maybe Text $sel:key:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text key} -> Maybe Text key) (\s :: LoadBalancerAttribute s@LoadBalancerAttribute' {} Maybe Text a -> LoadBalancerAttribute s {$sel:key:LoadBalancerAttribute' :: Maybe Text key = Maybe Text a} :: LoadBalancerAttribute) -- | The value of the attribute. loadBalancerAttribute_value :: Lens.Lens' LoadBalancerAttribute (Prelude.Maybe Prelude.Text) loadBalancerAttribute_value :: Lens' LoadBalancerAttribute (Maybe Text) loadBalancerAttribute_value = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b Lens.lens (\LoadBalancerAttribute' {Maybe Text value :: Maybe Text $sel:value:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text value} -> Maybe Text value) (\s :: LoadBalancerAttribute s@LoadBalancerAttribute' {} Maybe Text a -> LoadBalancerAttribute s {$sel:value:LoadBalancerAttribute' :: Maybe Text value = Maybe Text a} :: LoadBalancerAttribute) instance Data.FromXML LoadBalancerAttribute where parseXML :: [Node] -> Either String LoadBalancerAttribute parseXML [Node] x = Maybe Text -> Maybe Text -> LoadBalancerAttribute LoadBalancerAttribute' 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 "Key") 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 "Value") instance Prelude.Hashable LoadBalancerAttribute where hashWithSalt :: Int -> LoadBalancerAttribute -> Int hashWithSalt Int _salt LoadBalancerAttribute' {Maybe Text value :: Maybe Text key :: Maybe Text $sel:value:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text $sel:key:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text ..} = Int _salt forall a. Hashable a => Int -> a -> Int `Prelude.hashWithSalt` Maybe Text key forall a. Hashable a => Int -> a -> Int `Prelude.hashWithSalt` Maybe Text value instance Prelude.NFData LoadBalancerAttribute where rnf :: LoadBalancerAttribute -> () rnf LoadBalancerAttribute' {Maybe Text value :: Maybe Text key :: Maybe Text $sel:value:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text $sel:key:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text ..} = forall a. NFData a => a -> () Prelude.rnf Maybe Text key seq :: forall a b. a -> b -> b `Prelude.seq` forall a. NFData a => a -> () Prelude.rnf Maybe Text value instance Data.ToQuery LoadBalancerAttribute where toQuery :: LoadBalancerAttribute -> QueryString toQuery LoadBalancerAttribute' {Maybe Text value :: Maybe Text key :: Maybe Text $sel:value:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text $sel:key:LoadBalancerAttribute' :: LoadBalancerAttribute -> Maybe Text ..} = forall a. Monoid a => [a] -> a Prelude.mconcat [ByteString "Key" forall a. ToQuery a => ByteString -> a -> QueryString Data.=: Maybe Text key, ByteString "Value" forall a. ToQuery a => ByteString -> a -> QueryString Data.=: Maybe Text value]