{-# 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.Inspector.GetAssessmentReport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Produces an assessment report that includes detailed and comprehensive
-- results of a specified assessment run.
module Amazonka.Inspector.GetAssessmentReport
  ( -- * Creating a Request
    GetAssessmentReport (..),
    newGetAssessmentReport,

    -- * Request Lenses
    getAssessmentReport_assessmentRunArn,
    getAssessmentReport_reportFileFormat,
    getAssessmentReport_reportType,

    -- * Destructuring the Response
    GetAssessmentReportResponse (..),
    newGetAssessmentReportResponse,

    -- * Response Lenses
    getAssessmentReportResponse_url,
    getAssessmentReportResponse_httpStatus,
    getAssessmentReportResponse_status,
  )
where

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

-- | /See:/ 'newGetAssessmentReport' smart constructor.
data GetAssessmentReport = GetAssessmentReport'
  { -- | The ARN that specifies the assessment run for which you want to generate
    -- a report.
    GetAssessmentReport -> Text
assessmentRunArn :: Prelude.Text,
    -- | Specifies the file format (html or pdf) of the assessment report that
    -- you want to generate.
    GetAssessmentReport -> ReportFileFormat
reportFileFormat :: ReportFileFormat,
    -- | Specifies the type of the assessment report that you want to generate.
    -- There are two types of assessment reports: a finding report and a full
    -- report. For more information, see
    -- <https://docs.aws.amazon.com/inspector/latest/userguide/inspector_reports.html Assessment Reports>.
    GetAssessmentReport -> ReportType
reportType :: ReportType
  }
  deriving (GetAssessmentReport -> GetAssessmentReport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAssessmentReport -> GetAssessmentReport -> Bool
$c/= :: GetAssessmentReport -> GetAssessmentReport -> Bool
== :: GetAssessmentReport -> GetAssessmentReport -> Bool
$c== :: GetAssessmentReport -> GetAssessmentReport -> Bool
Prelude.Eq, ReadPrec [GetAssessmentReport]
ReadPrec GetAssessmentReport
Int -> ReadS GetAssessmentReport
ReadS [GetAssessmentReport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAssessmentReport]
$creadListPrec :: ReadPrec [GetAssessmentReport]
readPrec :: ReadPrec GetAssessmentReport
$creadPrec :: ReadPrec GetAssessmentReport
readList :: ReadS [GetAssessmentReport]
$creadList :: ReadS [GetAssessmentReport]
readsPrec :: Int -> ReadS GetAssessmentReport
$creadsPrec :: Int -> ReadS GetAssessmentReport
Prelude.Read, Int -> GetAssessmentReport -> ShowS
[GetAssessmentReport] -> ShowS
GetAssessmentReport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAssessmentReport] -> ShowS
$cshowList :: [GetAssessmentReport] -> ShowS
show :: GetAssessmentReport -> String
$cshow :: GetAssessmentReport -> String
showsPrec :: Int -> GetAssessmentReport -> ShowS
$cshowsPrec :: Int -> GetAssessmentReport -> ShowS
Prelude.Show, forall x. Rep GetAssessmentReport x -> GetAssessmentReport
forall x. GetAssessmentReport -> Rep GetAssessmentReport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAssessmentReport x -> GetAssessmentReport
$cfrom :: forall x. GetAssessmentReport -> Rep GetAssessmentReport x
Prelude.Generic)

-- |
-- Create a value of 'GetAssessmentReport' 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:
--
-- 'assessmentRunArn', 'getAssessmentReport_assessmentRunArn' - The ARN that specifies the assessment run for which you want to generate
-- a report.
--
-- 'reportFileFormat', 'getAssessmentReport_reportFileFormat' - Specifies the file format (html or pdf) of the assessment report that
-- you want to generate.
--
-- 'reportType', 'getAssessmentReport_reportType' - Specifies the type of the assessment report that you want to generate.
-- There are two types of assessment reports: a finding report and a full
-- report. For more information, see
-- <https://docs.aws.amazon.com/inspector/latest/userguide/inspector_reports.html Assessment Reports>.
newGetAssessmentReport ::
  -- | 'assessmentRunArn'
  Prelude.Text ->
  -- | 'reportFileFormat'
  ReportFileFormat ->
  -- | 'reportType'
  ReportType ->
  GetAssessmentReport
newGetAssessmentReport :: Text -> ReportFileFormat -> ReportType -> GetAssessmentReport
newGetAssessmentReport
  Text
pAssessmentRunArn_
  ReportFileFormat
pReportFileFormat_
  ReportType
pReportType_ =
    GetAssessmentReport'
      { $sel:assessmentRunArn:GetAssessmentReport' :: Text
assessmentRunArn =
          Text
pAssessmentRunArn_,
        $sel:reportFileFormat:GetAssessmentReport' :: ReportFileFormat
reportFileFormat = ReportFileFormat
pReportFileFormat_,
        $sel:reportType:GetAssessmentReport' :: ReportType
reportType = ReportType
pReportType_
      }

-- | The ARN that specifies the assessment run for which you want to generate
-- a report.
getAssessmentReport_assessmentRunArn :: Lens.Lens' GetAssessmentReport Prelude.Text
getAssessmentReport_assessmentRunArn :: Lens' GetAssessmentReport Text
getAssessmentReport_assessmentRunArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentReport' {Text
assessmentRunArn :: Text
$sel:assessmentRunArn:GetAssessmentReport' :: GetAssessmentReport -> Text
assessmentRunArn} -> Text
assessmentRunArn) (\s :: GetAssessmentReport
s@GetAssessmentReport' {} Text
a -> GetAssessmentReport
s {$sel:assessmentRunArn:GetAssessmentReport' :: Text
assessmentRunArn = Text
a} :: GetAssessmentReport)

-- | Specifies the file format (html or pdf) of the assessment report that
-- you want to generate.
getAssessmentReport_reportFileFormat :: Lens.Lens' GetAssessmentReport ReportFileFormat
getAssessmentReport_reportFileFormat :: Lens' GetAssessmentReport ReportFileFormat
getAssessmentReport_reportFileFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentReport' {ReportFileFormat
reportFileFormat :: ReportFileFormat
$sel:reportFileFormat:GetAssessmentReport' :: GetAssessmentReport -> ReportFileFormat
reportFileFormat} -> ReportFileFormat
reportFileFormat) (\s :: GetAssessmentReport
s@GetAssessmentReport' {} ReportFileFormat
a -> GetAssessmentReport
s {$sel:reportFileFormat:GetAssessmentReport' :: ReportFileFormat
reportFileFormat = ReportFileFormat
a} :: GetAssessmentReport)

-- | Specifies the type of the assessment report that you want to generate.
-- There are two types of assessment reports: a finding report and a full
-- report. For more information, see
-- <https://docs.aws.amazon.com/inspector/latest/userguide/inspector_reports.html Assessment Reports>.
getAssessmentReport_reportType :: Lens.Lens' GetAssessmentReport ReportType
getAssessmentReport_reportType :: Lens' GetAssessmentReport ReportType
getAssessmentReport_reportType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentReport' {ReportType
reportType :: ReportType
$sel:reportType:GetAssessmentReport' :: GetAssessmentReport -> ReportType
reportType} -> ReportType
reportType) (\s :: GetAssessmentReport
s@GetAssessmentReport' {} ReportType
a -> GetAssessmentReport
s {$sel:reportType:GetAssessmentReport' :: ReportType
reportType = ReportType
a} :: GetAssessmentReport)

instance Core.AWSRequest GetAssessmentReport where
  type
    AWSResponse GetAssessmentReport =
      GetAssessmentReportResponse
  request :: (Service -> Service)
-> GetAssessmentReport -> Request GetAssessmentReport
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 GetAssessmentReport
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetAssessmentReport)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> ReportStatus -> GetAssessmentReportResponse
GetAssessmentReportResponse'
            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
"url")
            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
"status")
      )

instance Prelude.Hashable GetAssessmentReport where
  hashWithSalt :: Int -> GetAssessmentReport -> Int
hashWithSalt Int
_salt GetAssessmentReport' {Text
ReportFileFormat
ReportType
reportType :: ReportType
reportFileFormat :: ReportFileFormat
assessmentRunArn :: Text
$sel:reportType:GetAssessmentReport' :: GetAssessmentReport -> ReportType
$sel:reportFileFormat:GetAssessmentReport' :: GetAssessmentReport -> ReportFileFormat
$sel:assessmentRunArn:GetAssessmentReport' :: GetAssessmentReport -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
assessmentRunArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ReportFileFormat
reportFileFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ReportType
reportType

instance Prelude.NFData GetAssessmentReport where
  rnf :: GetAssessmentReport -> ()
rnf GetAssessmentReport' {Text
ReportFileFormat
ReportType
reportType :: ReportType
reportFileFormat :: ReportFileFormat
assessmentRunArn :: Text
$sel:reportType:GetAssessmentReport' :: GetAssessmentReport -> ReportType
$sel:reportFileFormat:GetAssessmentReport' :: GetAssessmentReport -> ReportFileFormat
$sel:assessmentRunArn:GetAssessmentReport' :: GetAssessmentReport -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
assessmentRunArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ReportFileFormat
reportFileFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ReportType
reportType

instance Data.ToHeaders GetAssessmentReport where
  toHeaders :: GetAssessmentReport -> 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
"InspectorService.GetAssessmentReport" ::
                          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 GetAssessmentReport where
  toJSON :: GetAssessmentReport -> Value
toJSON GetAssessmentReport' {Text
ReportFileFormat
ReportType
reportType :: ReportType
reportFileFormat :: ReportFileFormat
assessmentRunArn :: Text
$sel:reportType:GetAssessmentReport' :: GetAssessmentReport -> ReportType
$sel:reportFileFormat:GetAssessmentReport' :: GetAssessmentReport -> ReportFileFormat
$sel:assessmentRunArn:GetAssessmentReport' :: GetAssessmentReport -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"assessmentRunArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
assessmentRunArn),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"reportFileFormat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ReportFileFormat
reportFileFormat),
            forall a. a -> Maybe a
Prelude.Just (Key
"reportType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ReportType
reportType)
          ]
      )

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

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

-- | /See:/ 'newGetAssessmentReportResponse' smart constructor.
data GetAssessmentReportResponse = GetAssessmentReportResponse'
  { -- | Specifies the URL where you can find the generated assessment report.
    -- This parameter is only returned if the report is successfully generated.
    GetAssessmentReportResponse -> Maybe Text
url :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetAssessmentReportResponse -> Int
httpStatus :: Prelude.Int,
    -- | Specifies the status of the request to generate an assessment report.
    GetAssessmentReportResponse -> ReportStatus
status :: ReportStatus
  }
  deriving (GetAssessmentReportResponse -> GetAssessmentReportResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAssessmentReportResponse -> GetAssessmentReportResponse -> Bool
$c/= :: GetAssessmentReportResponse -> GetAssessmentReportResponse -> Bool
== :: GetAssessmentReportResponse -> GetAssessmentReportResponse -> Bool
$c== :: GetAssessmentReportResponse -> GetAssessmentReportResponse -> Bool
Prelude.Eq, ReadPrec [GetAssessmentReportResponse]
ReadPrec GetAssessmentReportResponse
Int -> ReadS GetAssessmentReportResponse
ReadS [GetAssessmentReportResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAssessmentReportResponse]
$creadListPrec :: ReadPrec [GetAssessmentReportResponse]
readPrec :: ReadPrec GetAssessmentReportResponse
$creadPrec :: ReadPrec GetAssessmentReportResponse
readList :: ReadS [GetAssessmentReportResponse]
$creadList :: ReadS [GetAssessmentReportResponse]
readsPrec :: Int -> ReadS GetAssessmentReportResponse
$creadsPrec :: Int -> ReadS GetAssessmentReportResponse
Prelude.Read, Int -> GetAssessmentReportResponse -> ShowS
[GetAssessmentReportResponse] -> ShowS
GetAssessmentReportResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAssessmentReportResponse] -> ShowS
$cshowList :: [GetAssessmentReportResponse] -> ShowS
show :: GetAssessmentReportResponse -> String
$cshow :: GetAssessmentReportResponse -> String
showsPrec :: Int -> GetAssessmentReportResponse -> ShowS
$cshowsPrec :: Int -> GetAssessmentReportResponse -> ShowS
Prelude.Show, forall x.
Rep GetAssessmentReportResponse x -> GetAssessmentReportResponse
forall x.
GetAssessmentReportResponse -> Rep GetAssessmentReportResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAssessmentReportResponse x -> GetAssessmentReportResponse
$cfrom :: forall x.
GetAssessmentReportResponse -> Rep GetAssessmentReportResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAssessmentReportResponse' 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:
--
-- 'url', 'getAssessmentReportResponse_url' - Specifies the URL where you can find the generated assessment report.
-- This parameter is only returned if the report is successfully generated.
--
-- 'httpStatus', 'getAssessmentReportResponse_httpStatus' - The response's http status code.
--
-- 'status', 'getAssessmentReportResponse_status' - Specifies the status of the request to generate an assessment report.
newGetAssessmentReportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'status'
  ReportStatus ->
  GetAssessmentReportResponse
newGetAssessmentReportResponse :: Int -> ReportStatus -> GetAssessmentReportResponse
newGetAssessmentReportResponse Int
pHttpStatus_ ReportStatus
pStatus_ =
  GetAssessmentReportResponse'
    { $sel:url:GetAssessmentReportResponse' :: Maybe Text
url = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetAssessmentReportResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:status:GetAssessmentReportResponse' :: ReportStatus
status = ReportStatus
pStatus_
    }

-- | Specifies the URL where you can find the generated assessment report.
-- This parameter is only returned if the report is successfully generated.
getAssessmentReportResponse_url :: Lens.Lens' GetAssessmentReportResponse (Prelude.Maybe Prelude.Text)
getAssessmentReportResponse_url :: Lens' GetAssessmentReportResponse (Maybe Text)
getAssessmentReportResponse_url = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentReportResponse' {Maybe Text
url :: Maybe Text
$sel:url:GetAssessmentReportResponse' :: GetAssessmentReportResponse -> Maybe Text
url} -> Maybe Text
url) (\s :: GetAssessmentReportResponse
s@GetAssessmentReportResponse' {} Maybe Text
a -> GetAssessmentReportResponse
s {$sel:url:GetAssessmentReportResponse' :: Maybe Text
url = Maybe Text
a} :: GetAssessmentReportResponse)

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

-- | Specifies the status of the request to generate an assessment report.
getAssessmentReportResponse_status :: Lens.Lens' GetAssessmentReportResponse ReportStatus
getAssessmentReportResponse_status :: Lens' GetAssessmentReportResponse ReportStatus
getAssessmentReportResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAssessmentReportResponse' {ReportStatus
status :: ReportStatus
$sel:status:GetAssessmentReportResponse' :: GetAssessmentReportResponse -> ReportStatus
status} -> ReportStatus
status) (\s :: GetAssessmentReportResponse
s@GetAssessmentReportResponse' {} ReportStatus
a -> GetAssessmentReportResponse
s {$sel:status:GetAssessmentReportResponse' :: ReportStatus
status = ReportStatus
a} :: GetAssessmentReportResponse)

instance Prelude.NFData GetAssessmentReportResponse where
  rnf :: GetAssessmentReportResponse -> ()
rnf GetAssessmentReportResponse' {Int
Maybe Text
ReportStatus
status :: ReportStatus
httpStatus :: Int
url :: Maybe Text
$sel:status:GetAssessmentReportResponse' :: GetAssessmentReportResponse -> ReportStatus
$sel:httpStatus:GetAssessmentReportResponse' :: GetAssessmentReportResponse -> Int
$sel:url:GetAssessmentReportResponse' :: GetAssessmentReportResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
url
      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 ReportStatus
status