{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Inspector2.GetFindingsReportStatus
-- 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 status of a findings report.
module Amazonka.Inspector2.GetFindingsReportStatus
  ( -- * Creating a Request
    GetFindingsReportStatus (..),
    newGetFindingsReportStatus,

    -- * Request Lenses
    getFindingsReportStatus_reportId,

    -- * Destructuring the Response
    GetFindingsReportStatusResponse (..),
    newGetFindingsReportStatusResponse,

    -- * Response Lenses
    getFindingsReportStatusResponse_destination,
    getFindingsReportStatusResponse_errorCode,
    getFindingsReportStatusResponse_errorMessage,
    getFindingsReportStatusResponse_filterCriteria,
    getFindingsReportStatusResponse_reportId,
    getFindingsReportStatusResponse_status,
    getFindingsReportStatusResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetFindingsReportStatus' smart constructor.
data GetFindingsReportStatus = GetFindingsReportStatus'
  { -- | The ID of the report to retrieve the status of.
    GetFindingsReportStatus -> Maybe Text
reportId :: Prelude.Maybe Prelude.Text
  }
  deriving (GetFindingsReportStatus -> GetFindingsReportStatus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFindingsReportStatus -> GetFindingsReportStatus -> Bool
$c/= :: GetFindingsReportStatus -> GetFindingsReportStatus -> Bool
== :: GetFindingsReportStatus -> GetFindingsReportStatus -> Bool
$c== :: GetFindingsReportStatus -> GetFindingsReportStatus -> Bool
Prelude.Eq, ReadPrec [GetFindingsReportStatus]
ReadPrec GetFindingsReportStatus
Int -> ReadS GetFindingsReportStatus
ReadS [GetFindingsReportStatus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFindingsReportStatus]
$creadListPrec :: ReadPrec [GetFindingsReportStatus]
readPrec :: ReadPrec GetFindingsReportStatus
$creadPrec :: ReadPrec GetFindingsReportStatus
readList :: ReadS [GetFindingsReportStatus]
$creadList :: ReadS [GetFindingsReportStatus]
readsPrec :: Int -> ReadS GetFindingsReportStatus
$creadsPrec :: Int -> ReadS GetFindingsReportStatus
Prelude.Read, Int -> GetFindingsReportStatus -> ShowS
[GetFindingsReportStatus] -> ShowS
GetFindingsReportStatus -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFindingsReportStatus] -> ShowS
$cshowList :: [GetFindingsReportStatus] -> ShowS
show :: GetFindingsReportStatus -> String
$cshow :: GetFindingsReportStatus -> String
showsPrec :: Int -> GetFindingsReportStatus -> ShowS
$cshowsPrec :: Int -> GetFindingsReportStatus -> ShowS
Prelude.Show, forall x. Rep GetFindingsReportStatus x -> GetFindingsReportStatus
forall x. GetFindingsReportStatus -> Rep GetFindingsReportStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFindingsReportStatus x -> GetFindingsReportStatus
$cfrom :: forall x. GetFindingsReportStatus -> Rep GetFindingsReportStatus x
Prelude.Generic)

-- |
-- Create a value of 'GetFindingsReportStatus' 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:
--
-- 'reportId', 'getFindingsReportStatus_reportId' - The ID of the report to retrieve the status of.
newGetFindingsReportStatus ::
  GetFindingsReportStatus
newGetFindingsReportStatus :: GetFindingsReportStatus
newGetFindingsReportStatus =
  GetFindingsReportStatus'
    { $sel:reportId:GetFindingsReportStatus' :: Maybe Text
reportId =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The ID of the report to retrieve the status of.
getFindingsReportStatus_reportId :: Lens.Lens' GetFindingsReportStatus (Prelude.Maybe Prelude.Text)
getFindingsReportStatus_reportId :: Lens' GetFindingsReportStatus (Maybe Text)
getFindingsReportStatus_reportId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatus' {Maybe Text
reportId :: Maybe Text
$sel:reportId:GetFindingsReportStatus' :: GetFindingsReportStatus -> Maybe Text
reportId} -> Maybe Text
reportId) (\s :: GetFindingsReportStatus
s@GetFindingsReportStatus' {} Maybe Text
a -> GetFindingsReportStatus
s {$sel:reportId:GetFindingsReportStatus' :: Maybe Text
reportId = Maybe Text
a} :: GetFindingsReportStatus)

instance Core.AWSRequest GetFindingsReportStatus where
  type
    AWSResponse GetFindingsReportStatus =
      GetFindingsReportStatusResponse
  request :: (Service -> Service)
-> GetFindingsReportStatus -> Request GetFindingsReportStatus
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 GetFindingsReportStatus
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetFindingsReportStatus)))
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 Destination
-> Maybe ReportingErrorCode
-> Maybe Text
-> Maybe FilterCriteria
-> Maybe Text
-> Maybe ExternalReportStatus
-> Int
-> GetFindingsReportStatusResponse
GetFindingsReportStatusResponse'
            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
"destination")
            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
"errorCode")
            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
"errorMessage")
            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
"filterCriteria")
            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
"reportId")
            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
"status")
            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 GetFindingsReportStatus where
  hashWithSalt :: Int -> GetFindingsReportStatus -> Int
hashWithSalt Int
_salt GetFindingsReportStatus' {Maybe Text
reportId :: Maybe Text
$sel:reportId:GetFindingsReportStatus' :: GetFindingsReportStatus -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reportId

instance Prelude.NFData GetFindingsReportStatus where
  rnf :: GetFindingsReportStatus -> ()
rnf GetFindingsReportStatus' {Maybe Text
reportId :: Maybe Text
$sel:reportId:GetFindingsReportStatus' :: GetFindingsReportStatus -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportId

instance Data.ToHeaders GetFindingsReportStatus where
  toHeaders :: GetFindingsReportStatus -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetFindingsReportStatus where
  toJSON :: GetFindingsReportStatus -> Value
toJSON GetFindingsReportStatus' {Maybe Text
reportId :: Maybe Text
$sel:reportId:GetFindingsReportStatus' :: GetFindingsReportStatus -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"reportId" 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
reportId]
      )

instance Data.ToPath GetFindingsReportStatus where
  toPath :: GetFindingsReportStatus -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/reporting/status/get"

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

-- | /See:/ 'newGetFindingsReportStatusResponse' smart constructor.
data GetFindingsReportStatusResponse = GetFindingsReportStatusResponse'
  { -- | The destination of the report.
    GetFindingsReportStatusResponse -> Maybe Destination
destination :: Prelude.Maybe Destination,
    -- | The error code of the report.
    GetFindingsReportStatusResponse -> Maybe ReportingErrorCode
errorCode :: Prelude.Maybe ReportingErrorCode,
    -- | The error message of the report.
    GetFindingsReportStatusResponse -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | The filter criteria associated with the report.
    GetFindingsReportStatusResponse -> Maybe FilterCriteria
filterCriteria :: Prelude.Maybe FilterCriteria,
    -- | The ID of the report.
    GetFindingsReportStatusResponse -> Maybe Text
reportId :: Prelude.Maybe Prelude.Text,
    -- | The status of the report.
    GetFindingsReportStatusResponse -> Maybe ExternalReportStatus
status :: Prelude.Maybe ExternalReportStatus,
    -- | The response's http status code.
    GetFindingsReportStatusResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetFindingsReportStatusResponse
-> GetFindingsReportStatusResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFindingsReportStatusResponse
-> GetFindingsReportStatusResponse -> Bool
$c/= :: GetFindingsReportStatusResponse
-> GetFindingsReportStatusResponse -> Bool
== :: GetFindingsReportStatusResponse
-> GetFindingsReportStatusResponse -> Bool
$c== :: GetFindingsReportStatusResponse
-> GetFindingsReportStatusResponse -> Bool
Prelude.Eq, ReadPrec [GetFindingsReportStatusResponse]
ReadPrec GetFindingsReportStatusResponse
Int -> ReadS GetFindingsReportStatusResponse
ReadS [GetFindingsReportStatusResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetFindingsReportStatusResponse]
$creadListPrec :: ReadPrec [GetFindingsReportStatusResponse]
readPrec :: ReadPrec GetFindingsReportStatusResponse
$creadPrec :: ReadPrec GetFindingsReportStatusResponse
readList :: ReadS [GetFindingsReportStatusResponse]
$creadList :: ReadS [GetFindingsReportStatusResponse]
readsPrec :: Int -> ReadS GetFindingsReportStatusResponse
$creadsPrec :: Int -> ReadS GetFindingsReportStatusResponse
Prelude.Read, Int -> GetFindingsReportStatusResponse -> ShowS
[GetFindingsReportStatusResponse] -> ShowS
GetFindingsReportStatusResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFindingsReportStatusResponse] -> ShowS
$cshowList :: [GetFindingsReportStatusResponse] -> ShowS
show :: GetFindingsReportStatusResponse -> String
$cshow :: GetFindingsReportStatusResponse -> String
showsPrec :: Int -> GetFindingsReportStatusResponse -> ShowS
$cshowsPrec :: Int -> GetFindingsReportStatusResponse -> ShowS
Prelude.Show, forall x.
Rep GetFindingsReportStatusResponse x
-> GetFindingsReportStatusResponse
forall x.
GetFindingsReportStatusResponse
-> Rep GetFindingsReportStatusResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetFindingsReportStatusResponse x
-> GetFindingsReportStatusResponse
$cfrom :: forall x.
GetFindingsReportStatusResponse
-> Rep GetFindingsReportStatusResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetFindingsReportStatusResponse' 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:
--
-- 'destination', 'getFindingsReportStatusResponse_destination' - The destination of the report.
--
-- 'errorCode', 'getFindingsReportStatusResponse_errorCode' - The error code of the report.
--
-- 'errorMessage', 'getFindingsReportStatusResponse_errorMessage' - The error message of the report.
--
-- 'filterCriteria', 'getFindingsReportStatusResponse_filterCriteria' - The filter criteria associated with the report.
--
-- 'reportId', 'getFindingsReportStatusResponse_reportId' - The ID of the report.
--
-- 'status', 'getFindingsReportStatusResponse_status' - The status of the report.
--
-- 'httpStatus', 'getFindingsReportStatusResponse_httpStatus' - The response's http status code.
newGetFindingsReportStatusResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetFindingsReportStatusResponse
newGetFindingsReportStatusResponse :: Int -> GetFindingsReportStatusResponse
newGetFindingsReportStatusResponse Int
pHttpStatus_ =
  GetFindingsReportStatusResponse'
    { $sel:destination:GetFindingsReportStatusResponse' :: Maybe Destination
destination =
        forall a. Maybe a
Prelude.Nothing,
      $sel:errorCode:GetFindingsReportStatusResponse' :: Maybe ReportingErrorCode
errorCode = forall a. Maybe a
Prelude.Nothing,
      $sel:errorMessage:GetFindingsReportStatusResponse' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:filterCriteria:GetFindingsReportStatusResponse' :: Maybe FilterCriteria
filterCriteria = forall a. Maybe a
Prelude.Nothing,
      $sel:reportId:GetFindingsReportStatusResponse' :: Maybe Text
reportId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:GetFindingsReportStatusResponse' :: Maybe ExternalReportStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetFindingsReportStatusResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The destination of the report.
getFindingsReportStatusResponse_destination :: Lens.Lens' GetFindingsReportStatusResponse (Prelude.Maybe Destination)
getFindingsReportStatusResponse_destination :: Lens' GetFindingsReportStatusResponse (Maybe Destination)
getFindingsReportStatusResponse_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatusResponse' {Maybe Destination
destination :: Maybe Destination
$sel:destination:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe Destination
destination} -> Maybe Destination
destination) (\s :: GetFindingsReportStatusResponse
s@GetFindingsReportStatusResponse' {} Maybe Destination
a -> GetFindingsReportStatusResponse
s {$sel:destination:GetFindingsReportStatusResponse' :: Maybe Destination
destination = Maybe Destination
a} :: GetFindingsReportStatusResponse)

-- | The error code of the report.
getFindingsReportStatusResponse_errorCode :: Lens.Lens' GetFindingsReportStatusResponse (Prelude.Maybe ReportingErrorCode)
getFindingsReportStatusResponse_errorCode :: Lens' GetFindingsReportStatusResponse (Maybe ReportingErrorCode)
getFindingsReportStatusResponse_errorCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatusResponse' {Maybe ReportingErrorCode
errorCode :: Maybe ReportingErrorCode
$sel:errorCode:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe ReportingErrorCode
errorCode} -> Maybe ReportingErrorCode
errorCode) (\s :: GetFindingsReportStatusResponse
s@GetFindingsReportStatusResponse' {} Maybe ReportingErrorCode
a -> GetFindingsReportStatusResponse
s {$sel:errorCode:GetFindingsReportStatusResponse' :: Maybe ReportingErrorCode
errorCode = Maybe ReportingErrorCode
a} :: GetFindingsReportStatusResponse)

-- | The error message of the report.
getFindingsReportStatusResponse_errorMessage :: Lens.Lens' GetFindingsReportStatusResponse (Prelude.Maybe Prelude.Text)
getFindingsReportStatusResponse_errorMessage :: Lens' GetFindingsReportStatusResponse (Maybe Text)
getFindingsReportStatusResponse_errorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatusResponse' {Maybe Text
errorMessage :: Maybe Text
$sel:errorMessage:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe Text
errorMessage} -> Maybe Text
errorMessage) (\s :: GetFindingsReportStatusResponse
s@GetFindingsReportStatusResponse' {} Maybe Text
a -> GetFindingsReportStatusResponse
s {$sel:errorMessage:GetFindingsReportStatusResponse' :: Maybe Text
errorMessage = Maybe Text
a} :: GetFindingsReportStatusResponse)

-- | The filter criteria associated with the report.
getFindingsReportStatusResponse_filterCriteria :: Lens.Lens' GetFindingsReportStatusResponse (Prelude.Maybe FilterCriteria)
getFindingsReportStatusResponse_filterCriteria :: Lens' GetFindingsReportStatusResponse (Maybe FilterCriteria)
getFindingsReportStatusResponse_filterCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatusResponse' {Maybe FilterCriteria
filterCriteria :: Maybe FilterCriteria
$sel:filterCriteria:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe FilterCriteria
filterCriteria} -> Maybe FilterCriteria
filterCriteria) (\s :: GetFindingsReportStatusResponse
s@GetFindingsReportStatusResponse' {} Maybe FilterCriteria
a -> GetFindingsReportStatusResponse
s {$sel:filterCriteria:GetFindingsReportStatusResponse' :: Maybe FilterCriteria
filterCriteria = Maybe FilterCriteria
a} :: GetFindingsReportStatusResponse)

-- | The ID of the report.
getFindingsReportStatusResponse_reportId :: Lens.Lens' GetFindingsReportStatusResponse (Prelude.Maybe Prelude.Text)
getFindingsReportStatusResponse_reportId :: Lens' GetFindingsReportStatusResponse (Maybe Text)
getFindingsReportStatusResponse_reportId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatusResponse' {Maybe Text
reportId :: Maybe Text
$sel:reportId:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe Text
reportId} -> Maybe Text
reportId) (\s :: GetFindingsReportStatusResponse
s@GetFindingsReportStatusResponse' {} Maybe Text
a -> GetFindingsReportStatusResponse
s {$sel:reportId:GetFindingsReportStatusResponse' :: Maybe Text
reportId = Maybe Text
a} :: GetFindingsReportStatusResponse)

-- | The status of the report.
getFindingsReportStatusResponse_status :: Lens.Lens' GetFindingsReportStatusResponse (Prelude.Maybe ExternalReportStatus)
getFindingsReportStatusResponse_status :: Lens' GetFindingsReportStatusResponse (Maybe ExternalReportStatus)
getFindingsReportStatusResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetFindingsReportStatusResponse' {Maybe ExternalReportStatus
status :: Maybe ExternalReportStatus
$sel:status:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe ExternalReportStatus
status} -> Maybe ExternalReportStatus
status) (\s :: GetFindingsReportStatusResponse
s@GetFindingsReportStatusResponse' {} Maybe ExternalReportStatus
a -> GetFindingsReportStatusResponse
s {$sel:status:GetFindingsReportStatusResponse' :: Maybe ExternalReportStatus
status = Maybe ExternalReportStatus
a} :: GetFindingsReportStatusResponse)

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

instance
  Prelude.NFData
    GetFindingsReportStatusResponse
  where
  rnf :: GetFindingsReportStatusResponse -> ()
rnf GetFindingsReportStatusResponse' {Int
Maybe Text
Maybe Destination
Maybe ExternalReportStatus
Maybe ReportingErrorCode
Maybe FilterCriteria
httpStatus :: Int
status :: Maybe ExternalReportStatus
reportId :: Maybe Text
filterCriteria :: Maybe FilterCriteria
errorMessage :: Maybe Text
errorCode :: Maybe ReportingErrorCode
destination :: Maybe Destination
$sel:httpStatus:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Int
$sel:status:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe ExternalReportStatus
$sel:reportId:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe Text
$sel:filterCriteria:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe FilterCriteria
$sel:errorMessage:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe Text
$sel:errorCode:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe ReportingErrorCode
$sel:destination:GetFindingsReportStatusResponse' :: GetFindingsReportStatusResponse -> Maybe Destination
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Destination
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReportingErrorCode
errorCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FilterCriteria
filterCriteria
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExternalReportStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus