{-# 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.Config.ListConformancePackComplianceScores
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of conformance pack compliance scores. A compliance score
-- is the percentage of the number of compliant rule-resource combinations
-- in a conformance pack compared to the number of total possible
-- rule-resource combinations in the conformance pack. This metric provides
-- you with a high-level view of the compliance state of your conformance
-- packs. You can use it to identify, investigate, and understand the level
-- of compliance in your conformance packs.
--
-- Conformance packs with no evaluation results will have a compliance
-- score of @INSUFFICIENT_DATA@.
module Amazonka.Config.ListConformancePackComplianceScores
  ( -- * Creating a Request
    ListConformancePackComplianceScores (..),
    newListConformancePackComplianceScores,

    -- * Request Lenses
    listConformancePackComplianceScores_filters,
    listConformancePackComplianceScores_limit,
    listConformancePackComplianceScores_nextToken,
    listConformancePackComplianceScores_sortBy,
    listConformancePackComplianceScores_sortOrder,

    -- * Destructuring the Response
    ListConformancePackComplianceScoresResponse (..),
    newListConformancePackComplianceScoresResponse,

    -- * Response Lenses
    listConformancePackComplianceScoresResponse_nextToken,
    listConformancePackComplianceScoresResponse_httpStatus,
    listConformancePackComplianceScoresResponse_conformancePackComplianceScores,
  )
where

import Amazonka.Config.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

-- | /See:/ 'newListConformancePackComplianceScores' smart constructor.
data ListConformancePackComplianceScores = ListConformancePackComplianceScores'
  { -- | Filters the results based on the
    -- @ConformancePackComplianceScoresFilters@.
    ListConformancePackComplianceScores
-> Maybe ConformancePackComplianceScoresFilters
filters :: Prelude.Maybe ConformancePackComplianceScoresFilters,
    -- | The maximum number of conformance pack compliance scores returned on
    -- each page.
    ListConformancePackComplianceScores -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ string in a prior request that you can use to get the
    -- paginated response for next set of conformance pack compliance scores.
    ListConformancePackComplianceScores -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Sorts your conformance pack compliance scores in either ascending or
    -- descending order, depending on @SortOrder@.
    --
    -- By default, conformance pack compliance scores are sorted in
    -- alphabetical order by name of the conformance pack. Enter @SCORE@, to
    -- sort conformance pack compliance scores by the numerical value of the
    -- compliance score.
    ListConformancePackComplianceScores -> Maybe SortBy
sortBy :: Prelude.Maybe SortBy,
    -- | Determines the order in which conformance pack compliance scores are
    -- sorted. Either in ascending or descending order.
    --
    -- By default, conformance pack compliance scores are sorted in
    -- alphabetical order by name of the conformance pack. Conformance pack
    -- compliance scores are sorted in reverse alphabetical order if you enter
    -- @DESCENDING@.
    --
    -- You can sort conformance pack compliance scores by the numerical value
    -- of the compliance score by entering @SCORE@ in the @SortBy@ action. When
    -- compliance scores are sorted by @SCORE@, conformance packs with a
    -- compliance score of @INSUFFICIENT_DATA@ will be last when sorting by
    -- ascending order and first when sorting by descending order.
    ListConformancePackComplianceScores -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder
  }
  deriving (ListConformancePackComplianceScores
-> ListConformancePackComplianceScores -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConformancePackComplianceScores
-> ListConformancePackComplianceScores -> Bool
$c/= :: ListConformancePackComplianceScores
-> ListConformancePackComplianceScores -> Bool
== :: ListConformancePackComplianceScores
-> ListConformancePackComplianceScores -> Bool
$c== :: ListConformancePackComplianceScores
-> ListConformancePackComplianceScores -> Bool
Prelude.Eq, ReadPrec [ListConformancePackComplianceScores]
ReadPrec ListConformancePackComplianceScores
Int -> ReadS ListConformancePackComplianceScores
ReadS [ListConformancePackComplianceScores]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConformancePackComplianceScores]
$creadListPrec :: ReadPrec [ListConformancePackComplianceScores]
readPrec :: ReadPrec ListConformancePackComplianceScores
$creadPrec :: ReadPrec ListConformancePackComplianceScores
readList :: ReadS [ListConformancePackComplianceScores]
$creadList :: ReadS [ListConformancePackComplianceScores]
readsPrec :: Int -> ReadS ListConformancePackComplianceScores
$creadsPrec :: Int -> ReadS ListConformancePackComplianceScores
Prelude.Read, Int -> ListConformancePackComplianceScores -> ShowS
[ListConformancePackComplianceScores] -> ShowS
ListConformancePackComplianceScores -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConformancePackComplianceScores] -> ShowS
$cshowList :: [ListConformancePackComplianceScores] -> ShowS
show :: ListConformancePackComplianceScores -> String
$cshow :: ListConformancePackComplianceScores -> String
showsPrec :: Int -> ListConformancePackComplianceScores -> ShowS
$cshowsPrec :: Int -> ListConformancePackComplianceScores -> ShowS
Prelude.Show, forall x.
Rep ListConformancePackComplianceScores x
-> ListConformancePackComplianceScores
forall x.
ListConformancePackComplianceScores
-> Rep ListConformancePackComplianceScores x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListConformancePackComplianceScores x
-> ListConformancePackComplianceScores
$cfrom :: forall x.
ListConformancePackComplianceScores
-> Rep ListConformancePackComplianceScores x
Prelude.Generic)

-- |
-- Create a value of 'ListConformancePackComplianceScores' 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:
--
-- 'filters', 'listConformancePackComplianceScores_filters' - Filters the results based on the
-- @ConformancePackComplianceScoresFilters@.
--
-- 'limit', 'listConformancePackComplianceScores_limit' - The maximum number of conformance pack compliance scores returned on
-- each page.
--
-- 'nextToken', 'listConformancePackComplianceScores_nextToken' - The @nextToken@ string in a prior request that you can use to get the
-- paginated response for next set of conformance pack compliance scores.
--
-- 'sortBy', 'listConformancePackComplianceScores_sortBy' - Sorts your conformance pack compliance scores in either ascending or
-- descending order, depending on @SortOrder@.
--
-- By default, conformance pack compliance scores are sorted in
-- alphabetical order by name of the conformance pack. Enter @SCORE@, to
-- sort conformance pack compliance scores by the numerical value of the
-- compliance score.
--
-- 'sortOrder', 'listConformancePackComplianceScores_sortOrder' - Determines the order in which conformance pack compliance scores are
-- sorted. Either in ascending or descending order.
--
-- By default, conformance pack compliance scores are sorted in
-- alphabetical order by name of the conformance pack. Conformance pack
-- compliance scores are sorted in reverse alphabetical order if you enter
-- @DESCENDING@.
--
-- You can sort conformance pack compliance scores by the numerical value
-- of the compliance score by entering @SCORE@ in the @SortBy@ action. When
-- compliance scores are sorted by @SCORE@, conformance packs with a
-- compliance score of @INSUFFICIENT_DATA@ will be last when sorting by
-- ascending order and first when sorting by descending order.
newListConformancePackComplianceScores ::
  ListConformancePackComplianceScores
newListConformancePackComplianceScores :: ListConformancePackComplianceScores
newListConformancePackComplianceScores =
  ListConformancePackComplianceScores'
    { $sel:filters:ListConformancePackComplianceScores' :: Maybe ConformancePackComplianceScoresFilters
filters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ListConformancePackComplianceScores' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConformancePackComplianceScores' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListConformancePackComplianceScores' :: Maybe SortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListConformancePackComplianceScores' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing
    }

-- | Filters the results based on the
-- @ConformancePackComplianceScoresFilters@.
listConformancePackComplianceScores_filters :: Lens.Lens' ListConformancePackComplianceScores (Prelude.Maybe ConformancePackComplianceScoresFilters)
listConformancePackComplianceScores_filters :: Lens'
  ListConformancePackComplianceScores
  (Maybe ConformancePackComplianceScoresFilters)
listConformancePackComplianceScores_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScores' {Maybe ConformancePackComplianceScoresFilters
filters :: Maybe ConformancePackComplianceScoresFilters
$sel:filters:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores
-> Maybe ConformancePackComplianceScoresFilters
filters} -> Maybe ConformancePackComplianceScoresFilters
filters) (\s :: ListConformancePackComplianceScores
s@ListConformancePackComplianceScores' {} Maybe ConformancePackComplianceScoresFilters
a -> ListConformancePackComplianceScores
s {$sel:filters:ListConformancePackComplianceScores' :: Maybe ConformancePackComplianceScoresFilters
filters = Maybe ConformancePackComplianceScoresFilters
a} :: ListConformancePackComplianceScores)

-- | The maximum number of conformance pack compliance scores returned on
-- each page.
listConformancePackComplianceScores_limit :: Lens.Lens' ListConformancePackComplianceScores (Prelude.Maybe Prelude.Natural)
listConformancePackComplianceScores_limit :: Lens' ListConformancePackComplianceScores (Maybe Natural)
listConformancePackComplianceScores_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScores' {Maybe Natural
limit :: Maybe Natural
$sel:limit:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: ListConformancePackComplianceScores
s@ListConformancePackComplianceScores' {} Maybe Natural
a -> ListConformancePackComplianceScores
s {$sel:limit:ListConformancePackComplianceScores' :: Maybe Natural
limit = Maybe Natural
a} :: ListConformancePackComplianceScores)

-- | The @nextToken@ string in a prior request that you can use to get the
-- paginated response for next set of conformance pack compliance scores.
listConformancePackComplianceScores_nextToken :: Lens.Lens' ListConformancePackComplianceScores (Prelude.Maybe Prelude.Text)
listConformancePackComplianceScores_nextToken :: Lens' ListConformancePackComplianceScores (Maybe Text)
listConformancePackComplianceScores_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScores' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConformancePackComplianceScores
s@ListConformancePackComplianceScores' {} Maybe Text
a -> ListConformancePackComplianceScores
s {$sel:nextToken:ListConformancePackComplianceScores' :: Maybe Text
nextToken = Maybe Text
a} :: ListConformancePackComplianceScores)

-- | Sorts your conformance pack compliance scores in either ascending or
-- descending order, depending on @SortOrder@.
--
-- By default, conformance pack compliance scores are sorted in
-- alphabetical order by name of the conformance pack. Enter @SCORE@, to
-- sort conformance pack compliance scores by the numerical value of the
-- compliance score.
listConformancePackComplianceScores_sortBy :: Lens.Lens' ListConformancePackComplianceScores (Prelude.Maybe SortBy)
listConformancePackComplianceScores_sortBy :: Lens' ListConformancePackComplianceScores (Maybe SortBy)
listConformancePackComplianceScores_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScores' {Maybe SortBy
sortBy :: Maybe SortBy
$sel:sortBy:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortBy
sortBy} -> Maybe SortBy
sortBy) (\s :: ListConformancePackComplianceScores
s@ListConformancePackComplianceScores' {} Maybe SortBy
a -> ListConformancePackComplianceScores
s {$sel:sortBy:ListConformancePackComplianceScores' :: Maybe SortBy
sortBy = Maybe SortBy
a} :: ListConformancePackComplianceScores)

-- | Determines the order in which conformance pack compliance scores are
-- sorted. Either in ascending or descending order.
--
-- By default, conformance pack compliance scores are sorted in
-- alphabetical order by name of the conformance pack. Conformance pack
-- compliance scores are sorted in reverse alphabetical order if you enter
-- @DESCENDING@.
--
-- You can sort conformance pack compliance scores by the numerical value
-- of the compliance score by entering @SCORE@ in the @SortBy@ action. When
-- compliance scores are sorted by @SCORE@, conformance packs with a
-- compliance score of @INSUFFICIENT_DATA@ will be last when sorting by
-- ascending order and first when sorting by descending order.
listConformancePackComplianceScores_sortOrder :: Lens.Lens' ListConformancePackComplianceScores (Prelude.Maybe SortOrder)
listConformancePackComplianceScores_sortOrder :: Lens' ListConformancePackComplianceScores (Maybe SortOrder)
listConformancePackComplianceScores_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScores' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListConformancePackComplianceScores
s@ListConformancePackComplianceScores' {} Maybe SortOrder
a -> ListConformancePackComplianceScores
s {$sel:sortOrder:ListConformancePackComplianceScores' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListConformancePackComplianceScores)

instance
  Core.AWSRequest
    ListConformancePackComplianceScores
  where
  type
    AWSResponse ListConformancePackComplianceScores =
      ListConformancePackComplianceScoresResponse
  request :: (Service -> Service)
-> ListConformancePackComplianceScores
-> Request ListConformancePackComplianceScores
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 ListConformancePackComplianceScores
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListConformancePackComplianceScores)))
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
-> Int
-> [ConformancePackComplianceScore]
-> ListConformancePackComplianceScoresResponse
ListConformancePackComplianceScoresResponse'
            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.<*> (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 (Maybe a)
Data..?> Key
"ConformancePackComplianceScores"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance
  Prelude.Hashable
    ListConformancePackComplianceScores
  where
  hashWithSalt :: Int -> ListConformancePackComplianceScores -> Int
hashWithSalt
    Int
_salt
    ListConformancePackComplianceScores' {Maybe Natural
Maybe Text
Maybe ConformancePackComplianceScoresFilters
Maybe SortBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortBy
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ConformancePackComplianceScoresFilters
$sel:sortOrder:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortOrder
$sel:sortBy:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortBy
$sel:nextToken:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Text
$sel:limit:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Natural
$sel:filters:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores
-> Maybe ConformancePackComplianceScoresFilters
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConformancePackComplianceScoresFilters
filters
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortBy
sortBy
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder

instance
  Prelude.NFData
    ListConformancePackComplianceScores
  where
  rnf :: ListConformancePackComplianceScores -> ()
rnf ListConformancePackComplianceScores' {Maybe Natural
Maybe Text
Maybe ConformancePackComplianceScoresFilters
Maybe SortBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortBy
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ConformancePackComplianceScoresFilters
$sel:sortOrder:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortOrder
$sel:sortBy:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortBy
$sel:nextToken:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Text
$sel:limit:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Natural
$sel:filters:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores
-> Maybe ConformancePackComplianceScoresFilters
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConformancePackComplianceScoresFilters
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      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 Maybe SortBy
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortOrder
sortOrder

instance
  Data.ToHeaders
    ListConformancePackComplianceScores
  where
  toHeaders :: ListConformancePackComplianceScores -> 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
"StarlingDoveService.ListConformancePackComplianceScores" ::
                          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
    ListConformancePackComplianceScores
  where
  toJSON :: ListConformancePackComplianceScores -> Value
toJSON ListConformancePackComplianceScores' {Maybe Natural
Maybe Text
Maybe ConformancePackComplianceScoresFilters
Maybe SortBy
Maybe SortOrder
sortOrder :: Maybe SortOrder
sortBy :: Maybe SortBy
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ConformancePackComplianceScoresFilters
$sel:sortOrder:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortOrder
$sel:sortBy:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe SortBy
$sel:nextToken:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Text
$sel:limit:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores -> Maybe Natural
$sel:filters:ListConformancePackComplianceScores' :: ListConformancePackComplianceScores
-> Maybe ConformancePackComplianceScoresFilters
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" 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 ConformancePackComplianceScoresFilters
filters,
            (Key
"Limit" 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
limit,
            (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,
            (Key
"SortBy" 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 SortBy
sortBy,
            (Key
"SortOrder" 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 SortOrder
sortOrder
          ]
      )

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

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

-- | /See:/ 'newListConformancePackComplianceScoresResponse' smart constructor.
data ListConformancePackComplianceScoresResponse = ListConformancePackComplianceScoresResponse'
  { -- | The @nextToken@ string that you can use to get the next page of results
    -- in a paginated response.
    ListConformancePackComplianceScoresResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListConformancePackComplianceScoresResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list of @ConformancePackComplianceScore@ objects.
    ListConformancePackComplianceScoresResponse
-> [ConformancePackComplianceScore]
conformancePackComplianceScores :: [ConformancePackComplianceScore]
  }
  deriving (ListConformancePackComplianceScoresResponse
-> ListConformancePackComplianceScoresResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConformancePackComplianceScoresResponse
-> ListConformancePackComplianceScoresResponse -> Bool
$c/= :: ListConformancePackComplianceScoresResponse
-> ListConformancePackComplianceScoresResponse -> Bool
== :: ListConformancePackComplianceScoresResponse
-> ListConformancePackComplianceScoresResponse -> Bool
$c== :: ListConformancePackComplianceScoresResponse
-> ListConformancePackComplianceScoresResponse -> Bool
Prelude.Eq, ReadPrec [ListConformancePackComplianceScoresResponse]
ReadPrec ListConformancePackComplianceScoresResponse
Int -> ReadS ListConformancePackComplianceScoresResponse
ReadS [ListConformancePackComplianceScoresResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConformancePackComplianceScoresResponse]
$creadListPrec :: ReadPrec [ListConformancePackComplianceScoresResponse]
readPrec :: ReadPrec ListConformancePackComplianceScoresResponse
$creadPrec :: ReadPrec ListConformancePackComplianceScoresResponse
readList :: ReadS [ListConformancePackComplianceScoresResponse]
$creadList :: ReadS [ListConformancePackComplianceScoresResponse]
readsPrec :: Int -> ReadS ListConformancePackComplianceScoresResponse
$creadsPrec :: Int -> ReadS ListConformancePackComplianceScoresResponse
Prelude.Read, Int -> ListConformancePackComplianceScoresResponse -> ShowS
[ListConformancePackComplianceScoresResponse] -> ShowS
ListConformancePackComplianceScoresResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConformancePackComplianceScoresResponse] -> ShowS
$cshowList :: [ListConformancePackComplianceScoresResponse] -> ShowS
show :: ListConformancePackComplianceScoresResponse -> String
$cshow :: ListConformancePackComplianceScoresResponse -> String
showsPrec :: Int -> ListConformancePackComplianceScoresResponse -> ShowS
$cshowsPrec :: Int -> ListConformancePackComplianceScoresResponse -> ShowS
Prelude.Show, forall x.
Rep ListConformancePackComplianceScoresResponse x
-> ListConformancePackComplianceScoresResponse
forall x.
ListConformancePackComplianceScoresResponse
-> Rep ListConformancePackComplianceScoresResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListConformancePackComplianceScoresResponse x
-> ListConformancePackComplianceScoresResponse
$cfrom :: forall x.
ListConformancePackComplianceScoresResponse
-> Rep ListConformancePackComplianceScoresResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListConformancePackComplianceScoresResponse' 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', 'listConformancePackComplianceScoresResponse_nextToken' - The @nextToken@ string that you can use to get the next page of results
-- in a paginated response.
--
-- 'httpStatus', 'listConformancePackComplianceScoresResponse_httpStatus' - The response's http status code.
--
-- 'conformancePackComplianceScores', 'listConformancePackComplianceScoresResponse_conformancePackComplianceScores' - A list of @ConformancePackComplianceScore@ objects.
newListConformancePackComplianceScoresResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListConformancePackComplianceScoresResponse
newListConformancePackComplianceScoresResponse :: Int -> ListConformancePackComplianceScoresResponse
newListConformancePackComplianceScoresResponse
  Int
pHttpStatus_ =
    ListConformancePackComplianceScoresResponse'
      { $sel:nextToken:ListConformancePackComplianceScoresResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListConformancePackComplianceScoresResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:conformancePackComplianceScores:ListConformancePackComplianceScoresResponse' :: [ConformancePackComplianceScore]
conformancePackComplianceScores =
          forall a. Monoid a => a
Prelude.mempty
      }

-- | The @nextToken@ string that you can use to get the next page of results
-- in a paginated response.
listConformancePackComplianceScoresResponse_nextToken :: Lens.Lens' ListConformancePackComplianceScoresResponse (Prelude.Maybe Prelude.Text)
listConformancePackComplianceScoresResponse_nextToken :: Lens' ListConformancePackComplianceScoresResponse (Maybe Text)
listConformancePackComplianceScoresResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScoresResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConformancePackComplianceScoresResponse' :: ListConformancePackComplianceScoresResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConformancePackComplianceScoresResponse
s@ListConformancePackComplianceScoresResponse' {} Maybe Text
a -> ListConformancePackComplianceScoresResponse
s {$sel:nextToken:ListConformancePackComplianceScoresResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListConformancePackComplianceScoresResponse)

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

-- | A list of @ConformancePackComplianceScore@ objects.
listConformancePackComplianceScoresResponse_conformancePackComplianceScores :: Lens.Lens' ListConformancePackComplianceScoresResponse [ConformancePackComplianceScore]
listConformancePackComplianceScoresResponse_conformancePackComplianceScores :: Lens'
  ListConformancePackComplianceScoresResponse
  [ConformancePackComplianceScore]
listConformancePackComplianceScoresResponse_conformancePackComplianceScores = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConformancePackComplianceScoresResponse' {[ConformancePackComplianceScore]
conformancePackComplianceScores :: [ConformancePackComplianceScore]
$sel:conformancePackComplianceScores:ListConformancePackComplianceScoresResponse' :: ListConformancePackComplianceScoresResponse
-> [ConformancePackComplianceScore]
conformancePackComplianceScores} -> [ConformancePackComplianceScore]
conformancePackComplianceScores) (\s :: ListConformancePackComplianceScoresResponse
s@ListConformancePackComplianceScoresResponse' {} [ConformancePackComplianceScore]
a -> ListConformancePackComplianceScoresResponse
s {$sel:conformancePackComplianceScores:ListConformancePackComplianceScoresResponse' :: [ConformancePackComplianceScore]
conformancePackComplianceScores = [ConformancePackComplianceScore]
a} :: ListConformancePackComplianceScoresResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Prelude.NFData
    ListConformancePackComplianceScoresResponse
  where
  rnf :: ListConformancePackComplianceScoresResponse -> ()
rnf ListConformancePackComplianceScoresResponse' {Int
[ConformancePackComplianceScore]
Maybe Text
conformancePackComplianceScores :: [ConformancePackComplianceScore]
httpStatus :: Int
nextToken :: Maybe Text
$sel:conformancePackComplianceScores:ListConformancePackComplianceScoresResponse' :: ListConformancePackComplianceScoresResponse
-> [ConformancePackComplianceScore]
$sel:httpStatus:ListConformancePackComplianceScoresResponse' :: ListConformancePackComplianceScoresResponse -> Int
$sel:nextToken:ListConformancePackComplianceScoresResponse' :: ListConformancePackComplianceScoresResponse -> 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 Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ConformancePackComplianceScore]
conformancePackComplianceScores