{-# 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.Connect.GetMetricData
(
GetMetricData (..),
newGetMetricData,
getMetricData_groupings,
getMetricData_maxResults,
getMetricData_nextToken,
getMetricData_instanceId,
getMetricData_startTime,
getMetricData_endTime,
getMetricData_filters,
getMetricData_historicalMetrics,
GetMetricDataResponse (..),
newGetMetricDataResponse,
getMetricDataResponse_metricResults,
getMetricDataResponse_nextToken,
getMetricDataResponse_httpStatus,
)
where
import Amazonka.Connect.Types
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
data GetMetricData = GetMetricData'
{
GetMetricData -> Maybe [Grouping]
groupings :: Prelude.Maybe [Grouping],
GetMetricData -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
GetMetricData -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
GetMetricData -> Text
instanceId :: Prelude.Text,
GetMetricData -> POSIX
startTime :: Data.POSIX,
GetMetricData -> POSIX
endTime :: Data.POSIX,
GetMetricData -> Filters
filters :: Filters,
GetMetricData -> [HistoricalMetric]
historicalMetrics :: [HistoricalMetric]
}
deriving (GetMetricData -> GetMetricData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMetricData -> GetMetricData -> Bool
$c/= :: GetMetricData -> GetMetricData -> Bool
== :: GetMetricData -> GetMetricData -> Bool
$c== :: GetMetricData -> GetMetricData -> Bool
Prelude.Eq, ReadPrec [GetMetricData]
ReadPrec GetMetricData
Int -> ReadS GetMetricData
ReadS [GetMetricData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMetricData]
$creadListPrec :: ReadPrec [GetMetricData]
readPrec :: ReadPrec GetMetricData
$creadPrec :: ReadPrec GetMetricData
readList :: ReadS [GetMetricData]
$creadList :: ReadS [GetMetricData]
readsPrec :: Int -> ReadS GetMetricData
$creadsPrec :: Int -> ReadS GetMetricData
Prelude.Read, Int -> GetMetricData -> ShowS
[GetMetricData] -> ShowS
GetMetricData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMetricData] -> ShowS
$cshowList :: [GetMetricData] -> ShowS
show :: GetMetricData -> String
$cshow :: GetMetricData -> String
showsPrec :: Int -> GetMetricData -> ShowS
$cshowsPrec :: Int -> GetMetricData -> ShowS
Prelude.Show, forall x. Rep GetMetricData x -> GetMetricData
forall x. GetMetricData -> Rep GetMetricData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMetricData x -> GetMetricData
$cfrom :: forall x. GetMetricData -> Rep GetMetricData x
Prelude.Generic)
newGetMetricData ::
Prelude.Text ->
Prelude.UTCTime ->
Prelude.UTCTime ->
Filters ->
GetMetricData
newGetMetricData :: Text -> UTCTime -> UTCTime -> Filters -> GetMetricData
newGetMetricData
Text
pInstanceId_
UTCTime
pStartTime_
UTCTime
pEndTime_
Filters
pFilters_ =
GetMetricData'
{ $sel:groupings:GetMetricData' :: Maybe [Grouping]
groupings = forall a. Maybe a
Prelude.Nothing,
$sel:maxResults:GetMetricData' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:GetMetricData' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:instanceId:GetMetricData' :: Text
instanceId = Text
pInstanceId_,
$sel:startTime:GetMetricData' :: POSIX
startTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pStartTime_,
$sel:endTime:GetMetricData' :: POSIX
endTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pEndTime_,
$sel:filters:GetMetricData' :: Filters
filters = Filters
pFilters_,
$sel:historicalMetrics:GetMetricData' :: [HistoricalMetric]
historicalMetrics = forall a. Monoid a => a
Prelude.mempty
}
getMetricData_groupings :: Lens.Lens' GetMetricData (Prelude.Maybe [Grouping])
getMetricData_groupings :: Lens' GetMetricData (Maybe [Grouping])
getMetricData_groupings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {Maybe [Grouping]
groupings :: Maybe [Grouping]
$sel:groupings:GetMetricData' :: GetMetricData -> Maybe [Grouping]
groupings} -> Maybe [Grouping]
groupings) (\s :: GetMetricData
s@GetMetricData' {} Maybe [Grouping]
a -> GetMetricData
s {$sel:groupings:GetMetricData' :: Maybe [Grouping]
groupings = Maybe [Grouping]
a} :: GetMetricData) 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
getMetricData_maxResults :: Lens.Lens' GetMetricData (Prelude.Maybe Prelude.Natural)
getMetricData_maxResults :: Lens' GetMetricData (Maybe Natural)
getMetricData_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetMetricData' :: GetMetricData -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetMetricData
s@GetMetricData' {} Maybe Natural
a -> GetMetricData
s {$sel:maxResults:GetMetricData' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetMetricData)
getMetricData_nextToken :: Lens.Lens' GetMetricData (Prelude.Maybe Prelude.Text)
getMetricData_nextToken :: Lens' GetMetricData (Maybe Text)
getMetricData_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetMetricData' :: GetMetricData -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetMetricData
s@GetMetricData' {} Maybe Text
a -> GetMetricData
s {$sel:nextToken:GetMetricData' :: Maybe Text
nextToken = Maybe Text
a} :: GetMetricData)
getMetricData_instanceId :: Lens.Lens' GetMetricData Prelude.Text
getMetricData_instanceId :: Lens' GetMetricData Text
getMetricData_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {Text
instanceId :: Text
$sel:instanceId:GetMetricData' :: GetMetricData -> Text
instanceId} -> Text
instanceId) (\s :: GetMetricData
s@GetMetricData' {} Text
a -> GetMetricData
s {$sel:instanceId:GetMetricData' :: Text
instanceId = Text
a} :: GetMetricData)
getMetricData_startTime :: Lens.Lens' GetMetricData Prelude.UTCTime
getMetricData_startTime :: Lens' GetMetricData UTCTime
getMetricData_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {POSIX
startTime :: POSIX
$sel:startTime:GetMetricData' :: GetMetricData -> POSIX
startTime} -> POSIX
startTime) (\s :: GetMetricData
s@GetMetricData' {} POSIX
a -> GetMetricData
s {$sel:startTime:GetMetricData' :: POSIX
startTime = POSIX
a} :: GetMetricData) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
getMetricData_endTime :: Lens.Lens' GetMetricData Prelude.UTCTime
getMetricData_endTime :: Lens' GetMetricData UTCTime
getMetricData_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {POSIX
endTime :: POSIX
$sel:endTime:GetMetricData' :: GetMetricData -> POSIX
endTime} -> POSIX
endTime) (\s :: GetMetricData
s@GetMetricData' {} POSIX
a -> GetMetricData
s {$sel:endTime:GetMetricData' :: POSIX
endTime = POSIX
a} :: GetMetricData) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
getMetricData_filters :: Lens.Lens' GetMetricData Filters
getMetricData_filters :: Lens' GetMetricData Filters
getMetricData_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {Filters
filters :: Filters
$sel:filters:GetMetricData' :: GetMetricData -> Filters
filters} -> Filters
filters) (\s :: GetMetricData
s@GetMetricData' {} Filters
a -> GetMetricData
s {$sel:filters:GetMetricData' :: Filters
filters = Filters
a} :: GetMetricData)
getMetricData_historicalMetrics :: Lens.Lens' GetMetricData [HistoricalMetric]
getMetricData_historicalMetrics :: Lens' GetMetricData [HistoricalMetric]
getMetricData_historicalMetrics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricData' {[HistoricalMetric]
historicalMetrics :: [HistoricalMetric]
$sel:historicalMetrics:GetMetricData' :: GetMetricData -> [HistoricalMetric]
historicalMetrics} -> [HistoricalMetric]
historicalMetrics) (\s :: GetMetricData
s@GetMetricData' {} [HistoricalMetric]
a -> GetMetricData
s {$sel:historicalMetrics:GetMetricData' :: [HistoricalMetric]
historicalMetrics = [HistoricalMetric]
a} :: GetMetricData) 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 Core.AWSPager GetMetricData where
page :: GetMetricData -> AWSResponse GetMetricData -> Maybe GetMetricData
page GetMetricData
rq AWSResponse GetMetricData
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse GetMetricData
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetMetricDataResponse (Maybe Text)
getMetricDataResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse GetMetricData
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetMetricDataResponse (Maybe [HistoricalMetricResult])
getMetricDataResponse_metricResults
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
) =
forall a. Maybe a
Prelude.Nothing
| Bool
Prelude.otherwise =
forall a. a -> Maybe a
Prelude.Just
forall a b. (a -> b) -> a -> b
Prelude.$ GetMetricData
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetMetricData (Maybe Text)
getMetricData_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetMetricData
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetMetricDataResponse (Maybe Text)
getMetricDataResponse_nextToken
forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
instance Core.AWSRequest GetMetricData where
type
AWSResponse GetMetricData =
GetMetricDataResponse
request :: (Service -> Service) -> GetMetricData -> Request GetMetricData
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 GetMetricData
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetMetricData)))
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 [HistoricalMetricResult]
-> Maybe Text -> Int -> GetMetricDataResponse
GetMetricDataResponse'
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
"MetricResults" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
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
"NextToken")
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 GetMetricData where
hashWithSalt :: Int -> GetMetricData -> Int
hashWithSalt Int
_salt GetMetricData' {[HistoricalMetric]
Maybe Natural
Maybe [Grouping]
Maybe Text
Text
POSIX
Filters
historicalMetrics :: [HistoricalMetric]
filters :: Filters
endTime :: POSIX
startTime :: POSIX
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupings :: Maybe [Grouping]
$sel:historicalMetrics:GetMetricData' :: GetMetricData -> [HistoricalMetric]
$sel:filters:GetMetricData' :: GetMetricData -> Filters
$sel:endTime:GetMetricData' :: GetMetricData -> POSIX
$sel:startTime:GetMetricData' :: GetMetricData -> POSIX
$sel:instanceId:GetMetricData' :: GetMetricData -> Text
$sel:nextToken:GetMetricData' :: GetMetricData -> Maybe Text
$sel:maxResults:GetMetricData' :: GetMetricData -> Maybe Natural
$sel:groupings:GetMetricData' :: GetMetricData -> Maybe [Grouping]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Grouping]
groupings
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
startTime
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
endTime
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Filters
filters
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [HistoricalMetric]
historicalMetrics
instance Prelude.NFData GetMetricData where
rnf :: GetMetricData -> ()
rnf GetMetricData' {[HistoricalMetric]
Maybe Natural
Maybe [Grouping]
Maybe Text
Text
POSIX
Filters
historicalMetrics :: [HistoricalMetric]
filters :: Filters
endTime :: POSIX
startTime :: POSIX
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupings :: Maybe [Grouping]
$sel:historicalMetrics:GetMetricData' :: GetMetricData -> [HistoricalMetric]
$sel:filters:GetMetricData' :: GetMetricData -> Filters
$sel:endTime:GetMetricData' :: GetMetricData -> POSIX
$sel:startTime:GetMetricData' :: GetMetricData -> POSIX
$sel:instanceId:GetMetricData' :: GetMetricData -> Text
$sel:nextToken:GetMetricData' :: GetMetricData -> Maybe Text
$sel:maxResults:GetMetricData' :: GetMetricData -> Maybe Natural
$sel:groupings:GetMetricData' :: GetMetricData -> Maybe [Grouping]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Grouping]
groupings
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
startTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
endTime
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Filters
filters
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [HistoricalMetric]
historicalMetrics
instance Data.ToHeaders GetMetricData where
toHeaders :: GetMetricData -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON GetMetricData where
toJSON :: GetMetricData -> Value
toJSON GetMetricData' {[HistoricalMetric]
Maybe Natural
Maybe [Grouping]
Maybe Text
Text
POSIX
Filters
historicalMetrics :: [HistoricalMetric]
filters :: Filters
endTime :: POSIX
startTime :: POSIX
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupings :: Maybe [Grouping]
$sel:historicalMetrics:GetMetricData' :: GetMetricData -> [HistoricalMetric]
$sel:filters:GetMetricData' :: GetMetricData -> Filters
$sel:endTime:GetMetricData' :: GetMetricData -> POSIX
$sel:startTime:GetMetricData' :: GetMetricData -> POSIX
$sel:instanceId:GetMetricData' :: GetMetricData -> Text
$sel:nextToken:GetMetricData' :: GetMetricData -> Maybe Text
$sel:maxResults:GetMetricData' :: GetMetricData -> Maybe Natural
$sel:groupings:GetMetricData' :: GetMetricData -> Maybe [Grouping]
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"Groupings" 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 [Grouping]
groupings,
(Key
"MaxResults" 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 Natural
maxResults,
(Key
"NextToken" 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 Text
nextToken,
forall a. a -> Maybe a
Prelude.Just (Key
"StartTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
startTime),
forall a. a -> Maybe a
Prelude.Just (Key
"EndTime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
endTime),
forall a. a -> Maybe a
Prelude.Just (Key
"Filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Filters
filters),
forall a. a -> Maybe a
Prelude.Just
(Key
"HistoricalMetrics" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [HistoricalMetric]
historicalMetrics)
]
)
instance Data.ToPath GetMetricData where
toPath :: GetMetricData -> ByteString
toPath GetMetricData' {[HistoricalMetric]
Maybe Natural
Maybe [Grouping]
Maybe Text
Text
POSIX
Filters
historicalMetrics :: [HistoricalMetric]
filters :: Filters
endTime :: POSIX
startTime :: POSIX
instanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
groupings :: Maybe [Grouping]
$sel:historicalMetrics:GetMetricData' :: GetMetricData -> [HistoricalMetric]
$sel:filters:GetMetricData' :: GetMetricData -> Filters
$sel:endTime:GetMetricData' :: GetMetricData -> POSIX
$sel:startTime:GetMetricData' :: GetMetricData -> POSIX
$sel:instanceId:GetMetricData' :: GetMetricData -> Text
$sel:nextToken:GetMetricData' :: GetMetricData -> Maybe Text
$sel:maxResults:GetMetricData' :: GetMetricData -> Maybe Natural
$sel:groupings:GetMetricData' :: GetMetricData -> Maybe [Grouping]
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ByteString
"/metrics/historical/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]
instance Data.ToQuery GetMetricData where
toQuery :: GetMetricData -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data GetMetricDataResponse = GetMetricDataResponse'
{
GetMetricDataResponse -> Maybe [HistoricalMetricResult]
metricResults :: Prelude.Maybe [HistoricalMetricResult],
GetMetricDataResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
GetMetricDataResponse -> Int
httpStatus :: Prelude.Int
}
deriving (GetMetricDataResponse -> GetMetricDataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMetricDataResponse -> GetMetricDataResponse -> Bool
$c/= :: GetMetricDataResponse -> GetMetricDataResponse -> Bool
== :: GetMetricDataResponse -> GetMetricDataResponse -> Bool
$c== :: GetMetricDataResponse -> GetMetricDataResponse -> Bool
Prelude.Eq, ReadPrec [GetMetricDataResponse]
ReadPrec GetMetricDataResponse
Int -> ReadS GetMetricDataResponse
ReadS [GetMetricDataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetMetricDataResponse]
$creadListPrec :: ReadPrec [GetMetricDataResponse]
readPrec :: ReadPrec GetMetricDataResponse
$creadPrec :: ReadPrec GetMetricDataResponse
readList :: ReadS [GetMetricDataResponse]
$creadList :: ReadS [GetMetricDataResponse]
readsPrec :: Int -> ReadS GetMetricDataResponse
$creadsPrec :: Int -> ReadS GetMetricDataResponse
Prelude.Read, Int -> GetMetricDataResponse -> ShowS
[GetMetricDataResponse] -> ShowS
GetMetricDataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMetricDataResponse] -> ShowS
$cshowList :: [GetMetricDataResponse] -> ShowS
show :: GetMetricDataResponse -> String
$cshow :: GetMetricDataResponse -> String
showsPrec :: Int -> GetMetricDataResponse -> ShowS
$cshowsPrec :: Int -> GetMetricDataResponse -> ShowS
Prelude.Show, forall x. Rep GetMetricDataResponse x -> GetMetricDataResponse
forall x. GetMetricDataResponse -> Rep GetMetricDataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMetricDataResponse x -> GetMetricDataResponse
$cfrom :: forall x. GetMetricDataResponse -> Rep GetMetricDataResponse x
Prelude.Generic)
newGetMetricDataResponse ::
Prelude.Int ->
GetMetricDataResponse
newGetMetricDataResponse :: Int -> GetMetricDataResponse
newGetMetricDataResponse Int
pHttpStatus_ =
GetMetricDataResponse'
{ $sel:metricResults:GetMetricDataResponse' :: Maybe [HistoricalMetricResult]
metricResults =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:GetMetricDataResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:GetMetricDataResponse' :: Int
httpStatus = Int
pHttpStatus_
}
getMetricDataResponse_metricResults :: Lens.Lens' GetMetricDataResponse (Prelude.Maybe [HistoricalMetricResult])
getMetricDataResponse_metricResults :: Lens' GetMetricDataResponse (Maybe [HistoricalMetricResult])
getMetricDataResponse_metricResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricDataResponse' {Maybe [HistoricalMetricResult]
metricResults :: Maybe [HistoricalMetricResult]
$sel:metricResults:GetMetricDataResponse' :: GetMetricDataResponse -> Maybe [HistoricalMetricResult]
metricResults} -> Maybe [HistoricalMetricResult]
metricResults) (\s :: GetMetricDataResponse
s@GetMetricDataResponse' {} Maybe [HistoricalMetricResult]
a -> GetMetricDataResponse
s {$sel:metricResults:GetMetricDataResponse' :: Maybe [HistoricalMetricResult]
metricResults = Maybe [HistoricalMetricResult]
a} :: GetMetricDataResponse) 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
getMetricDataResponse_nextToken :: Lens.Lens' GetMetricDataResponse (Prelude.Maybe Prelude.Text)
getMetricDataResponse_nextToken :: Lens' GetMetricDataResponse (Maybe Text)
getMetricDataResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricDataResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetMetricDataResponse' :: GetMetricDataResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetMetricDataResponse
s@GetMetricDataResponse' {} Maybe Text
a -> GetMetricDataResponse
s {$sel:nextToken:GetMetricDataResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetMetricDataResponse)
getMetricDataResponse_httpStatus :: Lens.Lens' GetMetricDataResponse Prelude.Int
getMetricDataResponse_httpStatus :: Lens' GetMetricDataResponse Int
getMetricDataResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetMetricDataResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetMetricDataResponse' :: GetMetricDataResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetMetricDataResponse
s@GetMetricDataResponse' {} Int
a -> GetMetricDataResponse
s {$sel:httpStatus:GetMetricDataResponse' :: Int
httpStatus = Int
a} :: GetMetricDataResponse)
instance Prelude.NFData GetMetricDataResponse where
rnf :: GetMetricDataResponse -> ()
rnf GetMetricDataResponse' {Int
Maybe [HistoricalMetricResult]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
metricResults :: Maybe [HistoricalMetricResult]
$sel:httpStatus:GetMetricDataResponse' :: GetMetricDataResponse -> Int
$sel:nextToken:GetMetricDataResponse' :: GetMetricDataResponse -> Maybe Text
$sel:metricResults:GetMetricDataResponse' :: GetMetricDataResponse -> Maybe [HistoricalMetricResult]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [HistoricalMetricResult]
metricResults
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus