{-# 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.Shield.EnableApplicationLayerAutomaticResponse
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enable the Shield Advanced automatic application layer DDoS mitigation
-- for the protected resource.
--
-- This feature is available for Amazon CloudFront distributions and
-- Application Load Balancers only.
--
-- This causes Shield Advanced to create, verify, and apply WAF rules for
-- DDoS attacks that it detects for the resource. Shield Advanced applies
-- the rules in a Shield rule group inside the web ACL that you\'ve
-- associated with the resource. For information about how automatic
-- mitigation works and the requirements for using it, see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/ddos-advanced-automatic-app-layer-response.html Shield Advanced automatic application layer DDoS mitigation>.
--
-- Don\'t use this action to make changes to automatic mitigation settings
-- when it\'s already enabled for a resource. Instead, use
-- UpdateApplicationLayerAutomaticResponse.
--
-- To use this feature, you must associate a web ACL with the protected
-- resource. The web ACL must be created using the latest version of WAF
-- (v2). You can associate the web ACL through the Shield Advanced console
-- at <https://console.aws.amazon.com/wafv2/shieldv2#/>. For more
-- information, see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/getting-started-ddos.html Getting Started with Shield Advanced>.
-- You can also associate the web ACL to the resource through the WAF
-- console or the WAF API, but you must manage Shield Advanced automatic
-- mitigation through Shield Advanced. For information about WAF, see
-- <https://docs.aws.amazon.com/waf/latest/developerguide/ WAF Developer Guide>.
module Amazonka.Shield.EnableApplicationLayerAutomaticResponse
  ( -- * Creating a Request
    EnableApplicationLayerAutomaticResponse (..),
    newEnableApplicationLayerAutomaticResponse,

    -- * Request Lenses
    enableApplicationLayerAutomaticResponse_resourceArn,
    enableApplicationLayerAutomaticResponse_action,

    -- * Destructuring the Response
    EnableApplicationLayerAutomaticResponseResponse (..),
    newEnableApplicationLayerAutomaticResponseResponse,

    -- * Response Lenses
    enableApplicationLayerAutomaticResponseResponse_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.Shield.Types

-- | /See:/ 'newEnableApplicationLayerAutomaticResponse' smart constructor.
data EnableApplicationLayerAutomaticResponse = EnableApplicationLayerAutomaticResponse'
  { -- | The ARN (Amazon Resource Name) of the protected resource.
    EnableApplicationLayerAutomaticResponse -> Text
resourceArn :: Prelude.Text,
    -- | Specifies the action setting that Shield Advanced should use in the WAF
    -- rules that it creates on behalf of the protected resource in response to
    -- DDoS attacks. You specify this as part of the configuration for the
    -- automatic application layer DDoS mitigation feature, when you enable or
    -- update automatic mitigation. Shield Advanced creates the WAF rules in a
    -- Shield Advanced-managed rule group, inside the web ACL that you have
    -- associated with the resource.
    EnableApplicationLayerAutomaticResponse -> ResponseAction
action :: ResponseAction
  }
  deriving (EnableApplicationLayerAutomaticResponse
-> EnableApplicationLayerAutomaticResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableApplicationLayerAutomaticResponse
-> EnableApplicationLayerAutomaticResponse -> Bool
$c/= :: EnableApplicationLayerAutomaticResponse
-> EnableApplicationLayerAutomaticResponse -> Bool
== :: EnableApplicationLayerAutomaticResponse
-> EnableApplicationLayerAutomaticResponse -> Bool
$c== :: EnableApplicationLayerAutomaticResponse
-> EnableApplicationLayerAutomaticResponse -> Bool
Prelude.Eq, ReadPrec [EnableApplicationLayerAutomaticResponse]
ReadPrec EnableApplicationLayerAutomaticResponse
Int -> ReadS EnableApplicationLayerAutomaticResponse
ReadS [EnableApplicationLayerAutomaticResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnableApplicationLayerAutomaticResponse]
$creadListPrec :: ReadPrec [EnableApplicationLayerAutomaticResponse]
readPrec :: ReadPrec EnableApplicationLayerAutomaticResponse
$creadPrec :: ReadPrec EnableApplicationLayerAutomaticResponse
readList :: ReadS [EnableApplicationLayerAutomaticResponse]
$creadList :: ReadS [EnableApplicationLayerAutomaticResponse]
readsPrec :: Int -> ReadS EnableApplicationLayerAutomaticResponse
$creadsPrec :: Int -> ReadS EnableApplicationLayerAutomaticResponse
Prelude.Read, Int -> EnableApplicationLayerAutomaticResponse -> ShowS
[EnableApplicationLayerAutomaticResponse] -> ShowS
EnableApplicationLayerAutomaticResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableApplicationLayerAutomaticResponse] -> ShowS
$cshowList :: [EnableApplicationLayerAutomaticResponse] -> ShowS
show :: EnableApplicationLayerAutomaticResponse -> String
$cshow :: EnableApplicationLayerAutomaticResponse -> String
showsPrec :: Int -> EnableApplicationLayerAutomaticResponse -> ShowS
$cshowsPrec :: Int -> EnableApplicationLayerAutomaticResponse -> ShowS
Prelude.Show, forall x.
Rep EnableApplicationLayerAutomaticResponse x
-> EnableApplicationLayerAutomaticResponse
forall x.
EnableApplicationLayerAutomaticResponse
-> Rep EnableApplicationLayerAutomaticResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EnableApplicationLayerAutomaticResponse x
-> EnableApplicationLayerAutomaticResponse
$cfrom :: forall x.
EnableApplicationLayerAutomaticResponse
-> Rep EnableApplicationLayerAutomaticResponse x
Prelude.Generic)

-- |
-- Create a value of 'EnableApplicationLayerAutomaticResponse' 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', 'enableApplicationLayerAutomaticResponse_resourceArn' - The ARN (Amazon Resource Name) of the protected resource.
--
-- 'action', 'enableApplicationLayerAutomaticResponse_action' - Specifies the action setting that Shield Advanced should use in the WAF
-- rules that it creates on behalf of the protected resource in response to
-- DDoS attacks. You specify this as part of the configuration for the
-- automatic application layer DDoS mitigation feature, when you enable or
-- update automatic mitigation. Shield Advanced creates the WAF rules in a
-- Shield Advanced-managed rule group, inside the web ACL that you have
-- associated with the resource.
newEnableApplicationLayerAutomaticResponse ::
  -- | 'resourceArn'
  Prelude.Text ->
  -- | 'action'
  ResponseAction ->
  EnableApplicationLayerAutomaticResponse
newEnableApplicationLayerAutomaticResponse :: Text -> ResponseAction -> EnableApplicationLayerAutomaticResponse
newEnableApplicationLayerAutomaticResponse
  Text
pResourceArn_
  ResponseAction
pAction_ =
    EnableApplicationLayerAutomaticResponse'
      { $sel:resourceArn:EnableApplicationLayerAutomaticResponse' :: Text
resourceArn =
          Text
pResourceArn_,
        $sel:action:EnableApplicationLayerAutomaticResponse' :: ResponseAction
action = ResponseAction
pAction_
      }

-- | The ARN (Amazon Resource Name) of the protected resource.
enableApplicationLayerAutomaticResponse_resourceArn :: Lens.Lens' EnableApplicationLayerAutomaticResponse Prelude.Text
enableApplicationLayerAutomaticResponse_resourceArn :: Lens' EnableApplicationLayerAutomaticResponse Text
enableApplicationLayerAutomaticResponse_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableApplicationLayerAutomaticResponse' {Text
resourceArn :: Text
$sel:resourceArn:EnableApplicationLayerAutomaticResponse' :: EnableApplicationLayerAutomaticResponse -> Text
resourceArn} -> Text
resourceArn) (\s :: EnableApplicationLayerAutomaticResponse
s@EnableApplicationLayerAutomaticResponse' {} Text
a -> EnableApplicationLayerAutomaticResponse
s {$sel:resourceArn:EnableApplicationLayerAutomaticResponse' :: Text
resourceArn = Text
a} :: EnableApplicationLayerAutomaticResponse)

-- | Specifies the action setting that Shield Advanced should use in the WAF
-- rules that it creates on behalf of the protected resource in response to
-- DDoS attacks. You specify this as part of the configuration for the
-- automatic application layer DDoS mitigation feature, when you enable or
-- update automatic mitigation. Shield Advanced creates the WAF rules in a
-- Shield Advanced-managed rule group, inside the web ACL that you have
-- associated with the resource.
enableApplicationLayerAutomaticResponse_action :: Lens.Lens' EnableApplicationLayerAutomaticResponse ResponseAction
enableApplicationLayerAutomaticResponse_action :: Lens' EnableApplicationLayerAutomaticResponse ResponseAction
enableApplicationLayerAutomaticResponse_action = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EnableApplicationLayerAutomaticResponse' {ResponseAction
action :: ResponseAction
$sel:action:EnableApplicationLayerAutomaticResponse' :: EnableApplicationLayerAutomaticResponse -> ResponseAction
action} -> ResponseAction
action) (\s :: EnableApplicationLayerAutomaticResponse
s@EnableApplicationLayerAutomaticResponse' {} ResponseAction
a -> EnableApplicationLayerAutomaticResponse
s {$sel:action:EnableApplicationLayerAutomaticResponse' :: ResponseAction
action = ResponseAction
a} :: EnableApplicationLayerAutomaticResponse)

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

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

instance
  Data.ToHeaders
    EnableApplicationLayerAutomaticResponse
  where
  toHeaders :: EnableApplicationLayerAutomaticResponse -> 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
"AWSShield_20160616.EnableApplicationLayerAutomaticResponse" ::
                          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
    EnableApplicationLayerAutomaticResponse
  where
  toJSON :: EnableApplicationLayerAutomaticResponse -> Value
toJSON EnableApplicationLayerAutomaticResponse' {Text
ResponseAction
action :: ResponseAction
resourceArn :: Text
$sel:action:EnableApplicationLayerAutomaticResponse' :: EnableApplicationLayerAutomaticResponse -> ResponseAction
$sel:resourceArn:EnableApplicationLayerAutomaticResponse' :: EnableApplicationLayerAutomaticResponse -> 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),
            forall a. a -> Maybe a
Prelude.Just (Key
"Action" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ResponseAction
action)
          ]
      )

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

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

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

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

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

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