{-# 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.Kendra.GetSnapshots
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves search metrics data. The data provides a snapshot of how your
-- users interact with your search application and how effective the
-- application is.
module Amazonka.Kendra.GetSnapshots
  ( -- * Creating a Request
    GetSnapshots (..),
    newGetSnapshots,

    -- * Request Lenses
    getSnapshots_maxResults,
    getSnapshots_nextToken,
    getSnapshots_indexId,
    getSnapshots_interval,
    getSnapshots_metricType,

    -- * Destructuring the Response
    GetSnapshotsResponse (..),
    newGetSnapshotsResponse,

    -- * Response Lenses
    getSnapshotsResponse_nextToken,
    getSnapshotsResponse_snapShotTimeFilter,
    getSnapshotsResponse_snapshotsData,
    getSnapshotsResponse_snapshotsDataHeader,
    getSnapshotsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetSnapshots' smart constructor.
data GetSnapshots = GetSnapshots'
  { -- | The maximum number of returned data for the metric.
    GetSnapshots -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | If the previous response was incomplete (because there is more data to
    -- retrieve), Amazon Kendra returns a pagination token in the response. You
    -- can use this pagination token to retrieve the next set of search metrics
    -- data.
    GetSnapshots -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the index to get search metrics data.
    GetSnapshots -> Text
indexId :: Prelude.Text,
    -- | The time interval or time window to get search metrics data. The time
    -- interval uses the time zone of your index. You can view data in the
    -- following time windows:
    --
    -- -   @THIS_WEEK@: The current week, starting on the Sunday and ending on
    --     the day before the current date.
    --
    -- -   @ONE_WEEK_AGO@: The previous week, starting on the Sunday and ending
    --     on the following Saturday.
    --
    -- -   @TWO_WEEKS_AGO@: The week before the previous week, starting on the
    --     Sunday and ending on the following Saturday.
    --
    -- -   @THIS_MONTH@: The current month, starting on the first day of the
    --     month and ending on the day before the current date.
    --
    -- -   @ONE_MONTH_AGO@: The previous month, starting on the first day of
    --     the month and ending on the last day of the month.
    --
    -- -   @TWO_MONTHS_AGO@: The month before the previous month, starting on
    --     the first day of the month and ending on last day of the month.
    GetSnapshots -> Interval
interval :: Interval,
    -- | The metric you want to retrieve. You can specify only one metric per
    -- call.
    --
    -- For more information about the metrics you can view, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/search-analytics.html Gaining insights with search analytics>.
    GetSnapshots -> MetricType
metricType :: MetricType
  }
  deriving (GetSnapshots -> GetSnapshots -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSnapshots -> GetSnapshots -> Bool
$c/= :: GetSnapshots -> GetSnapshots -> Bool
== :: GetSnapshots -> GetSnapshots -> Bool
$c== :: GetSnapshots -> GetSnapshots -> Bool
Prelude.Eq, ReadPrec [GetSnapshots]
ReadPrec GetSnapshots
Int -> ReadS GetSnapshots
ReadS [GetSnapshots]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSnapshots]
$creadListPrec :: ReadPrec [GetSnapshots]
readPrec :: ReadPrec GetSnapshots
$creadPrec :: ReadPrec GetSnapshots
readList :: ReadS [GetSnapshots]
$creadList :: ReadS [GetSnapshots]
readsPrec :: Int -> ReadS GetSnapshots
$creadsPrec :: Int -> ReadS GetSnapshots
Prelude.Read, Int -> GetSnapshots -> ShowS
[GetSnapshots] -> ShowS
GetSnapshots -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSnapshots] -> ShowS
$cshowList :: [GetSnapshots] -> ShowS
show :: GetSnapshots -> String
$cshow :: GetSnapshots -> String
showsPrec :: Int -> GetSnapshots -> ShowS
$cshowsPrec :: Int -> GetSnapshots -> ShowS
Prelude.Show, forall x. Rep GetSnapshots x -> GetSnapshots
forall x. GetSnapshots -> Rep GetSnapshots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSnapshots x -> GetSnapshots
$cfrom :: forall x. GetSnapshots -> Rep GetSnapshots x
Prelude.Generic)

-- |
-- Create a value of 'GetSnapshots' 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', 'getSnapshots_maxResults' - The maximum number of returned data for the metric.
--
-- 'nextToken', 'getSnapshots_nextToken' - If the previous response was incomplete (because there is more data to
-- retrieve), Amazon Kendra returns a pagination token in the response. You
-- can use this pagination token to retrieve the next set of search metrics
-- data.
--
-- 'indexId', 'getSnapshots_indexId' - The identifier of the index to get search metrics data.
--
-- 'interval', 'getSnapshots_interval' - The time interval or time window to get search metrics data. The time
-- interval uses the time zone of your index. You can view data in the
-- following time windows:
--
-- -   @THIS_WEEK@: The current week, starting on the Sunday and ending on
--     the day before the current date.
--
-- -   @ONE_WEEK_AGO@: The previous week, starting on the Sunday and ending
--     on the following Saturday.
--
-- -   @TWO_WEEKS_AGO@: The week before the previous week, starting on the
--     Sunday and ending on the following Saturday.
--
-- -   @THIS_MONTH@: The current month, starting on the first day of the
--     month and ending on the day before the current date.
--
-- -   @ONE_MONTH_AGO@: The previous month, starting on the first day of
--     the month and ending on the last day of the month.
--
-- -   @TWO_MONTHS_AGO@: The month before the previous month, starting on
--     the first day of the month and ending on last day of the month.
--
-- 'metricType', 'getSnapshots_metricType' - The metric you want to retrieve. You can specify only one metric per
-- call.
--
-- For more information about the metrics you can view, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/search-analytics.html Gaining insights with search analytics>.
newGetSnapshots ::
  -- | 'indexId'
  Prelude.Text ->
  -- | 'interval'
  Interval ->
  -- | 'metricType'
  MetricType ->
  GetSnapshots
newGetSnapshots :: Text -> Interval -> MetricType -> GetSnapshots
newGetSnapshots Text
pIndexId_ Interval
pInterval_ MetricType
pMetricType_ =
  GetSnapshots'
    { $sel:maxResults:GetSnapshots' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetSnapshots' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:indexId:GetSnapshots' :: Text
indexId = Text
pIndexId_,
      $sel:interval:GetSnapshots' :: Interval
interval = Interval
pInterval_,
      $sel:metricType:GetSnapshots' :: MetricType
metricType = MetricType
pMetricType_
    }

-- | The maximum number of returned data for the metric.
getSnapshots_maxResults :: Lens.Lens' GetSnapshots (Prelude.Maybe Prelude.Int)
getSnapshots_maxResults :: Lens' GetSnapshots (Maybe Int)
getSnapshots_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshots' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:GetSnapshots' :: GetSnapshots -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: GetSnapshots
s@GetSnapshots' {} Maybe Int
a -> GetSnapshots
s {$sel:maxResults:GetSnapshots' :: Maybe Int
maxResults = Maybe Int
a} :: GetSnapshots)

-- | If the previous response was incomplete (because there is more data to
-- retrieve), Amazon Kendra returns a pagination token in the response. You
-- can use this pagination token to retrieve the next set of search metrics
-- data.
getSnapshots_nextToken :: Lens.Lens' GetSnapshots (Prelude.Maybe Prelude.Text)
getSnapshots_nextToken :: Lens' GetSnapshots (Maybe Text)
getSnapshots_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshots' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetSnapshots' :: GetSnapshots -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetSnapshots
s@GetSnapshots' {} Maybe Text
a -> GetSnapshots
s {$sel:nextToken:GetSnapshots' :: Maybe Text
nextToken = Maybe Text
a} :: GetSnapshots)

-- | The identifier of the index to get search metrics data.
getSnapshots_indexId :: Lens.Lens' GetSnapshots Prelude.Text
getSnapshots_indexId :: Lens' GetSnapshots Text
getSnapshots_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshots' {Text
indexId :: Text
$sel:indexId:GetSnapshots' :: GetSnapshots -> Text
indexId} -> Text
indexId) (\s :: GetSnapshots
s@GetSnapshots' {} Text
a -> GetSnapshots
s {$sel:indexId:GetSnapshots' :: Text
indexId = Text
a} :: GetSnapshots)

-- | The time interval or time window to get search metrics data. The time
-- interval uses the time zone of your index. You can view data in the
-- following time windows:
--
-- -   @THIS_WEEK@: The current week, starting on the Sunday and ending on
--     the day before the current date.
--
-- -   @ONE_WEEK_AGO@: The previous week, starting on the Sunday and ending
--     on the following Saturday.
--
-- -   @TWO_WEEKS_AGO@: The week before the previous week, starting on the
--     Sunday and ending on the following Saturday.
--
-- -   @THIS_MONTH@: The current month, starting on the first day of the
--     month and ending on the day before the current date.
--
-- -   @ONE_MONTH_AGO@: The previous month, starting on the first day of
--     the month and ending on the last day of the month.
--
-- -   @TWO_MONTHS_AGO@: The month before the previous month, starting on
--     the first day of the month and ending on last day of the month.
getSnapshots_interval :: Lens.Lens' GetSnapshots Interval
getSnapshots_interval :: Lens' GetSnapshots Interval
getSnapshots_interval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshots' {Interval
interval :: Interval
$sel:interval:GetSnapshots' :: GetSnapshots -> Interval
interval} -> Interval
interval) (\s :: GetSnapshots
s@GetSnapshots' {} Interval
a -> GetSnapshots
s {$sel:interval:GetSnapshots' :: Interval
interval = Interval
a} :: GetSnapshots)

-- | The metric you want to retrieve. You can specify only one metric per
-- call.
--
-- For more information about the metrics you can view, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/search-analytics.html Gaining insights with search analytics>.
getSnapshots_metricType :: Lens.Lens' GetSnapshots MetricType
getSnapshots_metricType :: Lens' GetSnapshots MetricType
getSnapshots_metricType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshots' {MetricType
metricType :: MetricType
$sel:metricType:GetSnapshots' :: GetSnapshots -> MetricType
metricType} -> MetricType
metricType) (\s :: GetSnapshots
s@GetSnapshots' {} MetricType
a -> GetSnapshots
s {$sel:metricType:GetSnapshots' :: MetricType
metricType = MetricType
a} :: GetSnapshots)

instance Core.AWSRequest GetSnapshots where
  type AWSResponse GetSnapshots = GetSnapshotsResponse
  request :: (Service -> Service) -> GetSnapshots -> Request GetSnapshots
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 GetSnapshots
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSnapshots)))
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
-> Maybe TimeRange
-> Maybe [[Text]]
-> Maybe [Text]
-> Int
-> GetSnapshotsResponse
GetSnapshotsResponse'
            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
"NextToken")
            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
"SnapShotTimeFilter")
            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
"SnapshotsData" 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
"SnapshotsDataHeader"
                            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable GetSnapshots where
  hashWithSalt :: Int -> GetSnapshots -> Int
hashWithSalt Int
_salt GetSnapshots' {Maybe Int
Maybe Text
Text
Interval
MetricType
metricType :: MetricType
interval :: Interval
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:metricType:GetSnapshots' :: GetSnapshots -> MetricType
$sel:interval:GetSnapshots' :: GetSnapshots -> Interval
$sel:indexId:GetSnapshots' :: GetSnapshots -> Text
$sel:nextToken:GetSnapshots' :: GetSnapshots -> Maybe Text
$sel:maxResults:GetSnapshots' :: GetSnapshots -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Interval
interval
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MetricType
metricType

instance Prelude.NFData GetSnapshots where
  rnf :: GetSnapshots -> ()
rnf GetSnapshots' {Maybe Int
Maybe Text
Text
Interval
MetricType
metricType :: MetricType
interval :: Interval
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:metricType:GetSnapshots' :: GetSnapshots -> MetricType
$sel:interval:GetSnapshots' :: GetSnapshots -> Interval
$sel:indexId:GetSnapshots' :: GetSnapshots -> Text
$sel:nextToken:GetSnapshots' :: GetSnapshots -> Maybe Text
$sel:maxResults:GetSnapshots' :: GetSnapshots -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
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
indexId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Interval
interval
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MetricType
metricType

instance Data.ToHeaders GetSnapshots where
  toHeaders :: GetSnapshots -> 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
"AWSKendraFrontendService.GetSnapshots" ::
                          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 GetSnapshots where
  toJSON :: GetSnapshots -> Value
toJSON GetSnapshots' {Maybe Int
Maybe Text
Text
Interval
MetricType
metricType :: MetricType
interval :: Interval
indexId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Int
$sel:metricType:GetSnapshots' :: GetSnapshots -> MetricType
$sel:interval:GetSnapshots' :: GetSnapshots -> Interval
$sel:indexId:GetSnapshots' :: GetSnapshots -> Text
$sel:nextToken:GetSnapshots' :: GetSnapshots -> Maybe Text
$sel:maxResults:GetSnapshots' :: GetSnapshots -> Maybe Int
..} =
    [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 Int
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
"IndexId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
indexId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Interval" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Interval
interval),
            forall a. a -> Maybe a
Prelude.Just (Key
"MetricType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= MetricType
metricType)
          ]
      )

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

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

-- | /See:/ 'newGetSnapshotsResponse' smart constructor.
data GetSnapshotsResponse = GetSnapshotsResponse'
  { -- | If the response is truncated, Amazon Kendra returns this token, which
    -- you can use in a later request to retrieve the next set of search
    -- metrics data.
    GetSnapshotsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The date-time for the beginning and end of the time window for the
    -- search metrics data.
    GetSnapshotsResponse -> Maybe TimeRange
snapShotTimeFilter :: Prelude.Maybe TimeRange,
    -- | The search metrics data. The data returned depends on the metric type
    -- you requested.
    GetSnapshotsResponse -> Maybe [[Text]]
snapshotsData :: Prelude.Maybe [[Prelude.Text]],
    -- | The column headers for the search metrics data.
    GetSnapshotsResponse -> Maybe [Text]
snapshotsDataHeader :: Prelude.Maybe [Prelude.Text],
    -- | The response's http status code.
    GetSnapshotsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSnapshotsResponse -> GetSnapshotsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSnapshotsResponse -> GetSnapshotsResponse -> Bool
$c/= :: GetSnapshotsResponse -> GetSnapshotsResponse -> Bool
== :: GetSnapshotsResponse -> GetSnapshotsResponse -> Bool
$c== :: GetSnapshotsResponse -> GetSnapshotsResponse -> Bool
Prelude.Eq, ReadPrec [GetSnapshotsResponse]
ReadPrec GetSnapshotsResponse
Int -> ReadS GetSnapshotsResponse
ReadS [GetSnapshotsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSnapshotsResponse]
$creadListPrec :: ReadPrec [GetSnapshotsResponse]
readPrec :: ReadPrec GetSnapshotsResponse
$creadPrec :: ReadPrec GetSnapshotsResponse
readList :: ReadS [GetSnapshotsResponse]
$creadList :: ReadS [GetSnapshotsResponse]
readsPrec :: Int -> ReadS GetSnapshotsResponse
$creadsPrec :: Int -> ReadS GetSnapshotsResponse
Prelude.Read, Int -> GetSnapshotsResponse -> ShowS
[GetSnapshotsResponse] -> ShowS
GetSnapshotsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSnapshotsResponse] -> ShowS
$cshowList :: [GetSnapshotsResponse] -> ShowS
show :: GetSnapshotsResponse -> String
$cshow :: GetSnapshotsResponse -> String
showsPrec :: Int -> GetSnapshotsResponse -> ShowS
$cshowsPrec :: Int -> GetSnapshotsResponse -> ShowS
Prelude.Show, forall x. Rep GetSnapshotsResponse x -> GetSnapshotsResponse
forall x. GetSnapshotsResponse -> Rep GetSnapshotsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSnapshotsResponse x -> GetSnapshotsResponse
$cfrom :: forall x. GetSnapshotsResponse -> Rep GetSnapshotsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSnapshotsResponse' 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:
--
-- 'nextToken', 'getSnapshotsResponse_nextToken' - If the response is truncated, Amazon Kendra returns this token, which
-- you can use in a later request to retrieve the next set of search
-- metrics data.
--
-- 'snapShotTimeFilter', 'getSnapshotsResponse_snapShotTimeFilter' - The date-time for the beginning and end of the time window for the
-- search metrics data.
--
-- 'snapshotsData', 'getSnapshotsResponse_snapshotsData' - The search metrics data. The data returned depends on the metric type
-- you requested.
--
-- 'snapshotsDataHeader', 'getSnapshotsResponse_snapshotsDataHeader' - The column headers for the search metrics data.
--
-- 'httpStatus', 'getSnapshotsResponse_httpStatus' - The response's http status code.
newGetSnapshotsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSnapshotsResponse
newGetSnapshotsResponse :: Int -> GetSnapshotsResponse
newGetSnapshotsResponse Int
pHttpStatus_ =
  GetSnapshotsResponse'
    { $sel:nextToken:GetSnapshotsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:snapShotTimeFilter:GetSnapshotsResponse' :: Maybe TimeRange
snapShotTimeFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotsData:GetSnapshotsResponse' :: Maybe [[Text]]
snapshotsData = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotsDataHeader:GetSnapshotsResponse' :: Maybe [Text]
snapshotsDataHeader = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSnapshotsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If the response is truncated, Amazon Kendra returns this token, which
-- you can use in a later request to retrieve the next set of search
-- metrics data.
getSnapshotsResponse_nextToken :: Lens.Lens' GetSnapshotsResponse (Prelude.Maybe Prelude.Text)
getSnapshotsResponse_nextToken :: Lens' GetSnapshotsResponse (Maybe Text)
getSnapshotsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshotsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetSnapshotsResponse
s@GetSnapshotsResponse' {} Maybe Text
a -> GetSnapshotsResponse
s {$sel:nextToken:GetSnapshotsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetSnapshotsResponse)

-- | The date-time for the beginning and end of the time window for the
-- search metrics data.
getSnapshotsResponse_snapShotTimeFilter :: Lens.Lens' GetSnapshotsResponse (Prelude.Maybe TimeRange)
getSnapshotsResponse_snapShotTimeFilter :: Lens' GetSnapshotsResponse (Maybe TimeRange)
getSnapshotsResponse_snapShotTimeFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshotsResponse' {Maybe TimeRange
snapShotTimeFilter :: Maybe TimeRange
$sel:snapShotTimeFilter:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe TimeRange
snapShotTimeFilter} -> Maybe TimeRange
snapShotTimeFilter) (\s :: GetSnapshotsResponse
s@GetSnapshotsResponse' {} Maybe TimeRange
a -> GetSnapshotsResponse
s {$sel:snapShotTimeFilter:GetSnapshotsResponse' :: Maybe TimeRange
snapShotTimeFilter = Maybe TimeRange
a} :: GetSnapshotsResponse)

-- | The search metrics data. The data returned depends on the metric type
-- you requested.
getSnapshotsResponse_snapshotsData :: Lens.Lens' GetSnapshotsResponse (Prelude.Maybe [[Prelude.Text]])
getSnapshotsResponse_snapshotsData :: Lens' GetSnapshotsResponse (Maybe [[Text]])
getSnapshotsResponse_snapshotsData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshotsResponse' {Maybe [[Text]]
snapshotsData :: Maybe [[Text]]
$sel:snapshotsData:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe [[Text]]
snapshotsData} -> Maybe [[Text]]
snapshotsData) (\s :: GetSnapshotsResponse
s@GetSnapshotsResponse' {} Maybe [[Text]]
a -> GetSnapshotsResponse
s {$sel:snapshotsData:GetSnapshotsResponse' :: Maybe [[Text]]
snapshotsData = Maybe [[Text]]
a} :: GetSnapshotsResponse) 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 column headers for the search metrics data.
getSnapshotsResponse_snapshotsDataHeader :: Lens.Lens' GetSnapshotsResponse (Prelude.Maybe [Prelude.Text])
getSnapshotsResponse_snapshotsDataHeader :: Lens' GetSnapshotsResponse (Maybe [Text])
getSnapshotsResponse_snapshotsDataHeader = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshotsResponse' {Maybe [Text]
snapshotsDataHeader :: Maybe [Text]
$sel:snapshotsDataHeader:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe [Text]
snapshotsDataHeader} -> Maybe [Text]
snapshotsDataHeader) (\s :: GetSnapshotsResponse
s@GetSnapshotsResponse' {} Maybe [Text]
a -> GetSnapshotsResponse
s {$sel:snapshotsDataHeader:GetSnapshotsResponse' :: Maybe [Text]
snapshotsDataHeader = Maybe [Text]
a} :: GetSnapshotsResponse) 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 response's http status code.
getSnapshotsResponse_httpStatus :: Lens.Lens' GetSnapshotsResponse Prelude.Int
getSnapshotsResponse_httpStatus :: Lens' GetSnapshotsResponse Int
getSnapshotsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSnapshotsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetSnapshotsResponse' :: GetSnapshotsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetSnapshotsResponse
s@GetSnapshotsResponse' {} Int
a -> GetSnapshotsResponse
s {$sel:httpStatus:GetSnapshotsResponse' :: Int
httpStatus = Int
a} :: GetSnapshotsResponse)

instance Prelude.NFData GetSnapshotsResponse where
  rnf :: GetSnapshotsResponse -> ()
rnf GetSnapshotsResponse' {Int
Maybe [[Text]]
Maybe [Text]
Maybe Text
Maybe TimeRange
httpStatus :: Int
snapshotsDataHeader :: Maybe [Text]
snapshotsData :: Maybe [[Text]]
snapShotTimeFilter :: Maybe TimeRange
nextToken :: Maybe Text
$sel:httpStatus:GetSnapshotsResponse' :: GetSnapshotsResponse -> Int
$sel:snapshotsDataHeader:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe [Text]
$sel:snapshotsData:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe [[Text]]
$sel:snapShotTimeFilter:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe TimeRange
$sel:nextToken:GetSnapshotsResponse' :: GetSnapshotsResponse -> Maybe Text
..} =
    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 Maybe TimeRange
snapShotTimeFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [[Text]]
snapshotsData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
snapshotsDataHeader
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus