{-# 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.Inspector2.ListCoverageStatistics
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists Amazon Inspector coverage statistics for your environment.
--
-- This operation returns paginated results.
module Amazonka.Inspector2.ListCoverageStatistics
  ( -- * Creating a Request
    ListCoverageStatistics (..),
    newListCoverageStatistics,

    -- * Request Lenses
    listCoverageStatistics_filterCriteria,
    listCoverageStatistics_groupBy,
    listCoverageStatistics_nextToken,

    -- * Destructuring the Response
    ListCoverageStatisticsResponse (..),
    newListCoverageStatisticsResponse,

    -- * Response Lenses
    listCoverageStatisticsResponse_countsByGroup,
    listCoverageStatisticsResponse_nextToken,
    listCoverageStatisticsResponse_httpStatus,
    listCoverageStatisticsResponse_totalCounts,
  )
where

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

-- | /See:/ 'newListCoverageStatistics' smart constructor.
data ListCoverageStatistics = ListCoverageStatistics'
  { -- | An object that contains details on the filters to apply to the coverage
    -- data for your environment.
    ListCoverageStatistics -> Maybe CoverageFilterCriteria
filterCriteria :: Prelude.Maybe CoverageFilterCriteria,
    -- | The value to group the results by.
    ListCoverageStatistics -> Maybe GroupKey
groupBy :: Prelude.Maybe GroupKey,
    -- | A token to use for paginating results that are returned in the response.
    -- Set the value of this parameter to null for the first request to a list
    -- action. For subsequent calls, use the @NextToken@ value returned from
    -- the previous request to continue listing results after the first page.
    ListCoverageStatistics -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListCoverageStatistics -> ListCoverageStatistics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCoverageStatistics -> ListCoverageStatistics -> Bool
$c/= :: ListCoverageStatistics -> ListCoverageStatistics -> Bool
== :: ListCoverageStatistics -> ListCoverageStatistics -> Bool
$c== :: ListCoverageStatistics -> ListCoverageStatistics -> Bool
Prelude.Eq, ReadPrec [ListCoverageStatistics]
ReadPrec ListCoverageStatistics
Int -> ReadS ListCoverageStatistics
ReadS [ListCoverageStatistics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCoverageStatistics]
$creadListPrec :: ReadPrec [ListCoverageStatistics]
readPrec :: ReadPrec ListCoverageStatistics
$creadPrec :: ReadPrec ListCoverageStatistics
readList :: ReadS [ListCoverageStatistics]
$creadList :: ReadS [ListCoverageStatistics]
readsPrec :: Int -> ReadS ListCoverageStatistics
$creadsPrec :: Int -> ReadS ListCoverageStatistics
Prelude.Read, Int -> ListCoverageStatistics -> ShowS
[ListCoverageStatistics] -> ShowS
ListCoverageStatistics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCoverageStatistics] -> ShowS
$cshowList :: [ListCoverageStatistics] -> ShowS
show :: ListCoverageStatistics -> String
$cshow :: ListCoverageStatistics -> String
showsPrec :: Int -> ListCoverageStatistics -> ShowS
$cshowsPrec :: Int -> ListCoverageStatistics -> ShowS
Prelude.Show, forall x. Rep ListCoverageStatistics x -> ListCoverageStatistics
forall x. ListCoverageStatistics -> Rep ListCoverageStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCoverageStatistics x -> ListCoverageStatistics
$cfrom :: forall x. ListCoverageStatistics -> Rep ListCoverageStatistics x
Prelude.Generic)

-- |
-- Create a value of 'ListCoverageStatistics' 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:
--
-- 'filterCriteria', 'listCoverageStatistics_filterCriteria' - An object that contains details on the filters to apply to the coverage
-- data for your environment.
--
-- 'groupBy', 'listCoverageStatistics_groupBy' - The value to group the results by.
--
-- 'nextToken', 'listCoverageStatistics_nextToken' - A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
newListCoverageStatistics ::
  ListCoverageStatistics
