{-# 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.GetConformancePackComplianceDetails
-- 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 compliance details of a conformance pack for all Amazon Web
-- Services resources that are monitered by conformance pack.
module Amazonka.Config.GetConformancePackComplianceDetails
  ( -- * Creating a Request
    GetConformancePackComplianceDetails (..),
    newGetConformancePackComplianceDetails,

    -- * Request Lenses
    getConformancePackComplianceDetails_filters,
    getConformancePackComplianceDetails_limit,
    getConformancePackComplianceDetails_nextToken,
    getConformancePackComplianceDetails_conformancePackName,

    -- * Destructuring the Response
    GetConformancePackComplianceDetailsResponse (..),
    newGetConformancePackComplianceDetailsResponse,

    -- * Response Lenses
    getConformancePackComplianceDetailsResponse_conformancePackRuleEvaluationResults,
    getConformancePackComplianceDetailsResponse_nextToken,
    getConformancePackComplianceDetailsResponse_httpStatus,
    getConformancePackComplianceDetailsResponse_conformancePackName,
  )
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:/ 'newGetConformancePackComplianceDetails' smart constructor.
data GetConformancePackComplianceDetails = GetConformancePackComplianceDetails'
  { -- | A @ConformancePackEvaluationFilters@ object.
    GetConformancePackComplianceDetails
-> Maybe ConformancePackEvaluationFilters
filters :: Prelude.Maybe ConformancePackEvaluationFilters,
    -- | The maximum number of evaluation results returned on each page. If you
    -- do no specify a number, Config uses the default. The default is 100.
    GetConformancePackComplianceDetails -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ string returned in a previous request that you use to
    -- request the next page of results in a paginated response.
    GetConformancePackComplianceDetails -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Name of the conformance pack.
    GetConformancePackComplianceDetails -> Text
conformancePackName :: Prelude.Text
  }
  deriving (GetConformancePackComplianceDetails
-> GetConformancePackComplianceDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConformancePackComplianceDetails
-> GetConformancePackComplianceDetails -> Bool
$c/= :: GetConformancePackComplianceDetails
-> GetConformancePackComplianceDetails -> Bool
== :: GetConformancePackComplianceDetails
-> GetConformancePackComplianceDetails -> Bool
$c== :: GetConformancePackComplianceDetails
-> GetConformancePackComplianceDetails -> Bool
Prelude.Eq, ReadPrec [GetConformancePackComplianceDetails]
ReadPrec GetConformancePackComplianceDetails
Int -> ReadS GetConformancePackComplianceDetails
ReadS [GetConformancePackComplianceDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetConformancePackComplianceDetails]
$creadListPrec :: ReadPrec [GetConformancePackComplianceDetails]
readPrec :: ReadPrec GetConformancePackComplianceDetails
$creadPrec :: ReadPrec GetConformancePackComplianceDetails
readList :: ReadS [GetConformancePackComplianceDetails]
$creadList :: ReadS [GetConformancePackComplianceDetails]
readsPrec :: Int -> ReadS GetConformancePackComplianceDetails
$creadsPrec :: Int -> ReadS GetConformancePackComplianceDetails
Prelude.Read, Int -> GetConformancePackComplianceDetails -> ShowS
[GetConformancePackComplianceDetails] -> ShowS
GetConformancePackComplianceDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConformancePackComplianceDetails] -> ShowS
$cshowList :: [GetConformancePackComplianceDetails] -> ShowS
show :: GetConformancePackComplianceDetails -> String
$cshow :: GetConformancePackComplianceDetails -> String
showsPrec :: Int -> GetConformancePackComplianceDetails -> ShowS
$cshowsPrec :: Int -> GetConformancePackComplianceDetails -> ShowS
Prelude.Show, forall x.
Rep GetConformancePackComplianceDetails x
-> GetConformancePackComplianceDetails
forall x.
GetConformancePackComplianceDetails
-> Rep GetConformancePackComplianceDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetConformancePackComplianceDetails x
-> GetConformancePackComplianceDetails
$cfrom :: forall x.
GetConformancePackComplianceDetails
-> Rep GetConformancePackComplianceDetails x
Prelude.Generic)

-- |
-- Create a value of 'GetConformancePackComplianceDetails' 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', 'getConformancePackComplianceDetails_filters' - A @ConformancePackEvaluationFilters@ object.
--
-- 'limit', 'getConformancePackComplianceDetails_limit' - The maximum number of evaluation results returned on each page. If you
-- do no specify a number, Config uses the default. The default is 100.
--
-- 'nextToken', 'getConformancePackComplianceDetails_nextToken' - The @nextToken@ string returned in a previous request that you use to
-- request the next page of results in a paginated response.
--
-- 'conformancePackName', 'getConformancePackComplianceDetails_conformancePackName' - Name of the conformance pack.
newGetConformancePackComplianceDetails ::
  -- | 'conformancePackName'
  Prelude.Text ->
  GetConformancePackComplianceDetails
newGetConformancePackComplianceDetails :: Text -> GetConformancePackComplianceDetails
newGetConformancePackComplianceDetails
  Text
pConformancePackName_ =
    GetConformancePackComplianceDetails'
      { $sel:filters:GetConformancePackComplianceDetails' :: Maybe ConformancePackEvaluationFilters
filters =
          forall a. Maybe a
Prelude.Nothing,
        $sel:limit:GetConformancePackComplianceDetails' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetConformancePackComplianceDetails' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:conformancePackName:GetConformancePackComplianceDetails' :: Text
conformancePackName =
          Text
pConformancePackName_
      }

-- | A @ConformancePackEvaluationFilters@ object.
getConformancePackComplianceDetails_filters :: Lens.Lens' GetConformancePackComplianceDetails (Prelude.Maybe ConformancePackEvaluationFilters)
getConformancePackComplianceDetails_filters :: Lens'
  GetConformancePackComplianceDetails
  (Maybe ConformancePackEvaluationFilters)
getConformancePackComplianceDetails_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConformancePackComplianceDetails' {Maybe ConformancePackEvaluationFilters
filters :: Maybe ConformancePackEvaluationFilters
$sel:filters:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails
-> Maybe ConformancePackEvaluationFilters
filters} -> Maybe ConformancePackEvaluationFilters
filters) (\s :: GetConformancePackComplianceDetails
s@GetConformancePackComplianceDetails' {} Maybe ConformancePackEvaluationFilters
a -> GetConformancePackComplianceDetails
s {$sel:filters:GetConformancePackComplianceDetails' :: Maybe ConformancePackEvaluationFilters
filters = Maybe ConformancePackEvaluationFilters
a} :: GetConformancePackComplianceDetails)

-- | The maximum number of evaluation results returned on each page. If you
-- do no specify a number, Config uses the default. The default is 100.
getConformancePackComplianceDetails_limit :: Lens.Lens' GetConformancePackComplianceDetails (Prelude.Maybe Prelude.Natural)
getConformancePackComplianceDetails_limit :: Lens' GetConformancePackComplianceDetails (Maybe Natural)
getConformancePackComplianceDetails_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConformancePackComplianceDetails' {Maybe Natural
limit :: Maybe Natural
$sel:limit:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: GetConformancePackComplianceDetails
s@GetConformancePackComplianceDetails' {} Maybe Natural
a -> GetConformancePackComplianceDetails
s {$sel:limit:GetConformancePackComplianceDetails' :: Maybe Natural
limit = Maybe Natural
a} :: GetConformancePackComplianceDetails)

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

-- | Name of the conformance pack.
getConformancePackComplianceDetails_conformancePackName :: Lens.Lens' GetConformancePackComplianceDetails Prelude.Text
getConformancePackComplianceDetails_conformancePackName :: Lens' GetConformancePackComplianceDetails Text
getConformancePackComplianceDetails_conformancePackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConformancePackComplianceDetails' {Text
conformancePackName :: Text
$sel:conformancePackName:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Text
conformancePackName} -> Text
conformancePackName) (\s :: GetConformancePackComplianceDetails
s@GetConformancePackComplianceDetails' {} Text
a -> GetConformancePackComplianceDetails
s {$sel:conformancePackName:GetConformancePackComplianceDetails' :: Text
conformancePackName = Text
a} :: GetConformancePackComplianceDetails)

instance
  Core.AWSRequest
    GetConformancePackComplianceDetails
  where
  type
    AWSResponse GetConformancePackComplianceDetails =
      GetConformancePackComplianceDetailsResponse
  request :: (Service -> Service)
-> GetConformancePackComplianceDetails
-> Request GetConformancePackComplianceDetails
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 GetConformancePackComplianceDetails
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetConformancePackComplianceDetails)))
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 [ConformancePackEvaluationResult]
-> Maybe Text
-> Int
-> Text
-> GetConformancePackComplianceDetailsResponse
GetConformancePackComplianceDetailsResponse'
            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
"ConformancePackRuleEvaluationResults"
                            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))
            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
"ConformancePackName")
      )

instance
  Prelude.Hashable
    GetConformancePackComplianceDetails
  where
  hashWithSalt :: Int -> GetConformancePackComplianceDetails -> Int
hashWithSalt
    Int
_salt
    GetConformancePackComplianceDetails' {Maybe Natural
Maybe Text
Maybe ConformancePackEvaluationFilters
Text
conformancePackName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ConformancePackEvaluationFilters
$sel:conformancePackName:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Text
$sel:nextToken:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Text
$sel:limit:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Natural
$sel:filters:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails
-> Maybe ConformancePackEvaluationFilters
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConformancePackEvaluationFilters
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` Text
conformancePackName

instance
  Prelude.NFData
    GetConformancePackComplianceDetails
  where
  rnf :: GetConformancePackComplianceDetails -> ()
rnf GetConformancePackComplianceDetails' {Maybe Natural
Maybe Text
Maybe ConformancePackEvaluationFilters
Text
conformancePackName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ConformancePackEvaluationFilters
$sel:conformancePackName:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Text
$sel:nextToken:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Text
$sel:limit:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Natural
$sel:filters:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails
-> Maybe ConformancePackEvaluationFilters
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConformancePackEvaluationFilters
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 Text
conformancePackName

instance
  Data.ToHeaders
    GetConformancePackComplianceDetails
  where
  toHeaders :: GetConformancePackComplianceDetails -> 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.GetConformancePackComplianceDetails" ::
                          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
    GetConformancePackComplianceDetails
  where
  toJSON :: GetConformancePackComplianceDetails -> Value
toJSON GetConformancePackComplianceDetails' {Maybe Natural
Maybe Text
Maybe ConformancePackEvaluationFilters
Text
conformancePackName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
filters :: Maybe ConformancePackEvaluationFilters
$sel:conformancePackName:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Text
$sel:nextToken:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Text
$sel:limit:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails -> Maybe Natural
$sel:filters:GetConformancePackComplianceDetails' :: GetConformancePackComplianceDetails
-> Maybe ConformancePackEvaluationFilters
..} =
    [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 ConformancePackEvaluationFilters
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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ConformancePackName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
conformancePackName)
          ]
      )

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

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

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

-- |
-- Create a value of 'GetConformancePackComplianceDetailsResponse' 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:
--
-- 'conformancePackRuleEvaluationResults', 'getConformancePackComplianceDetailsResponse_conformancePackRuleEvaluationResults' - Returns a list of @ConformancePackEvaluationResult@ objects.
--
-- 'nextToken', 'getConformancePackComplianceDetailsResponse_nextToken' - The @nextToken@ string returned in a previous request that you use to
-- request the next page of results in a paginated response.
--
-- 'httpStatus', 'getConformancePackComplianceDetailsResponse_httpStatus' - The response's http status code.
--
-- 'conformancePackName', 'getConformancePackComplianceDetailsResponse_conformancePackName' - Name of the conformance pack.
newGetConformancePackComplianceDetailsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'conformancePackName'
  Prelude.Text ->
  GetConformancePackComplianceDetailsResponse
newGetConformancePackComplianceDetailsResponse :: Int -> Text -> GetConformancePackComplianceDetailsResponse
newGetConformancePackComplianceDetailsResponse
  Int
pHttpStatus_
  Text
pConformancePackName_ =
    GetConformancePackComplianceDetailsResponse'
      { $sel:conformancePackRuleEvaluationResults:GetConformancePackComplianceDetailsResponse' :: Maybe [ConformancePackEvaluationResult]
conformancePackRuleEvaluationResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetConformancePackComplianceDetailsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetConformancePackComplianceDetailsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:conformancePackName:GetConformancePackComplianceDetailsResponse' :: Text
conformancePackName =
          Text
pConformancePackName_
      }

-- | Returns a list of @ConformancePackEvaluationResult@ objects.
getConformancePackComplianceDetailsResponse_conformancePackRuleEvaluationResults :: Lens.Lens' GetConformancePackComplianceDetailsResponse (Prelude.Maybe [ConformancePackEvaluationResult])
getConformancePackComplianceDetailsResponse_conformancePackRuleEvaluationResults :: Lens'
  GetConformancePackComplianceDetailsResponse
  (Maybe [ConformancePackEvaluationResult])
getConformancePackComplianceDetailsResponse_conformancePackRuleEvaluationResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConformancePackComplianceDetailsResponse' {Maybe [ConformancePackEvaluationResult]
conformancePackRuleEvaluationResults :: Maybe [ConformancePackEvaluationResult]
$sel:conformancePackRuleEvaluationResults:GetConformancePackComplianceDetailsResponse' :: GetConformancePackComplianceDetailsResponse
-> Maybe [ConformancePackEvaluationResult]
conformancePackRuleEvaluationResults} -> Maybe [ConformancePackEvaluationResult]
conformancePackRuleEvaluationResults) (\s :: GetConformancePackComplianceDetailsResponse
s@GetConformancePackComplianceDetailsResponse' {} Maybe [ConformancePackEvaluationResult]
a -> GetConformancePackComplianceDetailsResponse
s {$sel:conformancePackRuleEvaluationResults:GetConformancePackComplianceDetailsResponse' :: Maybe [ConformancePackEvaluationResult]
conformancePackRuleEvaluationResults = Maybe [ConformancePackEvaluationResult]
a} :: GetConformancePackComplianceDetailsResponse) 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 @nextToken@ string returned in a previous request that you use to
-- request the next page of results in a paginated response.
getConformancePackComplianceDetailsResponse_nextToken :: Lens.Lens' GetConformancePackComplianceDetailsResponse (Prelude.Maybe Prelude.Text)
getConformancePackComplianceDetailsResponse_nextToken :: Lens' GetConformancePackComplianceDetailsResponse (Maybe Text)
getConformancePackComplianceDetailsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConformancePackComplianceDetailsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetConformancePackComplianceDetailsResponse' :: GetConformancePackComplianceDetailsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetConformancePackComplianceDetailsResponse
s@GetConformancePackComplianceDetailsResponse' {} Maybe Text
a -> GetConformancePackComplianceDetailsResponse
s {$sel:nextToken:GetConformancePackComplianceDetailsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetConformancePackComplianceDetailsResponse)

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

-- | Name of the conformance pack.
getConformancePackComplianceDetailsResponse_conformancePackName :: Lens.Lens' GetConformancePackComplianceDetailsResponse Prelude.Text
getConformancePackComplianceDetailsResponse_conformancePackName :: Lens' GetConformancePackComplianceDetailsResponse Text
getConformancePackComplianceDetailsResponse_conformancePackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetConformancePackComplianceDetailsResponse' {Text
conformancePackName :: Text
$sel:conformancePackName:GetConformancePackComplianceDetailsResponse' :: GetConformancePackComplianceDetailsResponse -> Text
conformancePackName} -> Text
conformancePackName) (\s :: GetConformancePackComplianceDetailsResponse
s@GetConformancePackComplianceDetailsResponse' {} Text
a -> GetConformancePackComplianceDetailsResponse
s {$sel:conformancePackName:GetConformancePackComplianceDetailsResponse' :: Text
conformancePackName = Text
a} :: GetConformancePackComplianceDetailsResponse)

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