{-# 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.WAFRegional.Types.SampledHTTPRequest
-- 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.WAFRegional.Types.SampledHTTPRequest 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.WAFRegional.Types.HTTPRequest

-- | This is __AWS WAF Classic__ documentation. For more information, see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/classic-waf-chapter.html AWS WAF Classic>
-- in the developer guide.
--
-- __For the latest version of AWS WAF__, use the AWS WAFV2 API and see the
-- <https://docs.aws.amazon.com/waf/latest/developerguide/waf-chapter.html AWS WAF Developer Guide>.
-- With the latest version, AWS WAF has a single set of endpoints for
-- regional and global use.
--
-- The response from a GetSampledRequests request includes a
-- @SampledHTTPRequests@ complex type that appears as @SampledRequests@ in
-- the response syntax. @SampledHTTPRequests@ contains one
-- @SampledHTTPRequest@ object for each web request that is returned by
-- @GetSampledRequests@.
--
-- /See:/ 'newSampledHTTPRequest' smart constructor.
data SampledHTTPRequest = SampledHTTPRequest'
  { -- | The action for the @Rule@ that the request matched: @ALLOW@, @BLOCK@, or
    -- @COUNT@.
    SampledHTTPRequest -> Maybe Text
action :: Prelude.Maybe Prelude.Text,
    -- | This value is returned if the @GetSampledRequests@ request specifies the
    -- ID of a @RuleGroup@ rather than the ID of an individual rule.
    -- @RuleWithinRuleGroup@ is the rule within the specified @RuleGroup@ that
    -- matched the request listed in the response.
    SampledHTTPRequest -> Maybe Text
ruleWithinRuleGroup :: Prelude.Maybe Prelude.Text,
    -- | The time at which AWS WAF received the request from your AWS resource,
    -- in Unix time format (in seconds).
    SampledHTTPRequest -> Maybe POSIX
timestamp :: Prelude.Maybe Data.POSIX,
    -- | A complex type that contains detailed information about the request.
    SampledHTTPRequest -> HTTPRequest
request :: HTTPRequest,
    -- | A value that indicates how one result in the response relates
    -- proportionally to other results in the response. A result that has a
    -- weight of @2@ represents roughly twice as many CloudFront web requests
    -- as a result that has a weight of @1@.
    SampledHTTPRequest -> Natural
weight :: Prelude.Natural
  }
  deriving (SampledHTTPRequest -> SampledHTTPRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SampledHTTPRequest -> SampledHTTPRequest -> Bool
$c/= :: SampledHTTPRequest -> SampledHTTPRequest -> Bool
== :: SampledHTTPRequest -> SampledHTTPRequest -> Bool
$c== :: SampledHTTPRequest -> SampledHTTPRequest -> Bool
Prelude.Eq, ReadPrec [SampledHTTPRequest]
ReadPrec SampledHTTPRequest
Int -> ReadS SampledHTTPRequest
ReadS [SampledHTTPRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SampledHTTPRequest]
$creadListPrec :: ReadPrec [SampledHTTPRequest]
readPrec :: ReadPrec SampledHTTPRequest
$creadPrec :: ReadPrec SampledHTTPRequest
readList :: ReadS [SampledHTTPRequest]
$creadList :: ReadS [SampledHTTPRequest]
readsPrec :: Int -> ReadS SampledHTTPRequest
$creadsPrec :: Int -> ReadS SampledHTTPRequest
Prelude.Read, Int -> SampledHTTPRequest -> ShowS
[SampledHTTPRequest] -> ShowS
SampledHTTPRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SampledHTTPRequest] -> ShowS
$cshowList :: [SampledHTTPRequest] -> ShowS
show :: SampledHTTPRequest -> String
$cshow :: SampledHTTPRequest -> String
showsPrec :: Int -> SampledHTTPRequest -> ShowS
$cshowsPrec :: Int -> SampledHTTPRequest -> ShowS
Prelude.Show, forall x. Rep SampledHTTPRequest x -> SampledHTTPRequest
forall x. SampledHTTPRequest -> Rep SampledHTTPRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SampledHTTPRequest x -> SampledHTTPRequest
$cfrom :: forall x. SampledHTTPRequest -> Rep SampledHTTPRequest x
Prelude.Generic)

-- |
-- Create a value of 'SampledHTTPRequest' 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:
--
-- 'action', 'sampledHTTPRequest_action' - The action for the @Rule@ that the request matched: @ALLOW@, @BLOCK@, or
-- @COUNT@.
--
-- 'ruleWithinRuleGroup', 'sampledHTTPRequest_ruleWithinRuleGroup' - This value is returned if the @GetSampledRequests@ request specifies the
-- ID of a @RuleGroup@ rather than the ID of an individual rule.
-- @RuleWithinRuleGroup@ is the rule within the specified @RuleGroup@ that
-- matched the request listed in the response.
--
-- 'timestamp', 'sampledHTTPRequest_timestamp' - The time at which AWS WAF received the request from your AWS resource,
-- in Unix time format (in seconds).
--
-- 'request', 'sampledHTTPRequest_request' - A complex type that contains detailed information about the request.
--
-- 'weight', 'sampledHTTPRequest_weight' - A value that indicates how one result in the response relates
-- proportionally to other results in the response. A result that has a
-- weight of @2@ represents roughly twice as many CloudFront web requests
-- as a result that has a weight of @1@.
newSampledHTTPRequest ::
  -- | 'request'
  HTTPRequest ->
  -- | 'weight'
  Prelude.Natural ->
  SampledHTTPRequest
newSampledHTTPRequest :: HTTPRequest -> Natural -> SampledHTTPRequest
newSampledHTTPRequest HTTPRequest
pRequest_ Natural
pWeight_ =
  SampledHTTPRequest'
    { $sel:action:SampledHTTPRequest' :: Maybe Text
action = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleWithinRuleGroup:SampledHTTPRequest' :: Maybe Text
ruleWithinRuleGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:timestamp:SampledHTTPRequest' :: Maybe POSIX
timestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:request:SampledHTTPRequest' :: HTTPRequest
request = HTTPRequest
pRequest_,
      $sel:weight:SampledHTTPRequest' :: Natural
weight = Natural
pWeight_
    }

-- | The action for the @Rule@ that the request matched: @ALLOW@, @BLOCK@, or
-- @COUNT@.
sampledHTTPRequest_action :: Lens.Lens' SampledHTTPRequest (Prelude.Maybe Prelude.Text)
sampledHTTPRequest_action :: Lens' SampledHTTPRequest (Maybe Text)
sampledHTTPRequest_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SampledHTTPRequest' {Maybe Text
action :: Maybe Text
$sel:action:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe Text
action} -> Maybe Text
action) (\s :: SampledHTTPRequest
s@SampledHTTPRequest' {} Maybe Text
a -> SampledHTTPRequest
s {$sel:action:SampledHTTPRequest' :: Maybe Text
action = Maybe Text
a} :: SampledHTTPRequest)

-- | This value is returned if the @GetSampledRequests@ request specifies the
-- ID of a @RuleGroup@ rather than the ID of an individual rule.
-- @RuleWithinRuleGroup@ is the rule within the specified @RuleGroup@ that
-- matched the request listed in the response.
sampledHTTPRequest_ruleWithinRuleGroup :: Lens.Lens' SampledHTTPRequest (Prelude.Maybe Prelude.Text)
sampledHTTPRequest_ruleWithinRuleGroup :: Lens' SampledHTTPRequest (Maybe Text)
sampledHTTPRequest_ruleWithinRuleGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SampledHTTPRequest' {Maybe Text
ruleWithinRuleGroup :: Maybe Text
$sel:ruleWithinRuleGroup:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe Text
ruleWithinRuleGroup} -> Maybe Text
ruleWithinRuleGroup) (\s :: SampledHTTPRequest
s@SampledHTTPRequest' {} Maybe Text
a -> SampledHTTPRequest
s {$sel:ruleWithinRuleGroup:SampledHTTPRequest' :: Maybe Text
ruleWithinRuleGroup = Maybe Text
a} :: SampledHTTPRequest)