newListCoverageStatistics :: ListCoverageStatistics
newListCoverageStatistics =
  ListCoverageStatistics'
    { $sel:filterCriteria:ListCoverageStatistics' :: Maybe CoverageFilterCriteria
filterCriteria =
        forall a. Maybe a
Prelude.Nothing,
      $sel:groupBy:ListCoverageStatistics' :: Maybe GroupKey
groupBy = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCoverageStatistics' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | An object that contains details on the filters to apply to the coverage
-- data for your environment.
listCoverageStatistics_filterCriteria :: Lens.Lens' ListCoverageStatistics (Prelude.Maybe CoverageFilterCriteria)
listCoverageStatistics_filterCriteria :: Lens' ListCoverageStatistics (Maybe CoverageFilterCriteria)
listCoverageStatistics_filterCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCoverageStatistics' {Maybe CoverageFilterCriteria
filterCriteria :: Maybe CoverageFilterCriteria
$sel:filterCriteria:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe CoverageFilterCriteria
filterCriteria} -> Maybe CoverageFilterCriteria
filterCriteria) (\s :: ListCoverageStatistics
s@ListCoverageStatistics' {} Maybe CoverageFilterCriteria
a -> ListCoverageStatistics
s {$sel:filterCriteria:ListCoverageStatistics' :: Maybe CoverageFilterCriteria
filterCriteria = Maybe CoverageFilterCriteria
a} :: ListCoverageStatistics)

-- | The value to group the results by.
listCoverageStatistics_groupBy :: Lens.Lens' ListCoverageStatistics (Prelude.Maybe GroupKey)
listCoverageStatistics_groupBy :: Lens' ListCoverageStatistics (Maybe GroupKey)
listCoverageStatistics_groupBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCoverageStatistics' {Maybe GroupKey
groupBy :: Maybe GroupKey
$sel:groupBy:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe GroupKey
groupBy} -> Maybe GroupKey
groupBy) (\s :: ListCoverageStatistics
s@ListCoverageStatistics' {} Maybe GroupKey
a -> ListCoverageStatistics
s {$sel:groupBy:ListCoverageStatistics' :: Maybe GroupKey
groupBy = Maybe GroupKey
a} :: ListCoverageStatistics)

-- | A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
listCoverageStatistics_nextToken :: Lens.Lens' ListCoverageStatistics (Prelude.Maybe Prelude.Text)
listCoverageStatistics_nextToken :: Lens' ListCoverageStatistics (Maybe Text)
listCoverageStatistics_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCoverageStatistics' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCoverageStatistics
s@ListCoverageStatistics' {} Maybe Text
a -> ListCoverageStatistics
s {$sel:nextToken:ListCoverageStatistics' :: Maybe Text
nextToken = Maybe Text
a} :: ListCoverageStatistics)

instance Core.AWSPager ListCoverageStatistics where
  page :: ListCoverageStatistics
-> AWSResponse ListCoverageStatistics
-> Maybe ListCoverageStatistics
page ListCoverageStatistics
rq AWSResponse ListCoverageStatistics
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCoverageStatistics
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCoverageStatisticsResponse (Maybe Text)
listCoverageStatisticsResponse_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 ListCoverageStatistics
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCoverageStatisticsResponse (Maybe (NonEmpty Counts))
listCoverageStatisticsResponse_countsByGroup
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall l. IsList l => l -> [Item l]
Prelude.toList
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListCoverageStatistics
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListCoverageStatistics (Maybe Text)
listCoverageStatistics_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListCoverageStatistics
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCoverageStatisticsResponse (Maybe Text)
listCoverageStatisticsResponse_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 ListCoverageStatistics where
  type
    AWSResponse ListCoverageStatistics =
      ListCoverageStatisticsResponse
  request :: (Service -> Service)
-> ListCoverageStatistics -> Request ListCoverageStatistics
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 ListCoverageStatistics
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListCoverageStatistics)))
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 (NonEmpty Counts)
-> Maybe Text -> Int -> Integer -> ListCoverageStatisticsResponse
ListCoverageStatisticsResponse'
            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
"countsByGroup")
            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))
            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
"totalCounts")
      )

instance Prelude.Hashable ListCoverageStatistics where
  hashWithSalt :: Int -> ListCoverageStatistics -> Int
hashWithSalt Int
_salt ListCoverageStatistics' {Maybe Text
Maybe CoverageFilterCriteria
Maybe GroupKey
nextToken :: Maybe Text
groupBy :: Maybe GroupKey
filterCriteria :: Maybe CoverageFilterCriteria
$sel:nextToken:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe Text
$sel:groupBy:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe GroupKey
$sel:filterCriteria:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe CoverageFilterCriteria
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CoverageFilterCriteria
filterCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe GroupKey
groupBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListCoverageStatistics where
  rnf :: ListCoverageStatistics -> ()
rnf ListCoverageStatistics' {Maybe Text
Maybe CoverageFilterCriteria
Maybe GroupKey
nextToken :: Maybe Text
groupBy :: Maybe GroupKey
filterCriteria :: Maybe CoverageFilterCriteria
$sel:nextToken:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe Text
$sel:groupBy:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe GroupKey
$sel:filterCriteria:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe CoverageFilterCriteria
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CoverageFilterCriteria
filterCriteria
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe GroupKey
groupBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListCoverageStatistics where
  toHeaders :: ListCoverageStatistics -> 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 ListCoverageStatistics where
  toJSON :: ListCoverageStatistics -> Value
toJSON ListCoverageStatistics' {Maybe Text
Maybe CoverageFilterCriteria
Maybe GroupKey
nextToken :: Maybe Text
groupBy :: Maybe GroupKey
filterCriteria :: Maybe CoverageFilterCriteria
$sel:nextToken:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe Text
$sel:groupBy:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe GroupKey
$sel:filterCriteria:ListCoverageStatistics' :: ListCoverageStatistics -> Maybe CoverageFilterCriteria
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"filterCriteria" 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 CoverageFilterCriteria
filterCriteria,
            (Key
"groupBy" 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 GroupKey
groupBy,
            (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
          ]
      )

instance Data.ToPath ListCoverageStatistics where
  toPath :: ListCoverageStatistics -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/coverage/statistics/list"

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

-- | /See:/ 'newListCoverageStatisticsResponse' smart constructor.
data ListCoverageStatisticsResponse = ListCoverageStatisticsResponse'
  { -- | An array with the number for each group.
    ListCoverageStatisticsResponse -> Maybe (NonEmpty Counts)
countsByGroup :: Prelude.Maybe (Prelude.NonEmpty Counts),
    -- | A token to use for paginating results that are returned in the response.
    -- Set the value of this parameter to null for the first request to a list
    -- action. For subsequent calls, use the @NextToken@ value returned from
    -- the previous request to continue listing results after the first page.
    ListCoverageStatisticsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCoverageStatisticsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The total number for all groups.
    ListCoverageStatisticsResponse -> Integer
totalCounts :: Prelude.Integer
  }
  deriving (ListCoverageStatisticsResponse
-> ListCoverageStatisticsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCoverageStatisticsResponse
-> ListCoverageStatisticsResponse -> Bool
$c/= :: ListCoverageStatisticsResponse
-> ListCoverageStatisticsResponse -> Bool
== :: ListCoverageStatisticsResponse
-> ListCoverageStatisticsResponse -> Bool
$c== :: ListCoverageStatisticsResponse
-> ListCoverageStatisticsResponse -> Bool
Prelude.Eq, ReadPrec [ListCoverageStatisticsResponse]
ReadPrec ListCoverageStatisticsResponse
Int -> ReadS ListCoverageStatisticsResponse
ReadS [ListCoverageStatisticsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCoverageStatisticsResponse]
$creadListPrec :: ReadPrec [ListCoverageStatisticsResponse]
readPrec :: ReadPrec ListCoverageStatisticsResponse
$creadPrec :: ReadPrec ListCoverageStatisticsResponse
readList :: ReadS [ListCoverageStatisticsResponse]
$creadList :: ReadS [ListCoverageStatisticsResponse]
readsPrec :: Int -> ReadS ListCoverageStatisticsResponse
$creadsPrec :: Int -> ReadS ListCoverageStatisticsResponse
Prelude.Read, Int -> ListCoverageStatisticsResponse -> ShowS
[ListCoverageStatisticsResponse] -> ShowS
ListCoverageStatisticsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCoverageStatisticsResponse] -> ShowS
$cshowList :: [ListCoverageStatisticsResponse] -> ShowS
show :: ListCoverageStatisticsResponse -> String
$cshow :: ListCoverageStatisticsResponse -> String
showsPrec :: Int -> ListCoverageStatisticsResponse -> ShowS
$cshowsPrec :: Int -> ListCoverageStatisticsResponse -> ShowS
Prelude.Show, forall x.
Rep ListCoverageStatisticsResponse x
-> ListCoverageStatisticsResponse
forall x.
ListCoverageStatisticsResponse
-> Rep ListCoverageStatisticsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListCoverageStatisticsResponse x
-> ListCoverageStatisticsResponse
$cfrom :: forall x.
ListCoverageStatisticsResponse
-> Rep ListCoverageStatisticsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCoverageStatisticsResponse' 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:
--
-- 'countsByGroup', 'listCoverageStatisticsResponse_countsByGroup' - An array with the number for each group.
--
-- 'nextToken', 'listCoverageStatisticsResponse_nextToken' - A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
--
-- 'httpStatus', 'listCoverageStatisticsResponse_httpStatus' - The response's http status code.
--
-- 'totalCounts', 'listCoverageStatisticsResponse_totalCounts' - The total number for all groups.
newListCoverageStatisticsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'totalCounts'
  Prelude.Integer ->
  ListCoverageStatisticsResponse
newListCoverageStatisticsResponse :: Int -> Integer -> ListCoverageStatisticsResponse
newListCoverageStatisticsResponse
  Int
pHttpStatus_
  Integer
pTotalCounts_ =
    ListCoverageStatisticsResponse'
      { $sel:countsByGroup:ListCoverageStatisticsResponse' :: Maybe (NonEmpty Counts)
countsByGroup =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListCoverageStatisticsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListCoverageStatisticsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:totalCounts:ListCoverageStatisticsResponse' :: Integer
totalCounts = Integer
pTotalCounts_
      }

-- | An array with the number for each group.
listCoverageStatisticsResponse_countsByGroup :: Lens.Lens' ListCoverageStatisticsResponse (Prelude.Maybe (Prelude.NonEmpty Counts))
listCoverageStatisticsResponse_countsByGroup :: Lens' ListCoverageStatisticsResponse (Maybe (NonEmpty Counts))
listCoverageStatisticsResponse_countsByGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCoverageStatisticsResponse' {Maybe (NonEmpty Counts)
countsByGroup :: Maybe (NonEmpty Counts)
$sel:countsByGroup:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Maybe (NonEmpty Counts)
countsByGroup} -> Maybe (NonEmpty Counts)
countsByGroup) (\s :: ListCoverageStatisticsResponse
s@ListCoverageStatisticsResponse' {} Maybe (NonEmpty Counts)
a -> ListCoverageStatisticsResponse
s {$sel:countsByGroup:ListCoverageStatisticsResponse' :: Maybe (NonEmpty Counts)
countsByGroup = Maybe (NonEmpty Counts)
a} :: ListCoverageStatisticsResponse) 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

-- | A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
listCoverageStatisticsResponse_nextToken :: Lens.Lens' ListCoverageStatisticsResponse (Prelude.Maybe Prelude.Text)
listCoverageStatisticsResponse_nextToken :: Lens' ListCoverageStatisticsResponse (Maybe Text)
listCoverageStatisticsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCoverageStatisticsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCoverageStatisticsResponse
s@ListCoverageStatisticsResponse' {} Maybe Text
a -> ListCoverageStatisticsResponse
s {$sel:nextToken:ListCoverageStatisticsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListCoverageStatisticsResponse)

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

-- | The total number for all groups.
listCoverageStatisticsResponse_totalCounts :: Lens.Lens' ListCoverageStatisticsResponse Prelude.Integer
listCoverageStatisticsResponse_totalCounts :: Lens' ListCoverageStatisticsResponse Integer
listCoverageStatisticsResponse_totalCounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCoverageStatisticsResponse' {Integer
totalCounts :: Integer
$sel:totalCounts:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Integer
totalCounts} -> Integer
totalCounts) (\s :: ListCoverageStatisticsResponse
s@ListCoverageStatisticsResponse' {} Integer
a -> ListCoverageStatisticsResponse
s {$sel:totalCounts:ListCoverageStatisticsResponse' :: Integer
totalCounts = Integer
a} :: ListCoverageStatisticsResponse)

instance
  Prelude.NFData
    ListCoverageStatisticsResponse
  where
  rnf :: ListCoverageStatisticsResponse -> ()
rnf ListCoverageStatisticsResponse' {Int
Integer
Maybe (NonEmpty Counts)
Maybe Text
totalCounts :: Integer
httpStatus :: Int
nextToken :: Maybe Text
countsByGroup :: Maybe (NonEmpty Counts)
$sel:totalCounts:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Integer
$sel:httpStatus:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Int
$sel:nextToken:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Maybe Text
$sel:countsByGroup:ListCoverageStatisticsResponse' :: ListCoverageStatisticsResponse -> Maybe (NonEmpty Counts)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Counts)
countsByGroup
      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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
totalCounts