{-# 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.DescribeAttack
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes the details of a DDoS attack.
module Amazonka.Shield.DescribeAttack
  ( -- * Creating a Request
    DescribeAttack (..),
    newDescribeAttack,

    -- * Request Lenses
    describeAttack_attackId,

    -- * Destructuring the Response
    DescribeAttackResponse (..),
    newDescribeAttackResponse,

    -- * Response Lenses
    describeAttackResponse_attack,
    describeAttackResponse_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:/ 'newDescribeAttack' smart constructor.
data DescribeAttack = DescribeAttack'
  { -- | The unique identifier (ID) for the attack.
    DescribeAttack -> Text
attackId :: Prelude.Text
  }
  deriving (DescribeAttack -> DescribeAttack -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAttack -> DescribeAttack -> Bool
$c/= :: DescribeAttack -> DescribeAttack -> Bool
== :: DescribeAttack -> DescribeAttack -> Bool
$c== :: DescribeAttack -> DescribeAttack -> Bool
Prelude.Eq, ReadPrec [DescribeAttack]
ReadPrec DescribeAttack
Int -> ReadS DescribeAttack
ReadS [DescribeAttack]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAttack]
$creadListPrec :: ReadPrec [DescribeAttack]
readPrec :: ReadPrec DescribeAttack
$creadPrec :: ReadPrec DescribeAttack
readList :: ReadS [DescribeAttack]
$creadList :: ReadS [DescribeAttack]
readsPrec :: Int -> ReadS DescribeAttack
$creadsPrec :: Int -> ReadS DescribeAttack
Prelude.Read, Int -> DescribeAttack -> ShowS
[DescribeAttack] -> ShowS
DescribeAttack -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAttack] -> ShowS
$cshowList :: [DescribeAttack] -> ShowS
show :: DescribeAttack -> String
$cshow :: DescribeAttack -> String
showsPrec :: Int -> DescribeAttack -> ShowS
$cshowsPrec :: Int -> DescribeAttack -> ShowS
Prelude.Show, forall x. Rep DescribeAttack x -> DescribeAttack
forall x. DescribeAttack -> Rep DescribeAttack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAttack x -> DescribeAttack
$cfrom :: forall x. DescribeAttack -> Rep DescribeAttack x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAttack' 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:
--
-- 'attackId', 'describeAttack_attackId' - The unique identifier (ID) for the attack.
newDescribeAttack ::
  -- | 'attackId'
  Prelude.Text ->
  DescribeAttack
newDescribeAttack :: Text -> DescribeAttack
newDescribeAttack Text
pAttackId_ =
  DescribeAttack' {$sel:attackId:DescribeAttack' :: Text
attackId = Text
pAttackId_}

-- | The unique identifier (ID) for the attack.
describeAttack_attackId :: Lens.Lens' DescribeAttack Prelude.Text
describeAttack_attackId :: Lens' DescribeAttack Text
describeAttack_attackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttack' {Text
attackId :: Text
$sel:attackId:DescribeAttack' :: DescribeAttack -> Text
attackId} -> Text
attackId) (\s :: DescribeAttack
s@DescribeAttack' {} Text
a -> DescribeAttack
s {$sel:attackId:DescribeAttack' :: Text
attackId = Text
a} :: DescribeAttack)

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

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

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

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

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

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

-- |
-- Create a value of 'DescribeAttackResponse' 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:
--
-- 'attack', 'describeAttackResponse_attack' - The attack that you requested.
--
-- 'httpStatus', 'describeAttackResponse_httpStatus' - The response's http status code.
newDescribeAttackResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeAttackResponse
newDescribeAttackResponse :: Int -> DescribeAttackResponse
newDescribeAttackResponse Int
pHttpStatus_ =
  DescribeAttackResponse'
    { $sel:attack:DescribeAttackResponse' :: Maybe AttackDetail
attack = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeAttackResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The attack that you requested.
describeAttackResponse_attack :: Lens.Lens' DescribeAttackResponse (Prelude.Maybe AttackDetail)
describeAttackResponse_attack :: Lens' DescribeAttackResponse (Maybe AttackDetail)
describeAttackResponse_attack = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttackResponse' {Maybe AttackDetail
attack :: Maybe AttackDetail
$sel:attack:DescribeAttackResponse' :: DescribeAttackResponse -> Maybe AttackDetail
attack} -> Maybe AttackDetail
attack) (\s :: DescribeAttackResponse
s@DescribeAttackResponse' {} Maybe AttackDetail
a -> DescribeAttackResponse
s {$sel:attack:DescribeAttackResponse' :: Maybe AttackDetail
attack = Maybe AttackDetail
a} :: DescribeAttackResponse)

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

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