{-# 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.WAFV2.Types.HTTPRequest
-- 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.WAFV2.Types.HTTPRequest 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
import Amazonka.WAFV2.Types.HTTPHeader

-- | Part of the response from GetSampledRequests. This is a complex type
-- that appears as @Request@ in the response syntax. @HTTPRequest@ contains
-- information about one of the web requests.
--
-- /See:/ 'newHTTPRequest' smart constructor.
data HTTPRequest = HTTPRequest'
  { -- | The IP address that the request originated from. If the web ACL is
    -- associated with a CloudFront distribution, this is the value of one of
    -- the following fields in CloudFront access logs:
    --
    -- -   @c-ip@, if the viewer did not use an HTTP proxy or a load balancer
    --     to send the request
    --
    -- -   @x-forwarded-for@, if the viewer did use an HTTP proxy or a load
    --     balancer to send the request
    HTTPRequest -> Maybe Text
clientIP :: Prelude.Maybe Prelude.Text,
    -- | The two-letter country code for the country that the request originated
    -- from. For a current list of country codes, see the Wikipedia entry
    -- <https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2 ISO 3166-1 alpha-2>.
    HTTPRequest -> Maybe Text
country :: Prelude.Maybe Prelude.Text,
    -- | The HTTP version specified in the sampled web request, for example,
    -- @HTTP\/1.1@.
    HTTPRequest -> Maybe Text
hTTPVersion :: Prelude.Maybe Prelude.Text,
    -- | A complex type that contains the name and value for each header in the
    -- sampled web request.
    HTTPRequest -> Maybe [HTTPHeader]
headers :: Prelude.Maybe [HTTPHeader],
    -- | The HTTP method specified in the sampled web request.
    HTTPRequest -> Maybe Text
method :: Prelude.Maybe Prelude.Text,
    -- | The URI path of the request, which identifies the resource, for example,
    -- @\/images\/daily-ad.jpg@.
    HTTPRequest -> Maybe Text
uri :: Prelude.Maybe Prelude.Text
  }
  deriving (HTTPRequest -> HTTPRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HTTPRequest -> HTTPRequest -> Bool
$c/= :: HTTPRequest -> HTTPRequest -> Bool
== :: HTTPRequest -> HTTPRequest -> Bool
$c== :: HTTPRequest -> HTTPRequest -> Bool
Prelude.Eq, ReadPrec [HTTPRequest]
ReadPrec HTTPRequest
Int -> ReadS HTTPRequest
ReadS [HTTPRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HTTPRequest]
$creadListPrec :: ReadPrec [HTTPRequest]
readPrec :: ReadPrec HTTPRequest
$creadPrec :: ReadPrec HTTPRequest
readList :: ReadS [HTTPRequest]
$creadList :: ReadS [HTTPRequest]
readsPrec :: Int -> ReadS HTTPRequest
$creadsPrec :: Int -> ReadS HTTPRequest
Prelude.Read, Int -> HTTPRequest -> ShowS
[HTTPRequest] -> ShowS
HTTPRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HTTPRequest] -> ShowS
$cshowList :: [HTTPRequest] -> ShowS
show :: HTTPRequest -> String
$cshow :: HTTPRequest -> String
showsPrec :: Int -> HTTPRequest -> ShowS
$cshowsPrec :: Int -> HTTPRequest -> ShowS
Prelude.Show, forall x. Rep HTTPRequest x -> HTTPRequest
forall x. HTTPRequest -> Rep HTTPRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HTTPRequest x -> HTTPRequest
$cfrom :: forall x. HTTPRequest -> Rep HTTPRequest x
Prelude.Generic)

-- |
-- Create a value of 'HTTPRequest' 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:
--
-- 'clientIP', 'hTTPRequest_clientIP' - The IP address that the request originated from. If the web ACL is
-- associated with a CloudFront distribution, this is the value of one of
-- the following fields in CloudFront access logs:
--
-- -   @c-ip@, if the viewer did not use an HTTP proxy or a load balancer
--     to send the request
--
-- -   @x-forwarded-for@, if the viewer did use an HTTP proxy or a load
--     balancer to send the request
--
-- 'country', 'hTTPRequest_country' - The two-letter country code for the country that the request originated
-- from. For a current list of country codes, see the Wikipedia entry
-- <https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2 ISO 3166-1 alpha-2>.
--
-- 'hTTPVersion', 'hTTPRequest_hTTPVersion' - The HTTP version specified in the sampled web request, for example,
-- @HTTP\/1.1@.
--
-- 'headers', 'hTTPRequest_headers' - A complex type that contains the name and value for each header in the
-- sampled web request.
--
-- 'method', 'hTTPRequest_method' - The HTTP method specified in the sampled web request.
--
-- 'uri', 'hTTPRequest_uri' - The URI path of the request, which identifies the resource, for example,
-- @\/images\/daily-ad.jpg@.
newHTTPRequest ::
  HTTPRequest
newHTTPRequest :: HTTPRequest
newHTTPRequest =
  HTTPRequest'
    { $sel:clientIP:HTTPRequest' :: Maybe Text
clientIP = forall a. Maybe a
Prelude.Nothing,
      $sel:country:HTTPRequest' :: Maybe Text
country = forall a. Maybe a
Prelude.Nothing,
      $sel:hTTPVersion:HTTPRequest' :: Maybe Text
hTTPVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:headers:HTTPRequest' :: Maybe [HTTPHeader]
headers = forall a. Maybe a
Prelude.Nothing,
      $sel:method:HTTPRequest' :: Maybe Text
method = forall a. Maybe a
Prelude.Nothing,
      $sel:uri:HTTPRequest' :: Maybe Text
uri = forall a. Maybe a
Prelude.Nothing
    }

-- | The IP address that the request originated from. If the web ACL is
-- associated with a CloudFront distribution, this is the value of one of
-- the following fields in CloudFront access logs:
--
-- -   @c-ip@, if the viewer did not use an HTTP proxy or a load balancer
--     to send the request
--
-- -   @x-forwarded-for@, if the viewer did use an HTTP proxy or a load
--     balancer to send the request
hTTPRequest_clientIP :: Lens.Lens' HTTPRequest (Prelude.Maybe Prelude.Text)
hTTPRequest_clientIP :: Lens' HTTPRequest (Maybe Text)
hTTPRequest_clientIP = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HTTPRequest' {Maybe Text
clientIP :: Maybe Text
$sel:clientIP:HTTPRequest' :: HTTPRequest -> Maybe Text
clientIP} -> Maybe Text
clientIP) (\s :: HTTPRequest
s@HTTPRequest' {} Maybe Text
a -> HTTPRequest
s {$sel:clientIP:HTTPRequest' :: Maybe Text
clientIP = Maybe Text
a} :: HTTPRequest)

-- | The two-letter country code for the country that the request originated
-- from. For a current list of country codes, see the Wikipedia entry
-- <https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2 ISO 3166-1 alpha-2>.
hTTPRequest_country :: Lens.Lens' HTTPRequest (Prelude.Maybe Prelude.Text)
hTTPRequest_country :: Lens' HTTPRequest (Maybe Text)
hTTPRequest_country = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HTTPRequest' {Maybe Text
country :: Maybe Text
$sel:country:HTTPRequest' :: HTTPRequest -> Maybe Text
country} -> Maybe Text
country) (\s :: HTTPRequest
s@HTTPRequest' {} Maybe Text
a -> HTTPRequest
s {$sel:country:HTTPRequest' :: Maybe Text
country = Maybe Text
a} :: HTTPRequest)

-- | The HTTP version specified in the sampled web request, for example,
-- @HTTP\/1.1@.
hTTPRequest_hTTPVersion :: Lens.Lens' HTTPRequest (Prelude.Maybe Prelude.Text)
hTTPRequest_hTTPVersion :: Lens' HTTPRequest (Maybe Text)
hTTPRequest_hTTPVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HTTPRequest' {Maybe Text
hTTPVersion :: Maybe Text
$sel:hTTPVersion:HTTPRequest' :: HTTPRequest -> Maybe Text
hTTPVersion} -> Maybe Text
hTTPVersion) (\s :: HTTPRequest
s@HTTPRequest' {} Maybe Text
a -> HTTPRequest
s {$sel:hTTPVersion:HTTPRequest' :: Maybe Text
hTTPVersion = Maybe Text
a} :: HTTPRequest)

-- | A complex type that contains the name and value for each header in the
-- sampled web request.
hTTPRequest_headers :: Lens.Lens' HTTPRequest (Prelude.Maybe [HTTPHeader])
hTTPRequest_headers :: Lens' HTTPRequest (Maybe [HTTPHeader])
hTTPRequest_headers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HTTPRequest' {Maybe [HTTPHeader]
headers :: Maybe [HTTPHeader]
$sel:headers:HTTPRequest' :: HTTPRequest -> Maybe [HTTPHeader]
headers} -> Maybe [HTTPHeader]
headers) (\s :: HTTPRequest
s@HTTPRequest' {} Maybe [HTTPHeader]
a -> HTTPRequest
s {$sel:headers:HTTPRequest' :: Maybe [HTTPHeader]
headers = Maybe [HTTPHeader]
a} :: HTTPRequest) 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 HTTP method specified in the sampled web request.
hTTPRequest_method :: Lens.Lens' HTTPRequest (Prelude.Maybe Prelude.Text)
hTTPRequest_method :: Lens' HTTPRequest (Maybe Text)
hTTPRequest_method = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HTTPRequest' {Maybe Text
method :: Maybe Text
$sel:method:HTTPRequest' :: HTTPRequest -> Maybe Text
method} -> Maybe Text
method) (\s :: HTTPRequest
s@HTTPRequest' {} Maybe Text
a -> HTTPRequest
s {$sel:method:HTTPRequest' :: Maybe Text
method = Maybe Text
a} :: HTTPRequest)

-- | The URI path of the request, which identifies the resource, for example,
-- @\/images\/daily-ad.jpg@.
hTTPRequest_uri :: Lens.Lens' HTTPRequest (Prelude.Maybe Prelude.Text)
hTTPRequest_uri :: Lens' HTTPRequest (Maybe Text)
hTTPRequest_uri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HTTPRequest' {Maybe Text
uri :: Maybe Text
$sel:uri:HTTPRequest' :: HTTPRequest -> Maybe Text
uri} -> Maybe Text
uri) (\s :: HTTPRequest
s@HTTPRequest' {} Maybe Text
a -> HTTPRequest
s {$sel:uri:HTTPRequest' :: Maybe Text
uri = Maybe Text
a} :: HTTPRequest)

instance Data.FromJSON HTTPRequest where
  parseJSON :: Value -> Parser HTTPRequest
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HTTPRequest"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [HTTPHeader]
-> Maybe Text
-> Maybe Text
-> HTTPRequest
HTTPRequest'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ClientIP")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Country")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"HTTPVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Headers" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Method")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"URI")
      )

instance Prelude.Hashable HTTPRequest where
  hashWithSalt :: Int -> HTTPRequest -> Int
hashWithSalt Int
_salt HTTPRequest' {Maybe [HTTPHeader]
Maybe Text
uri :: Maybe Text
method :: Maybe Text
headers :: Maybe [HTTPHeader]
hTTPVersion :: Maybe Text
country :: Maybe Text
clientIP :: Maybe Text
$sel:uri:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:method:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:headers:HTTPRequest' :: HTTPRequest -> Maybe [HTTPHeader]
$sel:hTTPVersion:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:country:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:clientIP:HTTPRequest' :: HTTPRequest -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientIP
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
country
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hTTPVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [HTTPHeader]
headers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
method
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
uri

instance Prelude.NFData HTTPRequest where
  rnf :: HTTPRequest -> ()
rnf HTTPRequest' {Maybe [HTTPHeader]
Maybe Text
uri :: Maybe Text
method :: Maybe Text
headers :: Maybe [HTTPHeader]
hTTPVersion :: Maybe Text
country :: Maybe Text
clientIP :: Maybe Text
$sel:uri:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:method:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:headers:HTTPRequest' :: HTTPRequest -> Maybe [HTTPHeader]
$sel:hTTPVersion:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:country:HTTPRequest' :: HTTPRequest -> Maybe Text
$sel:clientIP:HTTPRequest' :: HTTPRequest -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientIP
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
country
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hTTPVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [HTTPHeader]
headers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
method
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
uri