{-# 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.WAFV2.AssociateWebACL
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates a web ACL with a regional application resource, to protect
-- the resource. A regional application can be an Application Load Balancer
-- (ALB), an Amazon API Gateway REST API, an AppSync GraphQL API, or an
-- Amazon Cognito user pool.
--
-- For Amazon CloudFront, don\'t use this call. Instead, use your
-- CloudFront distribution configuration. To associate a web ACL, in the
-- CloudFront call @UpdateDistribution@, set the web ACL ID to the Amazon
-- Resource Name (ARN) of the web ACL. For information, see
-- <https://docs.aws.amazon.com/cloudfront/latest/APIReference/API_UpdateDistribution.html UpdateDistribution>.
--
-- When you make changes to web ACLs or web ACL components, like rules and
-- rule groups, WAF propagates the changes everywhere that the web ACL and
-- its components are stored and used. Your changes are applied within
-- seconds, but there might be a brief period of inconsistency when the
-- changes have arrived in some places and not in others. So, for example,
-- if you change a rule action setting, the action might be the old action
-- in one area and the new action in another area. Or if you add an IP
-- address to an IP set used in a blocking rule, the new address might
-- briefly be blocked in one area while still allowed in another. This
-- temporary inconsistency can occur when you first associate a web ACL
-- with an Amazon Web Services resource and when you change a web ACL that
-- is already associated with a resource. Generally, any inconsistencies of
-- this type last only a few seconds.
module Amazonka.WAFV2.AssociateWebACL
  ( -- * Creating a Request
    AssociateWebACL (..),
    newAssociateWebACL,

    -- * Request Lenses
    associateWebACL_webACLArn,
    associateWebACL_resourceArn,

    -- * Destructuring the Response
    AssociateWebACLResponse (..),
    newAssociateWebACLResponse,

    -- * Response Lenses
    associateWebACLResponse_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.WAFV2.Types

-- | /See:/ 'newAssociateWebACL' smart constructor.
data AssociateWebACL = AssociateWebACL'
  { -- | The Amazon Resource Name (ARN) of the web ACL that you want to associate
    -- with the resource.
    AssociateWebACL -> Text
webACLArn :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the resource to associate with the web
    -- ACL.
    --
    -- The ARN must 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 REST API:
    --     @arn:aws:apigateway:@/@region@/@::\/restapis\/@/@api-id@/@\/stages\/@/@stage-name@/@ @
    --
    -- -   For an AppSync GraphQL API:
    --     @arn:aws:appsync:@/@region@/@:@/@account-id@/@:apis\/@/@GraphQLApiId@/@ @
    --
    -- -   For an Amazon Cognito user pool:
    --     @arn:aws:cognito-idp:@/@region@/@:@/@account-id@/@:userpool\/@/@user-pool-id@/@ @
    AssociateWebACL -> Text
resourceArn :: Prelude.Text
  }
  deriving (AssociateWebACL -> AssociateWebACL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateWebACL -> AssociateWebACL -> Bool
$c/= :: AssociateWebACL -> AssociateWebACL -> Bool
== :: AssociateWebACL -> AssociateWebACL -> Bool
$c== :: AssociateWebACL -> AssociateWebACL -> Bool
Prelude.Eq, ReadPrec [AssociateWebACL]
ReadPrec AssociateWebACL
Int -> ReadS AssociateWebACL
ReadS [AssociateWebACL]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateWebACL]
$creadListPrec :: ReadPrec [AssociateWebACL]
readPrec :: ReadPrec AssociateWebACL
$creadPrec :: ReadPrec AssociateWebACL
readList :: ReadS [AssociateWebACL]
$creadList :: ReadS [AssociateWebACL]
readsPrec :: Int -> ReadS AssociateWebACL
$creadsPrec :: Int -> ReadS AssociateWebACL
Prelude.Read, Int -> AssociateWebACL -> ShowS
[AssociateWebACL] -> ShowS
AssociateWebACL -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateWebACL] -> ShowS
$cshowList :: [AssociateWebACL] -> ShowS
show :: AssociateWebACL -> String
$cshow :: AssociateWebACL -> String
showsPrec :: Int -> AssociateWebACL -> ShowS
$cshowsPrec :: Int -> AssociateWebACL -> ShowS
Prelude.Show, forall x. Rep AssociateWebACL x -> AssociateWebACL
forall x. AssociateWebACL -> Rep AssociateWebACL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateWebACL x -> AssociateWebACL
$cfrom :: forall x. AssociateWebACL -> Rep AssociateWebACL x
Prelude.Generic)

-- |
-- Create a value of 'AssociateWebACL' 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:
--
-- 'webACLArn', 'associateWebACL_webACLArn' - The Amazon Resource Name (ARN) of the web ACL that you want to associate
-- with the resource.
--
-- 'resourceArn', 'associateWebACL_resourceArn' - The Amazon Resource Name (ARN) of the resource to associate with the web
-- ACL.
--
-- The ARN must 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 REST API:
--     @arn:aws:apigateway:@/@region@/@::\/restapis\/@/@api-id@/@\/stages\/@/@stage-name@/@ @
--
-- -   For an AppSync GraphQL API:
--     @arn:aws:appsync:@/@region@/@:@/@account-id@/@:apis\/@/@GraphQLApiId@/@ @
--
-- -   For an Amazon Cognito user pool:
--     @arn:aws:cognito-idp:@/@region@/@:@/@account-id@/@:userpool\/@/@user-pool-id@/@ @
newAssociateWebACL ::
  -- | 'webACLArn'
  Prelude.Text ->
  -- | 'resourceArn'
  Prelude.Text ->
  AssociateWebACL
newAssociateWebACL :: Text -> Text -> AssociateWebACL
newAssociateWebACL Text
pWebACLArn_ Text
pResourceArn_ =
  AssociateWebACL'
    { $sel:webACLArn:AssociateWebACL' :: Text
webACLArn = Text
pWebACLArn_,
      $sel:resourceArn:AssociateWebACL' :: Text
resourceArn = Text
pResourceArn_
    }

-- | The Amazon Resource Name (ARN) of the web ACL that you want to associate
-- with the resource.
associateWebACL_webACLArn :: Lens.Lens' AssociateWebACL Prelude.Text
associateWebACL_webACLArn :: Lens' AssociateWebACL Text
associateWebACL_webACLArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateWebACL' {Text
webACLArn :: Text
$sel:webACLArn:AssociateWebACL' :: AssociateWebACL -> Text
webACLArn} -> Text
webACLArn) (\s :: AssociateWebACL
s@AssociateWebACL' {} Text
a -> AssociateWebACL
s {$sel:webACLArn:AssociateWebACL' :: Text
webACLArn = Text
a} :: AssociateWebACL)

-- | The Amazon Resource Name (ARN) of the resource to associate with the web
-- ACL.
--
-- The ARN must 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 REST API:
--     @arn:aws:apigateway:@/@region@/@::\/restapis\/@/@api-id@/@\/stages\/@/@stage-name@/@ @
--
-- -   For an AppSync GraphQL API:
--     @arn:aws:appsync:@/@region@/@:@/@account-id@/@:apis\/@/@GraphQLApiId@/@ @
--
-- -   For an Amazon Cognito user pool:
--     @arn:aws:cognito-idp:@/@region@/@:@/@account-id@/@:userpool\/@/@user-pool-id@/@ @
associateWebACL_resourceArn :: Lens.Lens' AssociateWebACL Prelude.Text
associateWebACL_resourceArn :: Lens' AssociateWebACL Text
associateWebACL_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateWebACL' {Text
resourceArn :: Text
$sel:resourceArn:AssociateWebACL' :: AssociateWebACL -> Text
resourceArn} -> Text
resourceArn) (\s :: AssociateWebACL
s@AssociateWebACL' {} Text
a -> AssociateWebACL
s {$sel:resourceArn:AssociateWebACL' :: Text
resourceArn = Text
a} :: AssociateWebACL)

instance Core.AWSRequest AssociateWebACL where
  type
    AWSResponse AssociateWebACL =
      AssociateWebACLResponse
  request :: (Service -> Service) -> AssociateWebACL -> Request AssociateWebACL
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 AssociateWebACL
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AssociateWebACL)))
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 -> AssociateWebACLResponse
AssociateWebACLResponse'
            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 AssociateWebACL where
  hashWithSalt :: Int -> AssociateWebACL -> Int
hashWithSalt Int
_salt AssociateWebACL' {Text
resourceArn :: Text
webACLArn :: Text
$sel:resourceArn:AssociateWebACL' :: AssociateWebACL -> Text
$sel:webACLArn:AssociateWebACL' :: AssociateWebACL -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
webACLArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance Prelude.NFData AssociateWebACL where
  rnf :: AssociateWebACL -> ()
rnf AssociateWebACL' {Text
resourceArn :: Text
webACLArn :: Text
$sel:resourceArn:AssociateWebACL' :: AssociateWebACL -> Text
$sel:webACLArn:AssociateWebACL' :: AssociateWebACL -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
webACLArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

instance Data.ToHeaders AssociateWebACL where
  toHeaders :: AssociateWebACL -> 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_20190729.AssociateWebACL" ::
                          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 AssociateWebACL where
  toJSON :: AssociateWebACL -> Value
toJSON AssociateWebACL' {Text
resourceArn :: Text
webACLArn :: Text
$sel:resourceArn:AssociateWebACL' :: AssociateWebACL -> Text
$sel:webACLArn:AssociateWebACL' :: AssociateWebACL -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"WebACLArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
webACLArn),
            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 AssociateWebACL where
  toPath :: AssociateWebACL -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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