{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.WAF.DeleteGeoMatchSet
  ( 
    DeleteGeoMatchSet (..),
    newDeleteGeoMatchSet,
    
    deleteGeoMatchSet_geoMatchSetId,
    deleteGeoMatchSet_changeToken,
    
    DeleteGeoMatchSetResponse (..),
    newDeleteGeoMatchSetResponse,
    
    deleteGeoMatchSetResponse_changeToken,
    deleteGeoMatchSetResponse_httpStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.WAF.Types
data DeleteGeoMatchSet = DeleteGeoMatchSet'
  { 
    
    
    DeleteGeoMatchSet -> Text
geoMatchSetId :: Prelude.Text,
    
    DeleteGeoMatchSet -> Text
changeToken :: Prelude.Text
  }
  deriving (DeleteGeoMatchSet -> DeleteGeoMatchSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGeoMatchSet -> DeleteGeoMatchSet -> Bool
$c/= :: DeleteGeoMatchSet -> DeleteGeoMatchSet -> Bool
== :: DeleteGeoMatchSet -> DeleteGeoMatchSet -> Bool
$c== :: DeleteGeoMatchSet -> DeleteGeoMatchSet -> Bool
Prelude.Eq, ReadPrec [DeleteGeoMatchSet]
ReadPrec DeleteGeoMatchSet
Int -> ReadS DeleteGeoMatchSet
ReadS [DeleteGeoMatchSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGeoMatchSet]
$creadListPrec :: ReadPrec [DeleteGeoMatchSet]
readPrec :: ReadPrec DeleteGeoMatchSet
$creadPrec :: ReadPrec DeleteGeoMatchSet
readList :: ReadS [DeleteGeoMatchSet]
$creadList :: ReadS [DeleteGeoMatchSet]
readsPrec :: Int -> ReadS DeleteGeoMatchSet
$creadsPrec :: Int -> ReadS DeleteGeoMatchSet
Prelude.Read, Int -> DeleteGeoMatchSet -> ShowS
[DeleteGeoMatchSet] -> ShowS
DeleteGeoMatchSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGeoMatchSet] -> ShowS
$cshowList :: [DeleteGeoMatchSet] -> ShowS
show :: DeleteGeoMatchSet -> String
$cshow :: DeleteGeoMatchSet -> String
showsPrec :: Int -> DeleteGeoMatchSet -> ShowS
$cshowsPrec :: Int -> DeleteGeoMatchSet -> ShowS
Prelude.Show, forall x. Rep DeleteGeoMatchSet x -> DeleteGeoMatchSet
forall x. DeleteGeoMatchSet -> Rep DeleteGeoMatchSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGeoMatchSet x -> DeleteGeoMatchSet
$cfrom :: forall x. DeleteGeoMatchSet -> Rep DeleteGeoMatchSet x
Prelude.Generic)
newDeleteGeoMatchSet ::
  
  Prelude.Text ->
  
  Prelude.Text ->
  DeleteGeoMatchSet
newDeleteGeoMatchSet :: Text -> Text -> DeleteGeoMatchSet
newDeleteGeoMatchSet Text
pGeoMatchSetId_ Text
pChangeToken_ =
  DeleteGeoMatchSet'
    { $sel:geoMatchSetId:DeleteGeoMatchSet' :: Text
geoMatchSetId = Text
pGeoMatchSetId_,
      $sel:changeToken:DeleteGeoMatchSet' :: Text
changeToken = Text
pChangeToken_
    }
deleteGeoMatchSet_geoMatchSetId :: Lens.Lens' DeleteGeoMatchSet Prelude.Text
deleteGeoMatchSet_geoMatchSetId :: Lens' DeleteGeoMatchSet Text
deleteGeoMatchSet_geoMatchSetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGeoMatchSet' {Text
geoMatchSetId :: Text
$sel:geoMatchSetId:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
geoMatchSetId} -> Text
geoMatchSetId) (\s :: DeleteGeoMatchSet
s@DeleteGeoMatchSet' {} Text
a -> DeleteGeoMatchSet
s {$sel:geoMatchSetId:DeleteGeoMatchSet' :: Text
geoMatchSetId = Text
a} :: DeleteGeoMatchSet)
deleteGeoMatchSet_changeToken :: Lens.Lens' DeleteGeoMatchSet Prelude.Text
deleteGeoMatchSet_changeToken :: Lens' DeleteGeoMatchSet Text
deleteGeoMatchSet_changeToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGeoMatchSet' {Text
changeToken :: Text
$sel:changeToken:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
changeToken} -> Text
changeToken) (\s :: DeleteGeoMatchSet
s@DeleteGeoMatchSet' {} Text
a -> DeleteGeoMatchSet
s {$sel:changeToken:DeleteGeoMatchSet' :: Text
changeToken = Text
a} :: DeleteGeoMatchSet)
instance Core.AWSRequest DeleteGeoMatchSet where
  type
    AWSResponse DeleteGeoMatchSet =
      DeleteGeoMatchSetResponse
  request :: (Service -> Service)
-> DeleteGeoMatchSet -> Request DeleteGeoMatchSet
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteGeoMatchSet
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteGeoMatchSet)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> DeleteGeoMatchSetResponse
DeleteGeoMatchSetResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ChangeToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )
instance Prelude.Hashable DeleteGeoMatchSet where
  hashWithSalt :: Int -> DeleteGeoMatchSet -> Int
hashWithSalt Int
_salt DeleteGeoMatchSet' {Text
changeToken :: Text
geoMatchSetId :: Text
$sel:changeToken:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
$sel:geoMatchSetId:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
geoMatchSetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
changeToken
instance Prelude.NFData DeleteGeoMatchSet where
  rnf :: DeleteGeoMatchSet -> ()
rnf DeleteGeoMatchSet' {Text
changeToken :: Text
geoMatchSetId :: Text
$sel:changeToken:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
$sel:geoMatchSetId:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
geoMatchSetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
changeToken
instance Data.ToHeaders DeleteGeoMatchSet where
  toHeaders :: DeleteGeoMatchSet -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSWAF_20150824.DeleteGeoMatchSet" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )
instance Data.ToJSON DeleteGeoMatchSet where
  toJSON :: DeleteGeoMatchSet -> Value
toJSON DeleteGeoMatchSet' {Text
changeToken :: Text
geoMatchSetId :: Text
$sel:changeToken:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
$sel:geoMatchSetId:DeleteGeoMatchSet' :: DeleteGeoMatchSet -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"GeoMatchSetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
geoMatchSetId),
            forall a. a -> Maybe a
Prelude.Just (Key
"ChangeToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
changeToken)
          ]
      )
instance Data.ToPath DeleteGeoMatchSet where
  toPath :: DeleteGeoMatchSet -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DeleteGeoMatchSet where
  toQuery :: DeleteGeoMatchSet -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DeleteGeoMatchSetResponse = DeleteGeoMatchSetResponse'
  { 
    
    
    DeleteGeoMatchSetResponse -> Maybe Text
changeToken :: Prelude.Maybe Prelude.Text,
    
    DeleteGeoMatchSetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteGeoMatchSetResponse -> DeleteGeoMatchSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGeoMatchSetResponse -> DeleteGeoMatchSetResponse -> Bool
$c/= :: DeleteGeoMatchSetResponse -> DeleteGeoMatchSetResponse -> Bool
== :: DeleteGeoMatchSetResponse -> DeleteGeoMatchSetResponse -> Bool
$c== :: DeleteGeoMatchSetResponse -> DeleteGeoMatchSetResponse -> Bool
Prelude.Eq, ReadPrec [DeleteGeoMatchSetResponse]
ReadPrec DeleteGeoMatchSetResponse
Int -> ReadS DeleteGeoMatchSetResponse
ReadS [DeleteGeoMatchSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGeoMatchSetResponse]
$creadListPrec :: ReadPrec [DeleteGeoMatchSetResponse]
readPrec :: ReadPrec DeleteGeoMatchSetResponse
$creadPrec :: ReadPrec DeleteGeoMatchSetResponse
readList :: ReadS [DeleteGeoMatchSetResponse]
$creadList :: ReadS [DeleteGeoMatchSetResponse]
readsPrec :: Int -> ReadS DeleteGeoMatchSetResponse
$creadsPrec :: Int -> ReadS DeleteGeoMatchSetResponse
Prelude.Read, Int -> DeleteGeoMatchSetResponse -> ShowS
[DeleteGeoMatchSetResponse] -> ShowS
DeleteGeoMatchSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGeoMatchSetResponse] -> ShowS
$cshowList :: [DeleteGeoMatchSetResponse] -> ShowS
show :: DeleteGeoMatchSetResponse -> String
$cshow :: DeleteGeoMatchSetResponse -> String
showsPrec :: Int -> DeleteGeoMatchSetResponse -> ShowS
$cshowsPrec :: Int -> DeleteGeoMatchSetResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteGeoMatchSetResponse x -> DeleteGeoMatchSetResponse
forall x.
DeleteGeoMatchSetResponse -> Rep DeleteGeoMatchSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteGeoMatchSetResponse x -> DeleteGeoMatchSetResponse
$cfrom :: forall x.
DeleteGeoMatchSetResponse -> Rep DeleteGeoMatchSetResponse x
Prelude.Generic)
newDeleteGeoMatchSetResponse ::
  
  Prelude.Int ->
  DeleteGeoMatchSetResponse
newDeleteGeoMatchSetResponse :: Int -> DeleteGeoMatchSetResponse
newDeleteGeoMatchSetResponse Int
pHttpStatus_ =
  DeleteGeoMatchSetResponse'
    { $sel:changeToken:DeleteGeoMatchSetResponse' :: Maybe Text
changeToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteGeoMatchSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }
deleteGeoMatchSetResponse_changeToken :: Lens.Lens' DeleteGeoMatchSetResponse (Prelude.Maybe Prelude.Text)
deleteGeoMatchSetResponse_changeToken :: Lens' DeleteGeoMatchSetResponse (Maybe Text)
deleteGeoMatchSetResponse_changeToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGeoMatchSetResponse' {Maybe Text
changeToken :: Maybe Text
$sel:changeToken:DeleteGeoMatchSetResponse' :: DeleteGeoMatchSetResponse -> Maybe Text
changeToken} -> Maybe Text
changeToken) (\s :: DeleteGeoMatchSetResponse
s@DeleteGeoMatchSetResponse' {} Maybe Text
a -> DeleteGeoMatchSetResponse
s {$sel:changeToken:DeleteGeoMatchSetResponse' :: Maybe Text
changeToken = Maybe Text
a} :: DeleteGeoMatchSetResponse)
deleteGeoMatchSetResponse_httpStatus :: Lens.Lens' DeleteGeoMatchSetResponse Prelude.Int
deleteGeoMatchSetResponse_httpStatus :: Lens' DeleteGeoMatchSetResponse Int
deleteGeoMatchSetResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGeoMatchSetResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteGeoMatchSetResponse' :: DeleteGeoMatchSetResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteGeoMatchSetResponse
s@DeleteGeoMatchSetResponse' {} Int
a -> DeleteGeoMatchSetResponse
s {$sel:httpStatus:DeleteGeoMatchSetResponse' :: Int
httpStatus = Int
a} :: DeleteGeoMatchSetResponse)
instance Prelude.NFData DeleteGeoMatchSetResponse where
  rnf :: DeleteGeoMatchSetResponse -> ()
rnf DeleteGeoMatchSetResponse' {Int
Maybe Text
httpStatus :: Int
changeToken :: Maybe Text
$sel:httpStatus:DeleteGeoMatchSetResponse' :: DeleteGeoMatchSetResponse -> Int
$sel:changeToken:DeleteGeoMatchSetResponse' :: DeleteGeoMatchSetResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
changeToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus