{-# 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.ECR.BatchGetRepositoryScanningConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets the scanning configuration for one or more repositories.
module Amazonka.ECR.BatchGetRepositoryScanningConfiguration
  ( -- * Creating a Request
    BatchGetRepositoryScanningConfiguration (..),
    newBatchGetRepositoryScanningConfiguration,

    -- * Request Lenses
    batchGetRepositoryScanningConfiguration_repositoryNames,

    -- * Destructuring the Response
    BatchGetRepositoryScanningConfigurationResponse (..),
    newBatchGetRepositoryScanningConfigurationResponse,

    -- * Response Lenses
    batchGetRepositoryScanningConfigurationResponse_failures,
    batchGetRepositoryScanningConfigurationResponse_scanningConfigurations,
    batchGetRepositoryScanningConfigurationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newBatchGetRepositoryScanningConfiguration' smart constructor.
data BatchGetRepositoryScanningConfiguration = BatchGetRepositoryScanningConfiguration'
  { -- | One or more repository names to get the scanning configuration for.
    BatchGetRepositoryScanningConfiguration -> NonEmpty Text
repositoryNames :: Prelude.NonEmpty Prelude.Text
  }
  deriving (BatchGetRepositoryScanningConfiguration
-> BatchGetRepositoryScanningConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetRepositoryScanningConfiguration
-> BatchGetRepositoryScanningConfiguration -> Bool
$c/= :: BatchGetRepositoryScanningConfiguration
-> BatchGetRepositoryScanningConfiguration -> Bool
== :: BatchGetRepositoryScanningConfiguration
-> BatchGetRepositoryScanningConfiguration -> Bool
$c== :: BatchGetRepositoryScanningConfiguration
-> BatchGetRepositoryScanningConfiguration -> Bool
Prelude.Eq, ReadPrec [BatchGetRepositoryScanningConfiguration]
ReadPrec BatchGetRepositoryScanningConfiguration
Int -> ReadS BatchGetRepositoryScanningConfiguration
ReadS [BatchGetRepositoryScanningConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetRepositoryScanningConfiguration]
$creadListPrec :: ReadPrec [BatchGetRepositoryScanningConfiguration]
readPrec :: ReadPrec BatchGetRepositoryScanningConfiguration
$creadPrec :: ReadPrec BatchGetRepositoryScanningConfiguration
readList :: ReadS [BatchGetRepositoryScanningConfiguration]
$creadList :: ReadS [BatchGetRepositoryScanningConfiguration]
readsPrec :: Int -> ReadS BatchGetRepositoryScanningConfiguration
$creadsPrec :: Int -> ReadS BatchGetRepositoryScanningConfiguration
Prelude.Read, Int -> BatchGetRepositoryScanningConfiguration -> ShowS
[BatchGetRepositoryScanningConfiguration] -> ShowS
BatchGetRepositoryScanningConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetRepositoryScanningConfiguration] -> ShowS
$cshowList :: [BatchGetRepositoryScanningConfiguration] -> ShowS
show :: BatchGetRepositoryScanningConfiguration -> String
$cshow :: BatchGetRepositoryScanningConfiguration -> String
showsPrec :: Int -> BatchGetRepositoryScanningConfiguration -> ShowS
$cshowsPrec :: Int -> BatchGetRepositoryScanningConfiguration -> ShowS
Prelude.Show, forall x.
Rep BatchGetRepositoryScanningConfiguration x
-> BatchGetRepositoryScanningConfiguration
forall x.
BatchGetRepositoryScanningConfiguration
-> Rep BatchGetRepositoryScanningConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetRepositoryScanningConfiguration x
-> BatchGetRepositoryScanningConfiguration
$cfrom :: forall x.
BatchGetRepositoryScanningConfiguration
-> Rep BatchGetRepositoryScanningConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetRepositoryScanningConfiguration' 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:
--
-- 'repositoryNames', 'batchGetRepositoryScanningConfiguration_repositoryNames' - One or more repository names to get the scanning configuration for.
newBatchGetRepositoryScanningConfiguration ::
  -- | 'repositoryNames'
  Prelude.NonEmpty Prelude.Text ->
  BatchGetRepositoryScanningConfiguration
newBatchGetRepositoryScanningConfiguration :: NonEmpty Text -> BatchGetRepositoryScanningConfiguration
newBatchGetRepositoryScanningConfiguration
  NonEmpty Text
pRepositoryNames_ =
    BatchGetRepositoryScanningConfiguration'
      { $sel:repositoryNames:BatchGetRepositoryScanningConfiguration' :: NonEmpty Text
repositoryNames =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
            forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pRepositoryNames_
      }

-- | One or more repository names to get the scanning configuration for.
batchGetRepositoryScanningConfiguration_repositoryNames :: Lens.Lens' BatchGetRepositoryScanningConfiguration (Prelude.NonEmpty Prelude.Text)
batchGetRepositoryScanningConfiguration_repositoryNames :: Lens' BatchGetRepositoryScanningConfiguration (NonEmpty Text)
batchGetRepositoryScanningConfiguration_repositoryNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetRepositoryScanningConfiguration' {NonEmpty Text
repositoryNames :: NonEmpty Text
$sel:repositoryNames:BatchGetRepositoryScanningConfiguration' :: BatchGetRepositoryScanningConfiguration -> NonEmpty Text
repositoryNames} -> NonEmpty Text
repositoryNames) (\s :: BatchGetRepositoryScanningConfiguration
s@BatchGetRepositoryScanningConfiguration' {} NonEmpty Text
a -> BatchGetRepositoryScanningConfiguration
s {$sel:repositoryNames:BatchGetRepositoryScanningConfiguration' :: NonEmpty Text
repositoryNames = NonEmpty Text
a} :: BatchGetRepositoryScanningConfiguration) 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
  Core.AWSRequest
    BatchGetRepositoryScanningConfiguration
  where
  type
    AWSResponse
      BatchGetRepositoryScanningConfiguration =
      BatchGetRepositoryScanningConfigurationResponse
  request :: (Service -> Service)
-> BatchGetRepositoryScanningConfiguration
-> Request BatchGetRepositoryScanningConfiguration
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 BatchGetRepositoryScanningConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse BatchGetRepositoryScanningConfiguration)))
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 [RepositoryScanningConfigurationFailure]
-> Maybe [RepositoryScanningConfiguration]
-> Int
-> BatchGetRepositoryScanningConfigurationResponse
BatchGetRepositoryScanningConfigurationResponse'
            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
"failures" 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
"scanningConfigurations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    BatchGetRepositoryScanningConfiguration
  where
  hashWithSalt :: Int -> BatchGetRepositoryScanningConfiguration -> Int
hashWithSalt
    Int
_salt
    BatchGetRepositoryScanningConfiguration' {NonEmpty Text
repositoryNames :: NonEmpty Text
$sel:repositoryNames:BatchGetRepositoryScanningConfiguration' :: BatchGetRepositoryScanningConfiguration -> NonEmpty Text
..} =
      Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
repositoryNames

instance
  Prelude.NFData
    BatchGetRepositoryScanningConfiguration
  where
  rnf :: BatchGetRepositoryScanningConfiguration -> ()
rnf BatchGetRepositoryScanningConfiguration' {NonEmpty Text
repositoryNames :: NonEmpty Text
$sel:repositoryNames:BatchGetRepositoryScanningConfiguration' :: BatchGetRepositoryScanningConfiguration -> NonEmpty Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
repositoryNames

instance
  Data.ToHeaders
    BatchGetRepositoryScanningConfiguration
  where
  toHeaders :: BatchGetRepositoryScanningConfiguration -> 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
"AmazonEC2ContainerRegistry_V20150921.BatchGetRepositoryScanningConfiguration" ::
                          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
    BatchGetRepositoryScanningConfiguration
  where
  toJSON :: BatchGetRepositoryScanningConfiguration -> Value
toJSON BatchGetRepositoryScanningConfiguration' {NonEmpty Text
repositoryNames :: NonEmpty Text
$sel:repositoryNames:BatchGetRepositoryScanningConfiguration' :: BatchGetRepositoryScanningConfiguration -> NonEmpty Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"repositoryNames" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
repositoryNames)
          ]
      )

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

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

-- | /See:/ 'newBatchGetRepositoryScanningConfigurationResponse' smart constructor.
data BatchGetRepositoryScanningConfigurationResponse = BatchGetRepositoryScanningConfigurationResponse'
  { -- | Any failures associated with the call.
    BatchGetRepositoryScanningConfigurationResponse
-> Maybe [RepositoryScanningConfigurationFailure]
failures :: Prelude.Maybe [RepositoryScanningConfigurationFailure],
    -- | The scanning configuration for the requested repositories.
    BatchGetRepositoryScanningConfigurationResponse
-> Maybe [RepositoryScanningConfiguration]
scanningConfigurations :: Prelude.Maybe [RepositoryScanningConfiguration],
    -- | The response's http status code.
    BatchGetRepositoryScanningConfigurationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchGetRepositoryScanningConfigurationResponse
-> BatchGetRepositoryScanningConfigurationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetRepositoryScanningConfigurationResponse
-> BatchGetRepositoryScanningConfigurationResponse -> Bool
$c/= :: BatchGetRepositoryScanningConfigurationResponse
-> BatchGetRepositoryScanningConfigurationResponse -> Bool
== :: BatchGetRepositoryScanningConfigurationResponse
-> BatchGetRepositoryScanningConfigurationResponse -> Bool
$c== :: BatchGetRepositoryScanningConfigurationResponse
-> BatchGetRepositoryScanningConfigurationResponse -> Bool
Prelude.Eq, ReadPrec [BatchGetRepositoryScanningConfigurationResponse]
ReadPrec BatchGetRepositoryScanningConfigurationResponse
Int -> ReadS BatchGetRepositoryScanningConfigurationResponse
ReadS [BatchGetRepositoryScanningConfigurationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetRepositoryScanningConfigurationResponse]
$creadListPrec :: ReadPrec [BatchGetRepositoryScanningConfigurationResponse]
readPrec :: ReadPrec BatchGetRepositoryScanningConfigurationResponse
$creadPrec :: ReadPrec BatchGetRepositoryScanningConfigurationResponse
readList :: ReadS [BatchGetRepositoryScanningConfigurationResponse]
$creadList :: ReadS [BatchGetRepositoryScanningConfigurationResponse]
readsPrec :: Int -> ReadS BatchGetRepositoryScanningConfigurationResponse
$creadsPrec :: Int -> ReadS BatchGetRepositoryScanningConfigurationResponse
Prelude.Read, Int -> BatchGetRepositoryScanningConfigurationResponse -> ShowS
[BatchGetRepositoryScanningConfigurationResponse] -> ShowS
BatchGetRepositoryScanningConfigurationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetRepositoryScanningConfigurationResponse] -> ShowS
$cshowList :: [BatchGetRepositoryScanningConfigurationResponse] -> ShowS
show :: BatchGetRepositoryScanningConfigurationResponse -> String
$cshow :: BatchGetRepositoryScanningConfigurationResponse -> String
showsPrec :: Int -> BatchGetRepositoryScanningConfigurationResponse -> ShowS
$cshowsPrec :: Int -> BatchGetRepositoryScanningConfigurationResponse -> ShowS
Prelude.Show, forall x.
Rep BatchGetRepositoryScanningConfigurationResponse x
-> BatchGetRepositoryScanningConfigurationResponse
forall x.
BatchGetRepositoryScanningConfigurationResponse
-> Rep BatchGetRepositoryScanningConfigurationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetRepositoryScanningConfigurationResponse x
-> BatchGetRepositoryScanningConfigurationResponse
$cfrom :: forall x.
BatchGetRepositoryScanningConfigurationResponse
-> Rep BatchGetRepositoryScanningConfigurationResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetRepositoryScanningConfigurationResponse' 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:
--
-- 'failures', 'batchGetRepositoryScanningConfigurationResponse_failures' - Any failures associated with the call.
--
-- 'scanningConfigurations', 'batchGetRepositoryScanningConfigurationResponse_scanningConfigurations' - The scanning configuration for the requested repositories.
--
-- 'httpStatus', 'batchGetRepositoryScanningConfigurationResponse_httpStatus' - The response's http status code.
newBatchGetRepositoryScanningConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchGetRepositoryScanningConfigurationResponse
newBatchGetRepositoryScanningConfigurationResponse :: Int -> BatchGetRepositoryScanningConfigurationResponse
newBatchGetRepositoryScanningConfigurationResponse
  Int
pHttpStatus_ =
    BatchGetRepositoryScanningConfigurationResponse'
      { $sel:failures:BatchGetRepositoryScanningConfigurationResponse' :: Maybe [RepositoryScanningConfigurationFailure]
failures =
          forall a. Maybe a
Prelude.Nothing,
        $sel:scanningConfigurations:BatchGetRepositoryScanningConfigurationResponse' :: Maybe [RepositoryScanningConfiguration]
scanningConfigurations =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:BatchGetRepositoryScanningConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Any failures associated with the call.
batchGetRepositoryScanningConfigurationResponse_failures :: Lens.Lens' BatchGetRepositoryScanningConfigurationResponse (Prelude.Maybe [RepositoryScanningConfigurationFailure])
batchGetRepositoryScanningConfigurationResponse_failures :: Lens'
  BatchGetRepositoryScanningConfigurationResponse
  (Maybe [RepositoryScanningConfigurationFailure])
batchGetRepositoryScanningConfigurationResponse_failures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetRepositoryScanningConfigurationResponse' {Maybe [RepositoryScanningConfigurationFailure]
failures :: Maybe [RepositoryScanningConfigurationFailure]
$sel:failures:BatchGetRepositoryScanningConfigurationResponse' :: BatchGetRepositoryScanningConfigurationResponse
-> Maybe [RepositoryScanningConfigurationFailure]
failures} -> Maybe [RepositoryScanningConfigurationFailure]
failures) (\s :: BatchGetRepositoryScanningConfigurationResponse
s@BatchGetRepositoryScanningConfigurationResponse' {} Maybe [RepositoryScanningConfigurationFailure]
a -> BatchGetRepositoryScanningConfigurationResponse
s {$sel:failures:BatchGetRepositoryScanningConfigurationResponse' :: Maybe [RepositoryScanningConfigurationFailure]
failures = Maybe [RepositoryScanningConfigurationFailure]
a} :: BatchGetRepositoryScanningConfigurationResponse) 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 scanning configuration for the requested repositories.
batchGetRepositoryScanningConfigurationResponse_scanningConfigurations :: Lens.Lens' BatchGetRepositoryScanningConfigurationResponse (Prelude.Maybe [RepositoryScanningConfiguration])
batchGetRepositoryScanningConfigurationResponse_scanningConfigurations :: Lens'
  BatchGetRepositoryScanningConfigurationResponse
  (Maybe [RepositoryScanningConfiguration])
batchGetRepositoryScanningConfigurationResponse_scanningConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetRepositoryScanningConfigurationResponse' {Maybe [RepositoryScanningConfiguration]
scanningConfigurations :: Maybe [RepositoryScanningConfiguration]
$sel:scanningConfigurations:BatchGetRepositoryScanningConfigurationResponse' :: BatchGetRepositoryScanningConfigurationResponse
-> Maybe [RepositoryScanningConfiguration]
scanningConfigurations} -> Maybe [RepositoryScanningConfiguration]
scanningConfigurations) (\s :: BatchGetRepositoryScanningConfigurationResponse
s@BatchGetRepositoryScanningConfigurationResponse' {} Maybe [RepositoryScanningConfiguration]
a -> BatchGetRepositoryScanningConfigurationResponse
s {$sel:scanningConfigurations:BatchGetRepositoryScanningConfigurationResponse' :: Maybe [RepositoryScanningConfiguration]
scanningConfigurations = Maybe [RepositoryScanningConfiguration]
a} :: BatchGetRepositoryScanningConfigurationResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.NFData
    BatchGetRepositoryScanningConfigurationResponse
  where
  rnf :: BatchGetRepositoryScanningConfigurationResponse -> ()
rnf
    BatchGetRepositoryScanningConfigurationResponse' {Int
Maybe [RepositoryScanningConfigurationFailure]
Maybe [RepositoryScanningConfiguration]
httpStatus :: Int
scanningConfigurations :: Maybe [RepositoryScanningConfiguration]
failures :: Maybe [RepositoryScanningConfigurationFailure]
$sel:httpStatus:BatchGetRepositoryScanningConfigurationResponse' :: BatchGetRepositoryScanningConfigurationResponse -> Int
$sel:scanningConfigurations:BatchGetRepositoryScanningConfigurationResponse' :: BatchGetRepositoryScanningConfigurationResponse
-> Maybe [RepositoryScanningConfiguration]
$sel:failures:BatchGetRepositoryScanningConfigurationResponse' :: BatchGetRepositoryScanningConfigurationResponse
-> Maybe [RepositoryScanningConfigurationFailure]
..} =
      forall a. NFData a => a -> ()
Prelude.rnf Maybe [RepositoryScanningConfigurationFailure]
failures
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [RepositoryScanningConfiguration]
scanningConfigurations
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus