{-# 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.LookoutMetrics.GetFeedback
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Get feedback for an anomaly group.
module Amazonka.LookoutMetrics.GetFeedback
  ( -- * Creating a Request
    GetFeedback (..),
    newGetFeedback,

    -- * Request Lenses
    getFeedback_maxResults,
    getFeedback_nextToken,
    getFeedback_anomalyDetectorArn,
    getFeedback_anomalyGroupTimeSeriesFeedback,

    -- * Destructuring the Response
    GetFeedbackResponse (..),
    newGetFeedbackResponse,

    -- * Response Lenses
    getFeedbackResponse_anomalyGroupTimeSeriesFeedback,
    getFeedbackResponse_nextToken,
    getFeedbackResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LookoutMetrics.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetFeedback' smart constructor.
data GetFeedback = GetFeedback'
  { -- | The maximum number of results to return.
    GetFeedback -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specify the pagination token that\'s returned by a previous request to
    -- retrieve the next page of results.
    GetFeedback -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the anomaly detector.
    GetFeedback -> Text
anomalyDetectorArn :: Prelude.Text,
    -- | The anomalous metric and group ID.
    GetFeedback -> AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback :: AnomalyGroupTimeSeries
  }
  deriving (GetFeedback -> GetFeedback -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFeedback -> GetFeedback -> Bool
$c/= :: GetFeedback -> GetFeedback -> Bool
== :: GetFeedback -> GetFeedback -> Bool
$c== :: GetFeedback -> GetFeedback -> Bool
Prelude.Eq, ReadPrec [GetFeedback]
ReadPrec GetFeedback
Int -> ReadS GetFeedback
ReadS [GetFeedback]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFeedback]
$creadListPrec :: ReadPrec [GetFeedback]
readPrec :: ReadPrec GetFeedback
$creadPrec :: ReadPrec GetFeedback
readList :: ReadS [GetFeedback]
$creadList :: ReadS [GetFeedback]
readsPrec :: Int -> ReadS GetFeedback
$creadsPrec :: Int -> ReadS GetFeedback
Prelude.Read, Int -> GetFeedback -> ShowS
[GetFeedback] -> ShowS
GetFeedback -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFeedback] -> ShowS
$cshowList :: [GetFeedback] -> ShowS
show :: GetFeedback -> String
$cshow :: GetFeedback -> String
showsPrec :: Int -> GetFeedback -> ShowS
$cshowsPrec :: Int -> GetFeedback -> ShowS
Prelude.Show, forall x. Rep GetFeedback x -> GetFeedback
forall x. GetFeedback -> Rep GetFeedback x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFeedback x -> GetFeedback
$cfrom :: forall x. GetFeedback -> Rep GetFeedback x
Prelude.Generic)

-- |
-- Create a value of 'GetFeedback' 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:
--
-- 'maxResults', 'getFeedback_maxResults' - The maximum number of results to return.
--
-- 'nextToken', 'getFeedback_nextToken' - Specify the pagination token that\'s returned by a previous request to
-- retrieve the next page of results.
--
-- 'anomalyDetectorArn', 'getFeedback_anomalyDetectorArn' - The Amazon Resource Name (ARN) of the anomaly detector.
--
-- 'anomalyGroupTimeSeriesFeedback', 'getFeedback_anomalyGroupTimeSeriesFeedback' - The anomalous metric and group ID.
newGetFeedback ::
  -- | 'anomalyDetectorArn'
  Prelude.Text ->
  -- | 'anomalyGroupTimeSeriesFeedback'
  AnomalyGroupTimeSeries ->
  GetFeedback
newGetFeedback :: Text -> AnomalyGroupTimeSeries -> GetFeedback
newGetFeedback
  Text
pAnomalyDetectorArn_
  AnomalyGroupTimeSeries
pAnomalyGroupTimeSeriesFeedback_ =
    GetFeedback'
      { $sel:maxResults:GetFeedback' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetFeedback' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:anomalyDetectorArn:GetFeedback' :: Text
anomalyDetectorArn = Text
pAnomalyDetectorArn_,
        $sel:anomalyGroupTimeSeriesFeedback:GetFeedback' :: AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback =
          AnomalyGroupTimeSeries
pAnomalyGroupTimeSeriesFeedback_
      }

-- | The maximum number of results to return.
getFeedback_maxResults :: Lens.Lens' GetFeedback (Prelude.Maybe Prelude.Natural)
getFeedback_maxResults :: Lens' GetFeedback (Maybe Natural)
getFeedback_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFeedback' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetFeedback' :: GetFeedback -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetFeedback
s@GetFeedback' {} Maybe Natural
a -> GetFeedback
s {$sel:maxResults:GetFeedback' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetFeedback)

-- | Specify the pagination token that\'s returned by a previous request to
-- retrieve the next page of results.
getFeedback_nextToken :: Lens.Lens' GetFeedback (Prelude.Maybe Prelude.Text)
getFeedback_nextToken :: Lens' GetFeedback (Maybe Text)
getFeedback_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFeedback' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetFeedback' :: GetFeedback -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetFeedback
s@GetFeedback' {} Maybe Text
a -> GetFeedback
s {$sel:nextToken:GetFeedback' :: Maybe Text
nextToken = Maybe Text
a} :: GetFeedback)

-- | The Amazon Resource Name (ARN) of the anomaly detector.
getFeedback_anomalyDetectorArn :: Lens.Lens' GetFeedback Prelude.Text
getFeedback_anomalyDetectorArn :: Lens' GetFeedback Text
getFeedback_anomalyDetectorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFeedback' {Text
anomalyDetectorArn :: Text
$sel:anomalyDetectorArn:GetFeedback' :: GetFeedback -> Text
anomalyDetectorArn} -> Text
anomalyDetectorArn) (\s :: GetFeedback
s@GetFeedback' {} Text
a -> GetFeedback
s {$sel:anomalyDetectorArn:GetFeedback' :: Text
anomalyDetectorArn = Text
a} :: GetFeedback)

-- | The anomalous metric and group ID.
getFeedback_anomalyGroupTimeSeriesFeedback :: Lens.Lens' GetFeedback AnomalyGroupTimeSeries
getFeedback_anomalyGroupTimeSeriesFeedback :: Lens' GetFeedback AnomalyGroupTimeSeries
getFeedback_anomalyGroupTimeSeriesFeedback = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFeedback' {AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback :: AnomalyGroupTimeSeries
$sel:anomalyGroupTimeSeriesFeedback:GetFeedback' :: GetFeedback -> AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback} -> AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback) (\s :: GetFeedback
s@GetFeedback' {} AnomalyGroupTimeSeries
a -> GetFeedback
s {$sel:anomalyGroupTimeSeriesFeedback:GetFeedback' :: AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback = AnomalyGroupTimeSeries
a} :: GetFeedback)

instance Core.AWSRequest GetFeedback where
  type AWSResponse GetFeedback = GetFeedbackResponse
  request :: (Service -> Service) -> GetFeedback -> Request GetFeedback
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 GetFeedback
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetFeedback)))
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 [TimeSeriesFeedback]
-> Maybe Text -> Int -> GetFeedbackResponse
GetFeedbackResponse'
            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
"AnomalyGroupTimeSeriesFeedback"
                            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 GetFeedback where
  hashWithSalt :: Int -> GetFeedback -> Int
hashWithSalt Int
_salt GetFeedback' {Maybe Natural
Maybe Text
Text
AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback :: AnomalyGroupTimeSeries
anomalyDetectorArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:anomalyGroupTimeSeriesFeedback:GetFeedback' :: GetFeedback -> AnomalyGroupTimeSeries
$sel:anomalyDetectorArn:GetFeedback' :: GetFeedback -> Text
$sel:nextToken:GetFeedback' :: GetFeedback -> Maybe Text
$sel:maxResults:GetFeedback' :: GetFeedback -> Maybe Natural
..} =
    Int
_salt
      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
anomalyDetectorArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback

instance Prelude.NFData GetFeedback where
  rnf :: GetFeedback -> ()
rnf GetFeedback' {Maybe Natural
Maybe Text
Text
AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback :: AnomalyGroupTimeSeries
anomalyDetectorArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:anomalyGroupTimeSeriesFeedback:GetFeedback' :: GetFeedback -> AnomalyGroupTimeSeries
$sel:anomalyDetectorArn:GetFeedback' :: GetFeedback -> Text
$sel:nextToken:GetFeedback' :: GetFeedback -> Maybe Text
$sel:maxResults:GetFeedback' :: GetFeedback -> Maybe Natural
..} =
    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
anomalyDetectorArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback

instance Data.ToHeaders GetFeedback where
  toHeaders :: GetFeedback -> 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 GetFeedback where
  toJSON :: GetFeedback -> Value
toJSON GetFeedback' {Maybe Natural
Maybe Text
Text
AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback :: AnomalyGroupTimeSeries
anomalyDetectorArn :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:anomalyGroupTimeSeriesFeedback:GetFeedback' :: GetFeedback -> AnomalyGroupTimeSeries
$sel:anomalyDetectorArn:GetFeedback' :: GetFeedback -> Text
$sel:nextToken:GetFeedback' :: GetFeedback -> Maybe Text
$sel:maxResults:GetFeedback' :: GetFeedback -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"AnomalyDetectorArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
anomalyDetectorArn),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"AnomalyGroupTimeSeriesFeedback"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AnomalyGroupTimeSeries
anomalyGroupTimeSeriesFeedback
              )
          ]
      )

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

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

-- | /See:/ 'newGetFeedbackResponse' smart constructor.
data GetFeedbackResponse = GetFeedbackResponse'
  { -- | Feedback for an anomalous metric.
    GetFeedbackResponse -> Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback :: Prelude.Maybe [TimeSeriesFeedback],
    -- | The pagination token that\'s included if more results are available.
    GetFeedbackResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetFeedbackResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetFeedbackResponse -> GetFeedbackResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFeedbackResponse -> GetFeedbackResponse -> Bool
$c/= :: GetFeedbackResponse -> GetFeedbackResponse -> Bool
== :: GetFeedbackResponse -> GetFeedbackResponse -> Bool
$c== :: GetFeedbackResponse -> GetFeedbackResponse -> Bool
Prelude.Eq, ReadPrec [GetFeedbackResponse]
ReadPrec GetFeedbackResponse
Int -> ReadS GetFeedbackResponse
ReadS [GetFeedbackResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFeedbackResponse]
$creadListPrec :: ReadPrec [GetFeedbackResponse]
readPrec :: ReadPrec GetFeedbackResponse
$creadPrec :: ReadPrec GetFeedbackResponse
readList :: ReadS [GetFeedbackResponse]
$creadList :: ReadS [GetFeedbackResponse]
readsPrec :: Int -> ReadS GetFeedbackResponse
$creadsPrec :: Int -> ReadS GetFeedbackResponse
Prelude.Read, Int -> GetFeedbackResponse -> ShowS
[GetFeedbackResponse] -> ShowS
GetFeedbackResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFeedbackResponse] -> ShowS
$cshowList :: [GetFeedbackResponse] -> ShowS
show :: GetFeedbackResponse -> String
$cshow :: GetFeedbackResponse -> String
showsPrec :: Int -> GetFeedbackResponse -> ShowS
$cshowsPrec :: Int -> GetFeedbackResponse -> ShowS
Prelude.Show, forall x. Rep GetFeedbackResponse x -> GetFeedbackResponse
forall x. GetFeedbackResponse -> Rep GetFeedbackResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFeedbackResponse x -> GetFeedbackResponse
$cfrom :: forall x. GetFeedbackResponse -> Rep GetFeedbackResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFeedbackResponse' 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:
--
-- 'anomalyGroupTimeSeriesFeedback', 'getFeedbackResponse_anomalyGroupTimeSeriesFeedback' - Feedback for an anomalous metric.
--
-- 'nextToken', 'getFeedbackResponse_nextToken' - The pagination token that\'s included if more results are available.
--
-- 'httpStatus', 'getFeedbackResponse_httpStatus' - The response's http status code.
newGetFeedbackResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFeedbackResponse
newGetFeedbackResponse :: Int -> GetFeedbackResponse
newGetFeedbackResponse Int
pHttpStatus_ =
  GetFeedbackResponse'
    { $sel:anomalyGroupTimeSeriesFeedback:GetFeedbackResponse' :: Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetFeedbackResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFeedbackResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Feedback for an anomalous metric.
getFeedbackResponse_anomalyGroupTimeSeriesFeedback :: Lens.Lens' GetFeedbackResponse (Prelude.Maybe [TimeSeriesFeedback])
getFeedbackResponse_anomalyGroupTimeSeriesFeedback :: Lens' GetFeedbackResponse (Maybe [TimeSeriesFeedback])
getFeedbackResponse_anomalyGroupTimeSeriesFeedback = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFeedbackResponse' {Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback :: Maybe [TimeSeriesFeedback]
$sel:anomalyGroupTimeSeriesFeedback:GetFeedbackResponse' :: GetFeedbackResponse -> Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback} -> Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback) (\s :: GetFeedbackResponse
s@GetFeedbackResponse' {} Maybe [TimeSeriesFeedback]
a -> GetFeedbackResponse
s {$sel:anomalyGroupTimeSeriesFeedback:GetFeedbackResponse' :: Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback = Maybe [TimeSeriesFeedback]
a} :: GetFeedbackResponse) 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

-- | The pagination token that\'s included if more results are available.
getFeedbackResponse_nextToken :: Lens.Lens' GetFeedbackResponse (Prelude.Maybe Prelude.Text)
getFeedbackResponse_nextToken :: Lens' GetFeedbackResponse (Maybe Text)
getFeedbackResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFeedbackResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetFeedbackResponse' :: GetFeedbackResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetFeedbackResponse
s@GetFeedbackResponse' {} Maybe Text
a -> GetFeedbackResponse
s {$sel:nextToken:GetFeedbackResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetFeedbackResponse)

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

instance Prelude.NFData GetFeedbackResponse where
  rnf :: GetFeedbackResponse -> ()
rnf GetFeedbackResponse' {Int
Maybe [TimeSeriesFeedback]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
anomalyGroupTimeSeriesFeedback :: Maybe [TimeSeriesFeedback]
$sel:httpStatus:GetFeedbackResponse' :: GetFeedbackResponse -> Int
$sel:nextToken:GetFeedbackResponse' :: GetFeedbackResponse -> Maybe Text
$sel:anomalyGroupTimeSeriesFeedback:GetFeedbackResponse' :: GetFeedbackResponse -> Maybe [TimeSeriesFeedback]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [TimeSeriesFeedback]
anomalyGroupTimeSeriesFeedback
      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