{-# 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 #-}
module Amazonka.Shield.DescribeAttackStatistics
(
DescribeAttackStatistics (..),
newDescribeAttackStatistics,
DescribeAttackStatisticsResponse (..),
newDescribeAttackStatisticsResponse,
describeAttackStatisticsResponse_httpStatus,
describeAttackStatisticsResponse_timeRange,
describeAttackStatisticsResponse_dataItems,
)
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
data DescribeAttackStatistics = DescribeAttackStatistics'
{
}
deriving (DescribeAttackStatistics -> DescribeAttackStatistics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAttackStatistics -> DescribeAttackStatistics -> Bool
$c/= :: DescribeAttackStatistics -> DescribeAttackStatistics -> Bool
== :: DescribeAttackStatistics -> DescribeAttackStatistics -> Bool
$c== :: DescribeAttackStatistics -> DescribeAttackStatistics -> Bool
Prelude.Eq, ReadPrec [DescribeAttackStatistics]
ReadPrec DescribeAttackStatistics
Int -> ReadS DescribeAttackStatistics
ReadS [DescribeAttackStatistics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAttackStatistics]
$creadListPrec :: ReadPrec [DescribeAttackStatistics]
readPrec :: ReadPrec DescribeAttackStatistics
$creadPrec :: ReadPrec DescribeAttackStatistics
readList :: ReadS [DescribeAttackStatistics]
$creadList :: ReadS [DescribeAttackStatistics]
readsPrec :: Int -> ReadS DescribeAttackStatistics
$creadsPrec :: Int -> ReadS DescribeAttackStatistics
Prelude.Read, Int -> DescribeAttackStatistics -> ShowS
[DescribeAttackStatistics] -> ShowS
DescribeAttackStatistics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAttackStatistics] -> ShowS
$cshowList :: [DescribeAttackStatistics] -> ShowS
show :: DescribeAttackStatistics -> String
$cshow :: DescribeAttackStatistics -> String
showsPrec :: Int -> DescribeAttackStatistics -> ShowS
$cshowsPrec :: Int -> DescribeAttackStatistics -> ShowS
Prelude.Show, forall x.
Rep DescribeAttackStatistics x -> DescribeAttackStatistics
forall x.
DescribeAttackStatistics -> Rep DescribeAttackStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAttackStatistics x -> DescribeAttackStatistics
$cfrom :: forall x.
DescribeAttackStatistics -> Rep DescribeAttackStatistics x
Prelude.Generic)
newDescribeAttackStatistics ::
DescribeAttackStatistics
newDescribeAttackStatistics :: DescribeAttackStatistics
newDescribeAttackStatistics =
DescribeAttackStatistics
DescribeAttackStatistics'
instance Core.AWSRequest DescribeAttackStatistics where
type
AWSResponse DescribeAttackStatistics =
DescribeAttackStatisticsResponse
request :: (Service -> Service)
-> DescribeAttackStatistics -> Request DescribeAttackStatistics
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 DescribeAttackStatistics
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DescribeAttackStatistics)))
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 ->
Int
-> TimeRange
-> [AttackStatisticsDataItem]
-> DescribeAttackStatisticsResponse
DescribeAttackStatisticsResponse'
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))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"TimeRange")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DataItems" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
)
instance Prelude.Hashable DescribeAttackStatistics where
hashWithSalt :: Int -> DescribeAttackStatistics -> Int
hashWithSalt Int
_salt DescribeAttackStatistics
_ =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()
instance Prelude.NFData DescribeAttackStatistics where
rnf :: DescribeAttackStatistics -> ()
rnf DescribeAttackStatistics
_ = ()
instance Data.ToHeaders DescribeAttackStatistics where
toHeaders :: DescribeAttackStatistics -> 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.DescribeAttackStatistics" ::
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 DescribeAttackStatistics where
toJSON :: DescribeAttackStatistics -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)
instance Data.ToPath DescribeAttackStatistics where
toPath :: DescribeAttackStatistics -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeAttackStatistics where
toQuery :: DescribeAttackStatistics -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DescribeAttackStatisticsResponse = DescribeAttackStatisticsResponse'
{
DescribeAttackStatisticsResponse -> Int
httpStatus :: Prelude.Int,
DescribeAttackStatisticsResponse -> TimeRange
timeRange :: TimeRange,
DescribeAttackStatisticsResponse -> [AttackStatisticsDataItem]
dataItems :: [AttackStatisticsDataItem]
}
deriving (DescribeAttackStatisticsResponse
-> DescribeAttackStatisticsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAttackStatisticsResponse
-> DescribeAttackStatisticsResponse -> Bool
$c/= :: DescribeAttackStatisticsResponse
-> DescribeAttackStatisticsResponse -> Bool
== :: DescribeAttackStatisticsResponse
-> DescribeAttackStatisticsResponse -> Bool
$c== :: DescribeAttackStatisticsResponse
-> DescribeAttackStatisticsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAttackStatisticsResponse]
ReadPrec DescribeAttackStatisticsResponse
Int -> ReadS DescribeAttackStatisticsResponse
ReadS [DescribeAttackStatisticsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAttackStatisticsResponse]
$creadListPrec :: ReadPrec [DescribeAttackStatisticsResponse]
readPrec :: ReadPrec DescribeAttackStatisticsResponse
$creadPrec :: ReadPrec DescribeAttackStatisticsResponse
readList :: ReadS [DescribeAttackStatisticsResponse]
$creadList :: ReadS [DescribeAttackStatisticsResponse]
readsPrec :: Int -> ReadS DescribeAttackStatisticsResponse
$creadsPrec :: Int -> ReadS DescribeAttackStatisticsResponse
Prelude.Read, Int -> DescribeAttackStatisticsResponse -> ShowS
[DescribeAttackStatisticsResponse] -> ShowS
DescribeAttackStatisticsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAttackStatisticsResponse] -> ShowS
$cshowList :: [DescribeAttackStatisticsResponse] -> ShowS
show :: DescribeAttackStatisticsResponse -> String
$cshow :: DescribeAttackStatisticsResponse -> String
showsPrec :: Int -> DescribeAttackStatisticsResponse -> ShowS
$cshowsPrec :: Int -> DescribeAttackStatisticsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAttackStatisticsResponse x
-> DescribeAttackStatisticsResponse
forall x.
DescribeAttackStatisticsResponse
-> Rep DescribeAttackStatisticsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAttackStatisticsResponse x
-> DescribeAttackStatisticsResponse
$cfrom :: forall x.
DescribeAttackStatisticsResponse
-> Rep DescribeAttackStatisticsResponse x
Prelude.Generic)
newDescribeAttackStatisticsResponse ::
Prelude.Int ->
TimeRange ->
DescribeAttackStatisticsResponse
newDescribeAttackStatisticsResponse :: Int -> TimeRange -> DescribeAttackStatisticsResponse
newDescribeAttackStatisticsResponse
Int
pHttpStatus_
TimeRange
pTimeRange_ =
DescribeAttackStatisticsResponse'
{ $sel:httpStatus:DescribeAttackStatisticsResponse' :: Int
httpStatus =
Int
pHttpStatus_,
$sel:timeRange:DescribeAttackStatisticsResponse' :: TimeRange
timeRange = TimeRange
pTimeRange_,
$sel:dataItems:DescribeAttackStatisticsResponse' :: [AttackStatisticsDataItem]
dataItems = forall a. Monoid a => a
Prelude.mempty
}
describeAttackStatisticsResponse_httpStatus :: Lens.Lens' DescribeAttackStatisticsResponse Prelude.Int
describeAttackStatisticsResponse_httpStatus :: Lens' DescribeAttackStatisticsResponse Int
describeAttackStatisticsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttackStatisticsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeAttackStatisticsResponse' :: DescribeAttackStatisticsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeAttackStatisticsResponse
s@DescribeAttackStatisticsResponse' {} Int
a -> DescribeAttackStatisticsResponse
s {$sel:httpStatus:DescribeAttackStatisticsResponse' :: Int
httpStatus = Int
a} :: DescribeAttackStatisticsResponse)
describeAttackStatisticsResponse_timeRange :: Lens.Lens' DescribeAttackStatisticsResponse TimeRange
describeAttackStatisticsResponse_timeRange :: Lens' DescribeAttackStatisticsResponse TimeRange
describeAttackStatisticsResponse_timeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttackStatisticsResponse' {TimeRange
timeRange :: TimeRange
$sel:timeRange:DescribeAttackStatisticsResponse' :: DescribeAttackStatisticsResponse -> TimeRange
timeRange} -> TimeRange
timeRange) (\s :: DescribeAttackStatisticsResponse
s@DescribeAttackStatisticsResponse' {} TimeRange
a -> DescribeAttackStatisticsResponse
s {$sel:timeRange:DescribeAttackStatisticsResponse' :: TimeRange
timeRange = TimeRange
a} :: DescribeAttackStatisticsResponse)
describeAttackStatisticsResponse_dataItems :: Lens.Lens' DescribeAttackStatisticsResponse [AttackStatisticsDataItem]
describeAttackStatisticsResponse_dataItems :: Lens' DescribeAttackStatisticsResponse [AttackStatisticsDataItem]
describeAttackStatisticsResponse_dataItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAttackStatisticsResponse' {[AttackStatisticsDataItem]
dataItems :: [AttackStatisticsDataItem]
$sel:dataItems:DescribeAttackStatisticsResponse' :: DescribeAttackStatisticsResponse -> [AttackStatisticsDataItem]
dataItems} -> [AttackStatisticsDataItem]
dataItems) (\s :: DescribeAttackStatisticsResponse
s@DescribeAttackStatisticsResponse' {} [AttackStatisticsDataItem]
a -> DescribeAttackStatisticsResponse
s {$sel:dataItems:DescribeAttackStatisticsResponse' :: [AttackStatisticsDataItem]
dataItems = [AttackStatisticsDataItem]
a} :: DescribeAttackStatisticsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
instance
Prelude.NFData
DescribeAttackStatisticsResponse
where
rnf :: DescribeAttackStatisticsResponse -> ()
rnf DescribeAttackStatisticsResponse' {Int
[AttackStatisticsDataItem]
TimeRange
dataItems :: [AttackStatisticsDataItem]
timeRange :: TimeRange
httpStatus :: Int
$sel:dataItems:DescribeAttackStatisticsResponse' :: DescribeAttackStatisticsResponse -> [AttackStatisticsDataItem]
$sel:timeRange:DescribeAttackStatisticsResponse' :: DescribeAttackStatisticsResponse -> TimeRange
$sel:httpStatus:DescribeAttackStatisticsResponse' :: DescribeAttackStatisticsResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TimeRange
timeRange
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [AttackStatisticsDataItem]
dataItems