-- | The time at which AWS WAF received the request from your AWS resource,
-- in Unix time format (in seconds).
sampledHTTPRequest_timestamp :: Lens.Lens' SampledHTTPRequest (Prelude.Maybe Prelude.UTCTime)
sampledHTTPRequest_timestamp :: Lens' SampledHTTPRequest (Maybe UTCTime)
sampledHTTPRequest_timestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SampledHTTPRequest' {Maybe POSIX
timestamp :: Maybe POSIX
$sel:timestamp:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe POSIX
timestamp} -> Maybe POSIX
timestamp) (\s :: SampledHTTPRequest
s@SampledHTTPRequest' {} Maybe POSIX
a -> SampledHTTPRequest
s {$sel:timestamp:SampledHTTPRequest' :: Maybe POSIX
timestamp = Maybe POSIX
a} :: SampledHTTPRequest) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A complex type that contains detailed information about the request.
sampledHTTPRequest_request :: Lens.Lens' SampledHTTPRequest HTTPRequest
sampledHTTPRequest_request :: Lens' SampledHTTPRequest HTTPRequest
sampledHTTPRequest_request = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SampledHTTPRequest' {HTTPRequest
request :: HTTPRequest
$sel:request:SampledHTTPRequest' :: SampledHTTPRequest -> HTTPRequest
request} -> HTTPRequest
request) (\s :: SampledHTTPRequest
s@SampledHTTPRequest' {} HTTPRequest
a -> SampledHTTPRequest
s {$sel:request:SampledHTTPRequest' :: HTTPRequest
request = HTTPRequest
a} :: SampledHTTPRequest)

-- | A value that indicates how one result in the response relates
-- proportionally to other results in the response. A result that has a
-- weight of @2@ represents roughly twice as many CloudFront web requests
-- as a result that has a weight of @1@.
sampledHTTPRequest_weight :: Lens.Lens' SampledHTTPRequest Prelude.Natural
sampledHTTPRequest_weight :: Lens' SampledHTTPRequest Natural
sampledHTTPRequest_weight = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SampledHTTPRequest' {Natural
weight :: Natural
$sel:weight:SampledHTTPRequest' :: SampledHTTPRequest -> Natural
weight} -> Natural
weight) (\s :: SampledHTTPRequest
s@SampledHTTPRequest' {} Natural
a -> SampledHTTPRequest
s {$sel:weight:SampledHTTPRequest' :: Natural
weight = Natural
a} :: SampledHTTPRequest)

instance Data.FromJSON SampledHTTPRequest where
  parseJSON :: Value -> Parser SampledHTTPRequest
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SampledHTTPRequest"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe POSIX
-> HTTPRequest
-> Natural
-> SampledHTTPRequest
SampledHTTPRequest'
            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
"Action")
            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
"RuleWithinRuleGroup")
            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
"Timestamp")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Request")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Weight")
      )

instance Prelude.Hashable SampledHTTPRequest where
  hashWithSalt :: Int -> SampledHTTPRequest -> Int
hashWithSalt Int
_salt SampledHTTPRequest' {Natural
Maybe Text
Maybe POSIX
HTTPRequest
weight :: Natural
request :: HTTPRequest
timestamp :: Maybe POSIX
ruleWithinRuleGroup :: Maybe Text
action :: Maybe Text
$sel:weight:SampledHTTPRequest' :: SampledHTTPRequest -> Natural
$sel:request:SampledHTTPRequest' :: SampledHTTPRequest -> HTTPRequest
$sel:timestamp:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe POSIX
$sel:ruleWithinRuleGroup:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe Text
$sel:action:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
action
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ruleWithinRuleGroup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
timestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HTTPRequest
request
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
weight

instance Prelude.NFData SampledHTTPRequest where
  rnf :: SampledHTTPRequest -> ()
rnf SampledHTTPRequest' {Natural
Maybe Text
Maybe POSIX
HTTPRequest
weight :: Natural
request :: HTTPRequest
timestamp :: Maybe POSIX
ruleWithinRuleGroup :: Maybe Text
action :: Maybe Text
$sel:weight:SampledHTTPRequest' :: SampledHTTPRequest -> Natural
$sel:request:SampledHTTPRequest' :: SampledHTTPRequest -> HTTPRequest
$sel:timestamp:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe POSIX
$sel:ruleWithinRuleGroup:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe Text
$sel:action:SampledHTTPRequest' :: SampledHTTPRequest -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
action
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ruleWithinRuleGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
timestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HTTPRequest
request
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
weight