{-# 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.CreateProtection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Enables Shield Advanced for a specific Amazon Web Services resource. The
-- resource can be an Amazon CloudFront distribution, Amazon Route 53
-- hosted zone, Global Accelerator standard accelerator, Elastic IP
-- Address, Application Load Balancer, or a Classic Load Balancer. You can
-- protect Amazon EC2 instances and Network Load Balancers by association
-- with protected Amazon EC2 Elastic IP addresses.
--
-- You can add protection to only a single resource with each
-- @CreateProtection@ request. You can add protection to multiple resources
-- at once 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>
-- and
-- <https://docs.aws.amazon.com/waf/latest/developerguide/configure-new-protection.html Adding Shield Advanced protection to Amazon Web Services resources>.
module Amazonka.Shield.CreateProtection
  ( -- * Creating a Request
    CreateProtection (..),
    newCreateProtection,

    -- * Request Lenses
    createProtection_tags,
    createProtection_name,
    createProtection_resourceArn,

    -- * Destructuring the Response
    CreateProtectionResponse (..),
    newCreateProtectionResponse,

    -- * Response Lenses
    createProtectionResponse_protectionId,
    createProtectionResponse_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:/ 'newCreateProtection' smart constructor.
data CreateProtection = CreateProtection'
  { -- | One or more tag key-value pairs for the Protection object that is
    -- created.
    CreateProtection -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | Friendly name for the @Protection@ you are creating.
    CreateProtection -> Text
name :: Prelude.Text,
    -- | The ARN (Amazon Resource Name) of the resource to be protected.
    --
    -- 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 Elastic Load Balancer (Classic Load Balancer):
    --     @arn:aws:elasticloadbalancing:@/@region@/@:@/@account-id@/@:loadbalancer\/@/@load-balancer-name@/@ @
    --
    -- -   For an Amazon CloudFront distribution:
    --     @arn:aws:cloudfront::@/@account-id@/@:distribution\/@/@distribution-id@/@ @
    --
    -- -   For an Global Accelerator standard accelerator:
    --     @arn:aws:globalaccelerator::@/@account-id@/@:accelerator\/@/@accelerator-id@/@ @
    --
    -- -   For Amazon Route 53:
    --     @arn:aws:route53:::hostedzone\/@/@hosted-zone-id@/@ @
    --
    -- -   For an Elastic IP address:
    --     @arn:aws:ec2:@/@region@/@:@/@account-id@/@:eip-allocation\/@/@allocation-id@/@ @
    CreateProtection -> Text
resourceArn :: Prelude.Text
  }
  deriving (CreateProtection -> CreateProtection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProtection -> CreateProtection -> Bool
$c/= :: CreateProtection -> CreateProtection -> Bool
== :: CreateProtection -> CreateProtection -> Bool
$c== :: CreateProtection -> CreateProtection -> Bool
Prelude.Eq, ReadPrec [CreateProtection]
ReadPrec CreateProtection
Int -> ReadS CreateProtection
ReadS [CreateProtection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProtection]
$creadListPrec :: ReadPrec [CreateProtection]
readPrec :: ReadPrec CreateProtection
$creadPrec :: ReadPrec CreateProtection
readList :: ReadS [CreateProtection]
$creadList :: ReadS [CreateProtection]
readsPrec :: Int -> ReadS CreateProtection
$creadsPrec :: Int -> ReadS CreateProtection
Prelude.Read, Int -> CreateProtection -> ShowS
[CreateProtection] -> ShowS
CreateProtection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProtection] -> ShowS
$cshowList :: [CreateProtection] -> ShowS
show :: CreateProtection -> String
$cshow :: CreateProtection -> String
showsPrec :: Int -> CreateProtection -> ShowS
$cshowsPrec :: Int -> CreateProtection -> ShowS
Prelude.Show, forall x. Rep CreateProtection x -> CreateProtection
forall x. CreateProtection -> Rep CreateProtection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateProtection x -> CreateProtection
$cfrom :: forall x. CreateProtection -> Rep CreateProtection x
Prelude.Generic)

-- |
-- Create a value of 'CreateProtection' 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:
--
-- 'tags', 'createProtection_tags' - One or more tag key-value pairs for the Protection object that is
-- created.
--
-- 'name', 'createProtection_name' - Friendly name for the @Protection@ you are creating.
--
-- 'resourceArn', 'createProtection_resourceArn' - The ARN (Amazon Resource Name) of the resource to be protected.
--
-- 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 Elastic Load Balancer (Classic Load Balancer):
--     @arn:aws:elasticloadbalancing:@/@region@/@:@/@account-id@/@:loadbalancer\/@/@load-balancer-name@/@ @
--
-- -   For an Amazon CloudFront distribution:
--     @arn:aws:cloudfront::@/@account-id@/@:distribution\/@/@distribution-id@/@ @
--
-- -   For an Global Accelerator standard accelerator:
--     @arn:aws:globalaccelerator::@/@account-id@/@:accelerator\/@/@accelerator-id@/@ @
--
-- -   For Amazon Route 53:
--     @arn:aws:route53:::hostedzone\/@/@hosted-zone-id@/@ @
--
-- -   For an Elastic IP address:
--     @arn:aws:ec2:@/@region@/@:@/@account-id@/@:eip-allocation\/@/@allocation-id@/@ @
newCreateProtection ::
  -- | 'name'
  Prelude.Text ->
  -- | 'resourceArn'
  Prelude.Text ->
  CreateProtection
newCreateProtection :: Text -> Text -> CreateProtection
newCreateProtection Text
pName_ Text
pResourceArn_ =
  CreateProtection'
    { $sel:tags:CreateProtection' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateProtection' :: Text
name = Text
pName_,
      $sel:resourceArn:CreateProtection' :: Text
resourceArn = Text
pResourceArn_
    }

-- | One or more tag key-value pairs for the Protection object that is
-- created.
createProtection_tags :: Lens.Lens' CreateProtection (Prelude.Maybe [Tag])
createProtection_tags :: Lens' CreateProtection (Maybe [Tag])
createProtection_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtection' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateProtection' :: CreateProtection -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateProtection
s@CreateProtection' {} Maybe [Tag]
a -> CreateProtection
s {$sel:tags:CreateProtection' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateProtection) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Friendly name for the @Protection@ you are creating.
createProtection_name :: Lens.Lens' CreateProtection Prelude.Text
createProtection_name :: Lens' CreateProtection Text
createProtection_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtection' {Text
name :: Text
$sel:name:CreateProtection' :: CreateProtection -> Text
name} -> Text
name) (\s :: CreateProtection
s@CreateProtection' {} Text
a -> CreateProtection
s {$sel:name:CreateProtection' :: Text
name = Text
a} :: CreateProtection)

-- | The ARN (Amazon Resource Name) of the resource to be protected.
--
-- 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 Elastic Load Balancer (Classic Load Balancer):
--     @arn:aws:elasticloadbalancing:@/@region@/@:@/@account-id@/@:loadbalancer\/@/@load-balancer-name@/@ @
--
-- -   For an Amazon CloudFront distribution:
--     @arn:aws:cloudfront::@/@account-id@/@:distribution\/@/@distribution-id@/@ @
--
-- -   For an Global Accelerator standard accelerator:
--     @arn:aws:globalaccelerator::@/@account-id@/@:accelerator\/@/@accelerator-id@/@ @
--
-- -   For Amazon Route 53:
--     @arn:aws:route53:::hostedzone\/@/@hosted-zone-id@/@ @
--
-- -   For an Elastic IP address:
--     @arn:aws:ec2:@/@region@/@:@/@account-id@/@:eip-allocation\/@/@allocation-id@/@ @
createProtection_resourceArn :: Lens.Lens' CreateProtection Prelude.Text
createProtection_resourceArn :: Lens' CreateProtection Text
createProtection_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtection' {Text
resourceArn :: Text
$sel:resourceArn:CreateProtection' :: CreateProtection -> Text
resourceArn} -> Text
resourceArn) (\s :: CreateProtection
s@CreateProtection' {} Text
a -> CreateProtection
s {$sel:resourceArn:CreateProtection' :: Text
resourceArn = Text
a} :: CreateProtection)

instance Core.AWSRequest CreateProtection where
  type
    AWSResponse CreateProtection =
      CreateProtectionResponse
  request :: (Service -> Service)
-> CreateProtection -> Request CreateProtection
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 CreateProtection
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateProtection)))
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 -> CreateProtectionResponse
CreateProtectionResponse'
            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
"ProtectionId")
            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 CreateProtection where
  hashWithSalt :: Int -> CreateProtection -> Int
hashWithSalt Int
_salt CreateProtection' {Maybe [Tag]
Text
resourceArn :: Text
name :: Text
tags :: Maybe [Tag]
$sel:resourceArn:CreateProtection' :: CreateProtection -> Text
$sel:name:CreateProtection' :: CreateProtection -> Text
$sel:tags:CreateProtection' :: CreateProtection -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

instance Prelude.NFData CreateProtection where
  rnf :: CreateProtection -> ()
rnf CreateProtection' {Maybe [Tag]
Text
resourceArn :: Text
name :: Text
tags :: Maybe [Tag]
$sel:resourceArn:CreateProtection' :: CreateProtection -> Text
$sel:name:CreateProtection' :: CreateProtection -> Text
$sel:tags:CreateProtection' :: CreateProtection -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
resourceArn

instance Data.ToHeaders CreateProtection where
  toHeaders :: CreateProtection -> 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.CreateProtection" ::
                          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 CreateProtection where
  toJSON :: CreateProtection -> Value
toJSON CreateProtection' {Maybe [Tag]
Text
resourceArn :: Text
name :: Text
tags :: Maybe [Tag]
$sel:resourceArn:CreateProtection' :: CreateProtection -> Text
$sel:name:CreateProtection' :: CreateProtection -> Text
$sel:tags:CreateProtection' :: CreateProtection -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            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 CreateProtection where
  toPath :: CreateProtection -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCreateProtectionResponse' smart constructor.
data CreateProtectionResponse = CreateProtectionResponse'
  { -- | The unique identifier (ID) for the Protection object that is created.
    CreateProtectionResponse -> Maybe Text
protectionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateProtectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateProtectionResponse -> CreateProtectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProtectionResponse -> CreateProtectionResponse -> Bool
$c/= :: CreateProtectionResponse -> CreateProtectionResponse -> Bool
== :: CreateProtectionResponse -> CreateProtectionResponse -> Bool
$c== :: CreateProtectionResponse -> CreateProtectionResponse -> Bool
Prelude.Eq, ReadPrec [CreateProtectionResponse]
ReadPrec CreateProtectionResponse
Int -> ReadS CreateProtectionResponse
ReadS [CreateProtectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProtectionResponse]
$creadListPrec :: ReadPrec [CreateProtectionResponse]
readPrec :: ReadPrec CreateProtectionResponse
$creadPrec :: ReadPrec CreateProtectionResponse
readList :: ReadS [CreateProtectionResponse]
$creadList :: ReadS [CreateProtectionResponse]
readsPrec :: Int -> ReadS CreateProtectionResponse
$creadsPrec :: Int -> ReadS CreateProtectionResponse
Prelude.Read, Int -> CreateProtectionResponse -> ShowS
[CreateProtectionResponse] -> ShowS
CreateProtectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProtectionResponse] -> ShowS
$cshowList :: [CreateProtectionResponse] -> ShowS
show :: CreateProtectionResponse -> String
$cshow :: CreateProtectionResponse -> String
showsPrec :: Int -> CreateProtectionResponse -> ShowS
$cshowsPrec :: Int -> CreateProtectionResponse -> ShowS
Prelude.Show, forall x.
Rep CreateProtectionResponse x -> CreateProtectionResponse
forall x.
CreateProtectionResponse -> Rep CreateProtectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateProtectionResponse x -> CreateProtectionResponse
$cfrom :: forall x.
CreateProtectionResponse -> Rep CreateProtectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateProtectionResponse' 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:
--
-- 'protectionId', 'createProtectionResponse_protectionId' - The unique identifier (ID) for the Protection object that is created.
--
-- 'httpStatus', 'createProtectionResponse_httpStatus' - The response's http status code.
newCreateProtectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateProtectionResponse
newCreateProtectionResponse :: Int -> CreateProtectionResponse
newCreateProtectionResponse Int
pHttpStatus_ =
  CreateProtectionResponse'
    { $sel:protectionId:CreateProtectionResponse' :: Maybe Text
protectionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateProtectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique identifier (ID) for the Protection object that is created.
createProtectionResponse_protectionId :: Lens.Lens' CreateProtectionResponse (Prelude.Maybe Prelude.Text)
createProtectionResponse_protectionId :: Lens' CreateProtectionResponse (Maybe Text)
createProtectionResponse_protectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionResponse' {Maybe Text
protectionId :: Maybe Text
$sel:protectionId:CreateProtectionResponse' :: CreateProtectionResponse -> Maybe Text
protectionId} -> Maybe Text
protectionId) (\s :: CreateProtectionResponse
s@CreateProtectionResponse' {} Maybe Text
a -> CreateProtectionResponse
s {$sel:protectionId:CreateProtectionResponse' :: Maybe Text
protectionId = Maybe Text
a} :: CreateProtectionResponse)

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

instance Prelude.NFData CreateProtectionResponse where
  rnf :: CreateProtectionResponse -> ()
rnf CreateProtectionResponse' {Int
Maybe Text
httpStatus :: Int
protectionId :: Maybe Text
$sel:httpStatus:CreateProtectionResponse' :: CreateProtectionResponse -> Int
$sel:protectionId:CreateProtectionResponse' :: CreateProtectionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
protectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus