{-# 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.DescribeComplianceByResource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Indicates whether the specified Amazon Web Services resources are
-- compliant. If a resource is noncompliant, this action returns the number
-- of Config rules that the resource does not comply with.
--
-- A resource is compliant if it complies with all the Config rules that
-- evaluate it. It is noncompliant if it does not comply with one or more
-- of these rules.
--
-- If Config has no current evaluation results for the resource, it returns
-- @INSUFFICIENT_DATA@. This result might indicate one of the following
-- conditions about the rules that evaluate the resource:
--
-- -   Config has never invoked an evaluation for the rule. To check
--     whether it has, use the @DescribeConfigRuleEvaluationStatus@ action
--     to get the @LastSuccessfulInvocationTime@ and
--     @LastFailedInvocationTime@.
--
-- -   The rule\'s Lambda function is failing to send evaluation results to
--     Config. Verify that the role that you assigned to your configuration
--     recorder includes the @config:PutEvaluations@ permission. If the
--     rule is a custom rule, verify that the Lambda execution role
--     includes the @config:PutEvaluations@ permission.
--
-- -   The rule\'s Lambda function has returned @NOT_APPLICABLE@ for all
--     evaluation results. This can occur if the resources were deleted or
--     removed from the rule\'s scope.
--
-- This operation returns paginated results.
module Amazonka.Config.DescribeComplianceByResource
  ( -- * Creating a Request
    DescribeComplianceByResource (..),
    newDescribeComplianceByResource,

    -- * Request Lenses
    describeComplianceByResource_complianceTypes,
    describeComplianceByResource_limit,
    describeComplianceByResource_nextToken,
    describeComplianceByResource_resourceId,
    describeComplianceByResource_resourceType,

    -- * Destructuring the Response
    DescribeComplianceByResourceResponse (..),
    newDescribeComplianceByResourceResponse,

    -- * Response Lenses
    describeComplianceByResourceResponse_complianceByResources,
    describeComplianceByResourceResponse_nextToken,
    describeComplianceByResourceResponse_httpStatus,
  )
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:/ 'newDescribeComplianceByResource' smart constructor.
data DescribeComplianceByResource = DescribeComplianceByResource'
  { -- | Filters the results by compliance.
    --
    -- The allowed values are @COMPLIANT@, @NON_COMPLIANT@, and
    -- @INSUFFICIENT_DATA@.
    DescribeComplianceByResource -> Maybe [ComplianceType]
complianceTypes :: Prelude.Maybe [ComplianceType],
    -- | The maximum number of evaluation results returned on each page. The
    -- default is 10. You cannot specify a number greater than 100. If you
    -- specify 0, Config uses the default.
    DescribeComplianceByResource -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ string returned on a previous page that you use to get
    -- the next page of results in a paginated response.
    DescribeComplianceByResource -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the Amazon Web Services resource for which you want compliance
    -- information. You can specify only one resource ID. If you specify a
    -- resource ID, you must also specify a type for @ResourceType@.
    DescribeComplianceByResource -> Maybe Text
resourceId :: Prelude.Maybe Prelude.Text,
    -- | The types of Amazon Web Services resources for which you want compliance
    -- information (for example, @AWS::EC2::Instance@). For this action, you
    -- can specify that the resource type is an Amazon Web Services account by
    -- specifying @AWS::::Account@.
    DescribeComplianceByResource -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeComplianceByResource
-> DescribeComplianceByResource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComplianceByResource
-> DescribeComplianceByResource -> Bool
$c/= :: DescribeComplianceByResource
-> DescribeComplianceByResource -> Bool
== :: DescribeComplianceByResource
-> DescribeComplianceByResource -> Bool
$c== :: DescribeComplianceByResource
-> DescribeComplianceByResource -> Bool
Prelude.Eq, ReadPrec [DescribeComplianceByResource]
ReadPrec DescribeComplianceByResource
Int -> ReadS DescribeComplianceByResource
ReadS [DescribeComplianceByResource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComplianceByResource]
$creadListPrec :: ReadPrec [DescribeComplianceByResource]
readPrec :: ReadPrec DescribeComplianceByResource
$creadPrec :: ReadPrec DescribeComplianceByResource
readList :: ReadS [DescribeComplianceByResource]
$creadList :: ReadS [DescribeComplianceByResource]
readsPrec :: Int -> ReadS DescribeComplianceByResource
$creadsPrec :: Int -> ReadS DescribeComplianceByResource
Prelude.Read, Int -> DescribeComplianceByResource -> ShowS
[DescribeComplianceByResource] -> ShowS
DescribeComplianceByResource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComplianceByResource] -> ShowS
$cshowList :: [DescribeComplianceByResource] -> ShowS
show :: DescribeComplianceByResource -> String
$cshow :: DescribeComplianceByResource -> String
showsPrec :: Int -> DescribeComplianceByResource -> ShowS
$cshowsPrec :: Int -> DescribeComplianceByResource -> ShowS
Prelude.Show, forall x.
Rep DescribeComplianceByResource x -> DescribeComplianceByResource
forall x.
DescribeComplianceByResource -> Rep DescribeComplianceByResource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComplianceByResource x -> DescribeComplianceByResource
$cfrom :: forall x.
DescribeComplianceByResource -> Rep DescribeComplianceByResource x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComplianceByResource' 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:
--
-- 'complianceTypes', 'describeComplianceByResource_complianceTypes' - Filters the results by compliance.
--
-- The allowed values are @COMPLIANT@, @NON_COMPLIANT@, and
-- @INSUFFICIENT_DATA@.
--
-- 'limit', 'describeComplianceByResource_limit' - The maximum number of evaluation results returned on each page. The
-- default is 10. You cannot specify a number greater than 100. If you
-- specify 0, Config uses the default.
--
-- 'nextToken', 'describeComplianceByResource_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
--
-- 'resourceId', 'describeComplianceByResource_resourceId' - The ID of the Amazon Web Services resource for which you want compliance
-- information. You can specify only one resource ID. If you specify a
-- resource ID, you must also specify a type for @ResourceType@.
--
-- 'resourceType', 'describeComplianceByResource_resourceType' - The types of Amazon Web Services resources for which you want compliance
-- information (for example, @AWS::EC2::Instance@). For this action, you
-- can specify that the resource type is an Amazon Web Services account by
-- specifying @AWS::::Account@.
newDescribeComplianceByResource ::
  DescribeComplianceByResource
newDescribeComplianceByResource :: DescribeComplianceByResource
newDescribeComplianceByResource =
  DescribeComplianceByResource'
    { $sel:complianceTypes:DescribeComplianceByResource' :: Maybe [ComplianceType]
complianceTypes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:DescribeComplianceByResource' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeComplianceByResource' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceId:DescribeComplianceByResource' :: Maybe Text
resourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:DescribeComplianceByResource' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing
    }

-- | Filters the results by compliance.
--
-- The allowed values are @COMPLIANT@, @NON_COMPLIANT@, and
-- @INSUFFICIENT_DATA@.
describeComplianceByResource_complianceTypes :: Lens.Lens' DescribeComplianceByResource (Prelude.Maybe [ComplianceType])
describeComplianceByResource_complianceTypes :: Lens' DescribeComplianceByResource (Maybe [ComplianceType])
describeComplianceByResource_complianceTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComplianceByResource' {Maybe [ComplianceType]
complianceTypes :: Maybe [ComplianceType]
$sel:complianceTypes:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe [ComplianceType]
complianceTypes} -> Maybe [ComplianceType]
complianceTypes) (\s :: DescribeComplianceByResource
s@DescribeComplianceByResource' {} Maybe [ComplianceType]
a -> DescribeComplianceByResource
s {$sel:complianceTypes:DescribeComplianceByResource' :: Maybe [ComplianceType]
complianceTypes = Maybe [ComplianceType]
a} :: DescribeComplianceByResource) 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 maximum number of evaluation results returned on each page. The
-- default is 10. You cannot specify a number greater than 100. If you
-- specify 0, Config uses the default.
describeComplianceByResource_limit :: Lens.Lens' DescribeComplianceByResource (Prelude.Maybe Prelude.Natural)
describeComplianceByResource_limit :: Lens' DescribeComplianceByResource (Maybe Natural)
describeComplianceByResource_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComplianceByResource' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DescribeComplianceByResource
s@DescribeComplianceByResource' {} Maybe Natural
a -> DescribeComplianceByResource
s {$sel:limit:DescribeComplianceByResource' :: Maybe Natural
limit = Maybe Natural
a} :: DescribeComplianceByResource)

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

-- | The ID of the Amazon Web Services resource for which you want compliance
-- information. You can specify only one resource ID. If you specify a
-- resource ID, you must also specify a type for @ResourceType@.
describeComplianceByResource_resourceId :: Lens.Lens' DescribeComplianceByResource (Prelude.Maybe Prelude.Text)
describeComplianceByResource_resourceId :: Lens' DescribeComplianceByResource (Maybe Text)
describeComplianceByResource_resourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComplianceByResource' {Maybe Text
resourceId :: Maybe Text
$sel:resourceId:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
resourceId} -> Maybe Text
resourceId) (\s :: DescribeComplianceByResource
s@DescribeComplianceByResource' {} Maybe Text
a -> DescribeComplianceByResource
s {$sel:resourceId:DescribeComplianceByResource' :: Maybe Text
resourceId = Maybe Text
a} :: DescribeComplianceByResource)

-- | The types of Amazon Web Services resources for which you want compliance
-- information (for example, @AWS::EC2::Instance@). For this action, you
-- can specify that the resource type is an Amazon Web Services account by
-- specifying @AWS::::Account@.
describeComplianceByResource_resourceType :: Lens.Lens' DescribeComplianceByResource (Prelude.Maybe Prelude.Text)
describeComplianceByResource_resourceType :: Lens' DescribeComplianceByResource (Maybe Text)
describeComplianceByResource_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComplianceByResource' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: DescribeComplianceByResource
s@DescribeComplianceByResource' {} Maybe Text
a -> DescribeComplianceByResource
s {$sel:resourceType:DescribeComplianceByResource' :: Maybe Text
resourceType = Maybe Text
a} :: DescribeComplianceByResource)

instance Core.AWSPager DescribeComplianceByResource where
  page :: DescribeComplianceByResource
-> AWSResponse DescribeComplianceByResource
-> Maybe DescribeComplianceByResource
page DescribeComplianceByResource
rq AWSResponse DescribeComplianceByResource
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeComplianceByResource
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeComplianceByResourceResponse (Maybe Text)
describeComplianceByResourceResponse_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 DescribeComplianceByResource
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeComplianceByResourceResponse (Maybe [ComplianceByResource])
describeComplianceByResourceResponse_complianceByResources
            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
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeComplianceByResource
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeComplianceByResource (Maybe Text)
describeComplianceByResource_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeComplianceByResource
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeComplianceByResourceResponse (Maybe Text)
describeComplianceByResourceResponse_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 DescribeComplianceByResource where
  type
    AWSResponse DescribeComplianceByResource =
      DescribeComplianceByResourceResponse
  request :: (Service -> Service)
-> DescribeComplianceByResource
-> Request DescribeComplianceByResource
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 DescribeComplianceByResource
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeComplianceByResource)))
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 [ComplianceByResource]
-> Maybe Text -> Int -> DescribeComplianceByResourceResponse
DescribeComplianceByResourceResponse'
            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
"ComplianceByResources"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    DescribeComplianceByResource
  where
  hashWithSalt :: Int -> DescribeComplianceByResource -> Int
hashWithSalt Int
_salt DescribeComplianceByResource' {Maybe Natural
Maybe [ComplianceType]
Maybe Text
resourceType :: Maybe Text
resourceId :: Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
complianceTypes :: Maybe [ComplianceType]
$sel:resourceType:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:resourceId:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:nextToken:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:limit:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Natural
$sel:complianceTypes:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe [ComplianceType]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ComplianceType]
complianceTypes
      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 Text
resourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceType

instance Prelude.NFData DescribeComplianceByResource where
  rnf :: DescribeComplianceByResource -> ()
rnf DescribeComplianceByResource' {Maybe Natural
Maybe [ComplianceType]
Maybe Text
resourceType :: Maybe Text
resourceId :: Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
complianceTypes :: Maybe [ComplianceType]
$sel:resourceType:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:resourceId:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:nextToken:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:limit:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Natural
$sel:complianceTypes:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe [ComplianceType]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ComplianceType]
complianceTypes
      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 Text
resourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceType

instance Data.ToHeaders DescribeComplianceByResource where
  toHeaders :: DescribeComplianceByResource -> 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.DescribeComplianceByResource" ::
                          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 DescribeComplianceByResource where
  toJSON :: DescribeComplianceByResource -> Value
toJSON DescribeComplianceByResource' {Maybe Natural
Maybe [ComplianceType]
Maybe Text
resourceType :: Maybe Text
resourceId :: Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
complianceTypes :: Maybe [ComplianceType]
$sel:resourceType:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:resourceId:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:nextToken:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Text
$sel:limit:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe Natural
$sel:complianceTypes:DescribeComplianceByResource' :: DescribeComplianceByResource -> Maybe [ComplianceType]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ComplianceTypes" 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 [ComplianceType]
complianceTypes,
            (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
"ResourceId" 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
resourceId,
            (Key
"ResourceType" 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
resourceType
          ]
      )

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

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

-- |
--
-- /See:/ 'newDescribeComplianceByResourceResponse' smart constructor.
data DescribeComplianceByResourceResponse = DescribeComplianceByResourceResponse'
  { -- | Indicates whether the specified Amazon Web Services resource complies
    -- with all of the Config rules that evaluate it.
    DescribeComplianceByResourceResponse
-> Maybe [ComplianceByResource]
complianceByResources :: Prelude.Maybe [ComplianceByResource],
    -- | The string that you use in a subsequent request to get the next page of
    -- results in a paginated response.
    DescribeComplianceByResourceResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeComplianceByResourceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeComplianceByResourceResponse
-> DescribeComplianceByResourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeComplianceByResourceResponse
-> DescribeComplianceByResourceResponse -> Bool
$c/= :: DescribeComplianceByResourceResponse
-> DescribeComplianceByResourceResponse -> Bool
== :: DescribeComplianceByResourceResponse
-> DescribeComplianceByResourceResponse -> Bool
$c== :: DescribeComplianceByResourceResponse
-> DescribeComplianceByResourceResponse -> Bool
Prelude.Eq, ReadPrec [DescribeComplianceByResourceResponse]
ReadPrec DescribeComplianceByResourceResponse
Int -> ReadS DescribeComplianceByResourceResponse
ReadS [DescribeComplianceByResourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeComplianceByResourceResponse]
$creadListPrec :: ReadPrec [DescribeComplianceByResourceResponse]
readPrec :: ReadPrec DescribeComplianceByResourceResponse
$creadPrec :: ReadPrec DescribeComplianceByResourceResponse
readList :: ReadS [DescribeComplianceByResourceResponse]
$creadList :: ReadS [DescribeComplianceByResourceResponse]
readsPrec :: Int -> ReadS DescribeComplianceByResourceResponse
$creadsPrec :: Int -> ReadS DescribeComplianceByResourceResponse
Prelude.Read, Int -> DescribeComplianceByResourceResponse -> ShowS
[DescribeComplianceByResourceResponse] -> ShowS
DescribeComplianceByResourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeComplianceByResourceResponse] -> ShowS
$cshowList :: [DescribeComplianceByResourceResponse] -> ShowS
show :: DescribeComplianceByResourceResponse -> String
$cshow :: DescribeComplianceByResourceResponse -> String
showsPrec :: Int -> DescribeComplianceByResourceResponse -> ShowS
$cshowsPrec :: Int -> DescribeComplianceByResourceResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeComplianceByResourceResponse x
-> DescribeComplianceByResourceResponse
forall x.
DescribeComplianceByResourceResponse
-> Rep DescribeComplianceByResourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeComplianceByResourceResponse x
-> DescribeComplianceByResourceResponse
$cfrom :: forall x.
DescribeComplianceByResourceResponse
-> Rep DescribeComplianceByResourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeComplianceByResourceResponse' 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:
--
-- 'complianceByResources', 'describeComplianceByResourceResponse_complianceByResources' - Indicates whether the specified Amazon Web Services resource complies
-- with all of the Config rules that evaluate it.
--
-- 'nextToken', 'describeComplianceByResourceResponse_nextToken' - The string that you use in a subsequent request to get the next page of
-- results in a paginated response.
--
-- 'httpStatus', 'describeComplianceByResourceResponse_httpStatus' - The response's http status code.
newDescribeComplianceByResourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeComplianceByResourceResponse
newDescribeComplianceByResourceResponse :: Int -> DescribeComplianceByResourceResponse
newDescribeComplianceByResourceResponse Int
pHttpStatus_ =
  DescribeComplianceByResourceResponse'
    { $sel:complianceByResources:DescribeComplianceByResourceResponse' :: Maybe [ComplianceByResource]
complianceByResources =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeComplianceByResourceResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeComplianceByResourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Indicates whether the specified Amazon Web Services resource complies
-- with all of the Config rules that evaluate it.
describeComplianceByResourceResponse_complianceByResources :: Lens.Lens' DescribeComplianceByResourceResponse (Prelude.Maybe [ComplianceByResource])
describeComplianceByResourceResponse_complianceByResources :: Lens'
  DescribeComplianceByResourceResponse (Maybe [ComplianceByResource])
describeComplianceByResourceResponse_complianceByResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComplianceByResourceResponse' {Maybe [ComplianceByResource]
complianceByResources :: Maybe [ComplianceByResource]
$sel:complianceByResources:DescribeComplianceByResourceResponse' :: DescribeComplianceByResourceResponse
-> Maybe [ComplianceByResource]
complianceByResources} -> Maybe [ComplianceByResource]
complianceByResources) (\s :: DescribeComplianceByResourceResponse
s@DescribeComplianceByResourceResponse' {} Maybe [ComplianceByResource]
a -> DescribeComplianceByResourceResponse
s {$sel:complianceByResources:DescribeComplianceByResourceResponse' :: Maybe [ComplianceByResource]
complianceByResources = Maybe [ComplianceByResource]
a} :: DescribeComplianceByResourceResponse) 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 string that you use in a subsequent request to get the next page of
-- results in a paginated response.
describeComplianceByResourceResponse_nextToken :: Lens.Lens' DescribeComplianceByResourceResponse (Prelude.Maybe Prelude.Text)
describeComplianceByResourceResponse_nextToken :: Lens' DescribeComplianceByResourceResponse (Maybe Text)
describeComplianceByResourceResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeComplianceByResourceResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeComplianceByResourceResponse' :: DescribeComplianceByResourceResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeComplianceByResourceResponse
s@DescribeComplianceByResourceResponse' {} Maybe Text
a -> DescribeComplianceByResourceResponse
s {$sel:nextToken:DescribeComplianceByResourceResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeComplianceByResourceResponse)

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

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