{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}

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

-- |
-- Module      : Amazonka.WAF.Types.PredicateType
-- 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.WAF.Types.PredicateType
  ( PredicateType
      ( ..,
        PredicateType_ByteMatch,
        PredicateType_GeoMatch,
        PredicateType_IPMatch,
        PredicateType_RegexMatch,
        PredicateType_SizeConstraint,
        PredicateType_SqlInjectionMatch,
        PredicateType_XssMatch
      ),
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

newtype PredicateType = PredicateType'
  { PredicateType -> Text
fromPredicateType ::
      Data.Text
  }
  deriving stock
    ( Int -> PredicateType -> ShowS
[PredicateType] -> ShowS
PredicateType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PredicateType] -> ShowS
$cshowList :: [PredicateType] -> ShowS
show :: PredicateType -> String
$cshow :: PredicateType -> String
showsPrec :: Int -> PredicateType -> ShowS
$cshowsPrec :: Int -> PredicateType -> ShowS
Prelude.Show,
      ReadPrec [PredicateType]
ReadPrec PredicateType
Int -> ReadS PredicateType
ReadS [PredicateType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PredicateType]
$creadListPrec :: ReadPrec [PredicateType]
readPrec :: ReadPrec PredicateType
$creadPrec :: ReadPrec PredicateType
readList :: ReadS [PredicateType]
$creadList :: ReadS [PredicateType]
readsPrec :: Int -> ReadS PredicateType
$creadsPrec :: Int -> ReadS PredicateType
Prelude.Read,
      PredicateType -> PredicateType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PredicateType -> PredicateType -> Bool
$c/= :: PredicateType -> PredicateType -> Bool
== :: PredicateType -> PredicateType -> Bool
$c== :: PredicateType -> PredicateType -> Bool
Prelude.Eq,
      Eq PredicateType
PredicateType -> PredicateType -> Bool
PredicateType -> PredicateType -> Ordering
PredicateType -> PredicateType -> PredicateType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PredicateType -> PredicateType -> PredicateType
$cmin :: PredicateType -> PredicateType -> PredicateType
max :: PredicateType -> PredicateType -> PredicateType
$cmax :: PredicateType -> PredicateType -> PredicateType
>= :: PredicateType -> PredicateType -> Bool
$c>= :: PredicateType -> PredicateType -> Bool
> :: PredicateType -> PredicateType -> Bool
$c> :: PredicateType -> PredicateType -> Bool
<= :: PredicateType -> PredicateType -> Bool
$c<= :: PredicateType -> PredicateType -> Bool
< :: PredicateType -> PredicateType -> Bool
$c< :: PredicateType -> PredicateType -> Bool
compare :: PredicateType -> PredicateType -> Ordering
$ccompare :: PredicateType -> PredicateType -> Ordering
Prelude.Ord,
      forall x. Rep PredicateType x -> PredicateType
forall x. PredicateType -> Rep PredicateType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PredicateType x -> PredicateType
$cfrom :: forall x. PredicateType -> Rep PredicateType x
Prelude.Generic
    )
  deriving newtype
    ( Eq PredicateType
Int -> PredicateType -> Int
PredicateType -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: PredicateType -> Int
$chash :: PredicateType -> Int
hashWithSalt :: Int -> PredicateType -> Int
$chashWithSalt :: Int -> PredicateType -> Int
Prelude.Hashable,
      PredicateType -> ()
forall a. (a -> ()) -> NFData a
rnf :: PredicateType -> ()
$crnf :: PredicateType -> ()
Prelude.NFData,
      Text -> Either String PredicateType
forall a. (Text -> Either String a) -> FromText a
fromText :: Text -> Either String PredicateType
$cfromText :: Text -> Either String PredicateType
Data.FromText,
      PredicateType -> Text
forall a. (a -> Text) -> ToText a
toText :: PredicateType -> Text
$ctoText :: PredicateType -> Text
Data.ToText,
      PredicateType -> ByteString
forall a. (a -> ByteString) -> ToByteString a
toBS :: PredicateType -> ByteString
$ctoBS :: PredicateType -> ByteString
Data.ToByteString,
      PredicateType -> ByteStringBuilder
forall a. (a -> ByteStringBuilder) -> ToLog a
build :: PredicateType -> ByteStringBuilder
$cbuild :: PredicateType -> ByteStringBuilder
Data.ToLog,
      HeaderName -> PredicateType -> [Header]
forall a. (HeaderName -> a -> [Header]) -> ToHeader a
toHeader :: HeaderName -> PredicateType -> [Header]
$ctoHeader :: HeaderName -> PredicateType -> [Header]
Data.ToHeader,
      PredicateType -> QueryString
forall a. (a -> QueryString) -> ToQuery a
toQuery :: PredicateType -> QueryString
$ctoQuery :: PredicateType -> QueryString
Data.ToQuery,
      Value -> Parser [PredicateType]
Value -> Parser PredicateType
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PredicateType]
$cparseJSONList :: Value -> Parser [PredicateType]
parseJSON :: Value -> Parser PredicateType
$cparseJSON :: Value -> Parser PredicateType
Data.FromJSON,
      FromJSONKeyFunction [PredicateType]
FromJSONKeyFunction PredicateType
forall a.
FromJSONKeyFunction a -> FromJSONKeyFunction [a] -> FromJSONKey a
fromJSONKeyList :: FromJSONKeyFunction [PredicateType]
$cfromJSONKeyList :: FromJSONKeyFunction [PredicateType]
fromJSONKey :: FromJSONKeyFunction PredicateType
$cfromJSONKey :: FromJSONKeyFunction PredicateType
Data.FromJSONKey,
      [PredicateType] -> Encoding
[PredicateType] -> Value
PredicateType -> Encoding
PredicateType -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PredicateType] -> Encoding
$ctoEncodingList :: [PredicateType] -> Encoding
toJSONList :: [PredicateType] -> Value
$ctoJSONList :: [PredicateType] -> Value
toEncoding :: PredicateType -> Encoding
$ctoEncoding :: PredicateType -> Encoding
toJSON :: PredicateType -> Value
$ctoJSON :: PredicateType -> Value
Data.ToJSON,
      ToJSONKeyFunction [PredicateType]
ToJSONKeyFunction PredicateType
forall a.
ToJSONKeyFunction a -> ToJSONKeyFunction [a] -> ToJSONKey a
toJSONKeyList :: ToJSONKeyFunction [PredicateType]
$ctoJSONKeyList :: ToJSONKeyFunction [PredicateType]
toJSONKey :: ToJSONKeyFunction PredicateType
$ctoJSONKey :: ToJSONKeyFunction PredicateType
Data.ToJSONKey,
      [Node] -> Either String PredicateType
forall a. ([Node] -> Either String a) -> FromXML a
parseXML :: [Node] -> Either String PredicateType
$cparseXML :: [Node] -> Either String PredicateType
Data.FromXML,
      PredicateType -> XML
forall a. (a -> XML) -> ToXML a
toXML :: PredicateType -> XML
$ctoXML :: PredicateType -> XML
Data.ToXML
    )

pattern PredicateType_ByteMatch :: PredicateType
pattern $bPredicateType_ByteMatch :: PredicateType
$mPredicateType_ByteMatch :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_ByteMatch = PredicateType' "ByteMatch"

pattern PredicateType_GeoMatch :: PredicateType
pattern $bPredicateType_GeoMatch :: PredicateType
$mPredicateType_GeoMatch :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_GeoMatch = PredicateType' "GeoMatch"

pattern PredicateType_IPMatch :: PredicateType
pattern $bPredicateType_IPMatch :: PredicateType
$mPredicateType_IPMatch :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_IPMatch = PredicateType' "IPMatch"

pattern PredicateType_RegexMatch :: PredicateType
pattern $bPredicateType_RegexMatch :: PredicateType
$mPredicateType_RegexMatch :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_RegexMatch = PredicateType' "RegexMatch"

pattern PredicateType_SizeConstraint :: PredicateType
pattern $bPredicateType_SizeConstraint :: PredicateType
$mPredicateType_SizeConstraint :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_SizeConstraint = PredicateType' "SizeConstraint"

pattern PredicateType_SqlInjectionMatch :: PredicateType
pattern $bPredicateType_SqlInjectionMatch :: PredicateType
$mPredicateType_SqlInjectionMatch :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_SqlInjectionMatch = PredicateType' "SqlInjectionMatch"

pattern PredicateType_XssMatch :: PredicateType
pattern $bPredicateType_XssMatch :: PredicateType
$mPredicateType_XssMatch :: forall {r}. PredicateType -> ((# #) -> r) -> ((# #) -> r) -> r
PredicateType_XssMatch = PredicateType' "XssMatch"

{-# COMPLETE
  PredicateType_ByteMatch,
  PredicateType_GeoMatch,
  PredicateType_IPMatch,
  PredicateType_RegexMatch,
  PredicateType_SizeConstraint,
  PredicateType_SqlInjectionMatch,
  PredicateType_XssMatch,
  PredicateType'
  #-}