{-# 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 #-}

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

-- |
-- Module      : Amazonka.WAFRegional.DisassociateWebACL
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This is __AWS WAF Classic Regional__ 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.
--
-- Removes a web ACL from the specified resource, either an application
-- load balancer or Amazon API Gateway stage.
module Amazonka.WAFRegional.DisassociateWebACL
  ( -- * Creating a Request
    DisassociateWebACL (..),
    newDisassociateWebACL,

    -- * Request Lenses
    disassociateWebACL_resourceArn,

    -- * Destructuring the Response
    DisassociateWebACLResponse (..),
    newDisassociateWebACLResponse,

    -- * Response Lenses
    disassociateWebACLResponse_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.WAFRegional.Types

-- | /See:/ 'newDisassociateWebACL' smart constructor.
data DisassociateWebACL = DisassociateWebACL'
  { -- | The ARN (Amazon Resource Name) of the resource from which the web ACL is
    -- being removed, either an application load balancer or Amazon API Gateway
    -- stage.
    --
    -- The ARN should be in one of the following formats:
    --
    -- -   For an Application Load Balancer:
    --     @arn:aws:elasticloadbalancing:@/@region@/@:@/@account-id@/@:loadbalancer\/app\/@/@load-balancer-name@/@\/@/@load-balancer-id@/@ @
    --
    -- -   For an Amazon API Gateway stage:
    --     @arn:aws:apigateway:@/@region@/@::\/restapis\/@/@api-id@/@\/stages\/@/@stage-name@/@ @
    DisassociateWebACL -> Text
resourceArn :: Prelude.Text
  }
  deriving (DisassociateWebACL -> DisassociateWebACL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateWebACL -> DisassociateWebACL -> Bool
$c/= :: DisassociateWebACL -> DisassociateWebACL -> Bool
== :: DisassociateWebACL -> DisassociateWebACL -> Bool
$c== :: DisassociateWebACL -> DisassociateWebACL -> Bool
Prelude.Eq, ReadPrec [DisassociateWebACL]
ReadPrec DisassociateWebACL
Int -> ReadS DisassociateWebACL
ReadS [DisassociateWebACL]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateWebACL]
$creadListPrec :: ReadPrec [DisassociateWebACL]
readPrec :: ReadPrec DisassociateWebACL
$creadPrec :: ReadPrec DisassociateWebACL
readList :: ReadS [DisassociateWebACL]
$creadList :: ReadS [DisassociateWebACL]
readsPrec :: Int -> ReadS DisassociateWebACL
$creadsPrec :: Int -> ReadS DisassociateWebACL
Prelude.Read, Int -> DisassociateWebACL -> ShowS
[DisassociateWebACL] -> ShowS
DisassociateWebACL -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateWebACL] -> ShowS
$cshowList :: [DisassociateWebACL] -> ShowS
show :: DisassociateWebACL -> String
$cshow :: DisassociateWebACL -> String
showsPrec :: Int -> DisassociateWebACL -> ShowS
$cshowsPrec :: Int -> DisassociateWebACL -> ShowS
Prelude.Show, forall x. Rep DisassociateWebACL x -> DisassociateWebACL
forall x. DisassociateWebACL -> Rep DisassociateWebACL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisassociateWebACL x -> DisassociateWebACL
$cfrom :: forall x. DisassociateWebACL -> Rep DisassociateWebACL x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateWebACL' 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:
--
-- 'resourceArn', 'disassociateWebACL_resourceArn' - The ARN (Amazon Resource Name) of the resource from which the web ACL is
-- being removed, either an application load balancer or Amazon API Gateway
-- stage.
--
-- The ARN should be in one of the following formats:
--
-- -   For an Application Load Balancer:
--     @arn:aws:elasticloadbalancing:@/@region@/@:@/@account-id@/@:loadbalancer\/app\/@/@load-balancer-name@/@\/@/@load-balancer-id@/@ @
--
-- -   For an Amazon API Gateway stage:
--     @arn:aws:apigateway:@/@region@/@::\/restapis\/@/@api-id@/@\/stages\/@/@stage-name@/@ @
newDisassociateWebACL ::
  -- | 'resourceArn'
  Prelude.Text ->
  DisassociateWebACL
newDisassociateWebACL :: Text -> DisassociateWebACL
newDisassociateWebACL Text
pResourceArn_ =
  DisassociateWebACL' {$sel:resourceArn:DisassociateWebACL' :: Text
resourceArn = Text
pResourceArn_}

-- | The ARN (Amazon Resource Name) of the resource from which the web ACL is
-- being removed, either an application load balancer or Amazon API Gateway
-- stage.
--
-- The ARN should be in one of the following formats:
--
-- -   For an Application Load Balancer:
--     @arn:aws:elasticloadbalancing:@/@region@/@:@/@account-id@/@:loadbalancer\/app\/@/@load-balancer-name@/@\/@/@load-balancer-id@/@ @
--
-- -   For an Amazon API Gateway stage:
--     @arn:aws:apigateway:@/@region@/@::\/restapis\/@/@api-id@/@\/stages\/@/@stage-name@/@ @
disassociateWebACL_resourceArn :: Lens.Lens' DisassociateWebACL Prelude.Text
disassociateWebACL_resourceArn :: Lens' DisassociateWebACL Text
disassociateWebACL_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateWebACL' {Text
resourceArn :: Text
$sel:resourceArn:DisassociateWebACL' :: DisassociateWebACL -> Text
resourceArn} -> Text
resourceArn) (\s :: DisassociateWebACL
s@DisassociateWebACL' {} Text
a -> DisassociateWebACL
s {$sel:resourceArn:DisassociateWebACL' :: Text
resourceArn = Text
a} :: DisassociateWebACL)

instance Core.AWSRequest DisassociateWebACL where
  type
    AWSResponse DisassociateWebACL =
      DisassociateWebACLResponse
  request :: (Service -> Service)
-> DisassociateWebACL -> Request DisassociateWebACL
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 DisassociateWebACL
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateWebACL)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DisassociateWebACLResponse
DisassociateWebACLResponse'
            forall (f :: * -> *) a b. Functor 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 DisassociateWebACL where
  hashWithSalt :: Int -> DisassociateWebACL -> Int
hashWithSalt Int
_salt DisassociateWebACL' {Text
resourceArn :: Text
$sel:resourceArn:DisassociateWebACL' :: DisassociateWebACL -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance Prelude.NFData DisassociateWebACL where
  rnf :: DisassociateWebACL -> ()
rnf DisassociateWebACL' {Text
resourceArn :: Text
$sel:resourceArn:DisassociateWebACL' :: DisassociateWebACL -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

instance Data.ToHeaders DisassociateWebACL where
  toHeaders :: DisassociateWebACL -> 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_Regional_20161128.DisassociateWebACL" ::
                          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 DisassociateWebACL where
  toJSON :: DisassociateWebACL -> Value
toJSON DisassociateWebACL' {Text
resourceArn :: Text
$sel:resourceArn:DisassociateWebACL' :: DisassociateWebACL -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"ResourceArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
resourceArn)]
      )

instance Data.ToPath DisassociateWebACL where
  toPath :: DisassociateWebACL -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DisassociateWebACL where
  toQuery :: DisassociateWebACL -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDisassociateWebACLResponse' smart constructor.
data DisassociateWebACLResponse = DisassociateWebACLResponse'
  { -- | The response's http status code.
    DisassociateWebACLResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateWebACLResponse -> DisassociateWebACLResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateWebACLResponse -> DisassociateWebACLResponse -> Bool
$c/= :: DisassociateWebACLResponse -> DisassociateWebACLResponse -> Bool
== :: DisassociateWebACLResponse -> DisassociateWebACLResponse -> Bool
$c== :: DisassociateWebACLResponse -> DisassociateWebACLResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateWebACLResponse]
ReadPrec DisassociateWebACLResponse
Int -> ReadS DisassociateWebACLResponse
ReadS [DisassociateWebACLResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateWebACLResponse]
$creadListPrec :: ReadPrec [DisassociateWebACLResponse]
readPrec :: ReadPrec DisassociateWebACLResponse
$creadPrec :: ReadPrec DisassociateWebACLResponse
readList :: ReadS [DisassociateWebACLResponse]
$creadList :: ReadS [DisassociateWebACLResponse]
readsPrec :: Int -> ReadS DisassociateWebACLResponse
$creadsPrec :: Int -> ReadS DisassociateWebACLResponse
Prelude.Read, Int -> DisassociateWebACLResponse -> ShowS
[DisassociateWebACLResponse] -> ShowS
DisassociateWebACLResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateWebACLResponse] -> ShowS
$cshowList :: [DisassociateWebACLResponse] -> ShowS
show :: DisassociateWebACLResponse -> String
$cshow :: DisassociateWebACLResponse -> String
showsPrec :: Int -> DisassociateWebACLResponse -> ShowS
$cshowsPrec :: Int -> DisassociateWebACLResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateWebACLResponse x -> DisassociateWebACLResponse
forall x.
DisassociateWebACLResponse -> Rep DisassociateWebACLResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateWebACLResponse x -> DisassociateWebACLResponse
$cfrom :: forall x.
DisassociateWebACLResponse -> Rep DisassociateWebACLResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateWebACLResponse' 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:
--
-- 'httpStatus', 'disassociateWebACLResponse_httpStatus' - The response's http status code.
newDisassociateWebACLResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateWebACLResponse
newDisassociateWebACLResponse :: Int -> DisassociateWebACLResponse
newDisassociateWebACLResponse Int
pHttpStatus_ =
  DisassociateWebACLResponse'
    { $sel:httpStatus:DisassociateWebACLResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

-- | The response's http status code.
disassociateWebACLResponse_httpStatus :: Lens.Lens' DisassociateWebACLResponse Prelude.Int
disassociateWebACLResponse_httpStatus :: Lens' DisassociateWebACLResponse Int
disassociateWebACLResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateWebACLResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateWebACLResponse' :: DisassociateWebACLResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DisassociateWebACLResponse
s@DisassociateWebACLResponse' {} Int
a -> DisassociateWebACLResponse
s {$sel:httpStatus:DisassociateWebACLResponse' :: Int
httpStatus = Int
a} :: DisassociateWebACLResponse)

instance Prelude.NFData DisassociateWebACLResponse where
  rnf :: DisassociateWebACLResponse -> ()
rnf DisassociateWebACLResponse' {Int
httpStatus :: Int
$sel:httpStatus:DisassociateWebACLResponse' :: DisassociateWebACLResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus