{-# 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.CreateFindingsReport
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a finding report.
module Amazonka.Inspector2.CreateFindingsReport
  ( -- * Creating a Request
    CreateFindingsReport (..),
    newCreateFindingsReport,

    -- * Request Lenses
    createFindingsReport_filterCriteria,
    createFindingsReport_reportFormat,
    createFindingsReport_s3Destination,

    -- * Destructuring the Response
    CreateFindingsReportResponse (..),
    newCreateFindingsReportResponse,

    -- * Response Lenses
    createFindingsReportResponse_reportId,
    createFindingsReportResponse_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:/ 'newCreateFindingsReport' smart constructor.
data CreateFindingsReport = CreateFindingsReport'
  { -- | The filter criteria to apply to the results of the finding report.
    CreateFindingsReport -> Maybe FilterCriteria
filterCriteria :: Prelude.Maybe FilterCriteria,
    -- | The format to generate the report in.
    CreateFindingsReport -> ReportFormat
reportFormat :: ReportFormat,
    -- | The Amazon S3 export destination for the report.
    CreateFindingsReport -> Destination
s3Destination :: Destination
  }
  deriving (CreateFindingsReport -> CreateFindingsReport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateFindingsReport -> CreateFindingsReport -> Bool
$c/= :: CreateFindingsReport -> CreateFindingsReport -> Bool
== :: CreateFindingsReport -> CreateFindingsReport -> Bool
$c== :: CreateFindingsReport -> CreateFindingsReport -> Bool
Prelude.Eq, ReadPrec [CreateFindingsReport]
ReadPrec CreateFindingsReport
Int -> ReadS CreateFindingsReport
ReadS [CreateFindingsReport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateFindingsReport]
$creadListPrec :: ReadPrec [CreateFindingsReport]
readPrec :: ReadPrec CreateFindingsReport
$creadPrec :: ReadPrec CreateFindingsReport
readList :: ReadS [CreateFindingsReport]
$creadList :: ReadS [CreateFindingsReport]
readsPrec :: Int -> ReadS CreateFindingsReport
$creadsPrec :: Int -> ReadS CreateFindingsReport
Prelude.Read, Int -> CreateFindingsReport -> ShowS
[CreateFindingsReport] -> ShowS
CreateFindingsReport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateFindingsReport] -> ShowS
$cshowList :: [CreateFindingsReport] -> ShowS
show :: CreateFindingsReport -> String
$cshow :: CreateFindingsReport -> String
showsPrec :: Int -> CreateFindingsReport -> ShowS
$cshowsPrec :: Int -> CreateFindingsReport -> ShowS
Prelude.Show, forall x. Rep CreateFindingsReport x -> CreateFindingsReport
forall x. CreateFindingsReport -> Rep CreateFindingsReport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateFindingsReport x -> CreateFindingsReport
$cfrom :: forall x. CreateFindingsReport -> Rep CreateFindingsReport x
Prelude.Generic)

-- |
-- Create a value of 'CreateFindingsReport' 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:
--
-- 'filterCriteria', 'createFindingsReport_filterCriteria' - The filter criteria to apply to the results of the finding report.
--
-- 'reportFormat', 'createFindingsReport_reportFormat' - The format to generate the report in.
--
-- 's3Destination', 'createFindingsReport_s3Destination' - The Amazon S3 export destination for the report.
newCreateFindingsReport ::
  -- | 'reportFormat'
  ReportFormat ->
  -- | 's3Destination'
  Destination ->
  CreateFindingsReport
newCreateFindingsReport :: ReportFormat -> Destination -> CreateFindingsReport
newCreateFindingsReport
  ReportFormat
pReportFormat_
  Destination
pS3Destination_ =
    CreateFindingsReport'
      { $sel:filterCriteria:CreateFindingsReport' :: Maybe FilterCriteria
filterCriteria =
          forall a. Maybe a
Prelude.Nothing,
        $sel:reportFormat:CreateFindingsReport' :: ReportFormat
reportFormat = ReportFormat
pReportFormat_,
        $sel:s3Destination:CreateFindingsReport' :: Destination
s3Destination = Destination
pS3Destination_
      }

-- | The filter criteria to apply to the results of the finding report.
createFindingsReport_filterCriteria :: Lens.Lens' CreateFindingsReport (Prelude.Maybe FilterCriteria)
createFindingsReport_filterCriteria :: Lens' CreateFindingsReport (Maybe FilterCriteria)
createFindingsReport_filterCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFindingsReport' {Maybe FilterCriteria
filterCriteria :: Maybe FilterCriteria
$sel:filterCriteria:CreateFindingsReport' :: CreateFindingsReport -> Maybe FilterCriteria
filterCriteria} -> Maybe FilterCriteria
filterCriteria) (\s :: CreateFindingsReport
s@CreateFindingsReport' {} Maybe FilterCriteria
a -> CreateFindingsReport
s {$sel:filterCriteria:CreateFindingsReport' :: Maybe FilterCriteria
filterCriteria = Maybe FilterCriteria
a} :: CreateFindingsReport)

-- | The format to generate the report in.
createFindingsReport_reportFormat :: Lens.Lens' CreateFindingsReport ReportFormat
createFindingsReport_reportFormat :: Lens' CreateFindingsReport ReportFormat
createFindingsReport_reportFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFindingsReport' {ReportFormat
reportFormat :: ReportFormat
$sel:reportFormat:CreateFindingsReport' :: CreateFindingsReport -> ReportFormat
reportFormat} -> ReportFormat
reportFormat) (\s :: CreateFindingsReport
s@CreateFindingsReport' {} ReportFormat
a -> CreateFindingsReport
s {$sel:reportFormat:CreateFindingsReport' :: ReportFormat
reportFormat = ReportFormat
a} :: CreateFindingsReport)

-- | The Amazon S3 export destination for the report.
createFindingsReport_s3Destination :: Lens.Lens' CreateFindingsReport Destination
createFindingsReport_s3Destination :: Lens' CreateFindingsReport Destination
createFindingsReport_s3Destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateFindingsReport' {Destination
s3Destination :: Destination
$sel:s3Destination:CreateFindingsReport' :: CreateFindingsReport -> Destination
s3Destination} -> Destination
s3Destination) (\s :: CreateFindingsReport
s@CreateFindingsReport' {} Destination
a -> CreateFindingsReport
s {$sel:s3Destination:CreateFindingsReport' :: Destination
s3Destination = Destination
a} :: CreateFindingsReport)

instance Core.AWSRequest CreateFindingsReport where
  type
    AWSResponse CreateFindingsReport =
      CreateFindingsReportResponse
  request :: (Service -> Service)
-> CreateFindingsReport -> Request CreateFindingsReport
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 CreateFindingsReport
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateFindingsReport)))
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 -> CreateFindingsReportResponse
CreateFindingsReportResponse'
            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
"reportId")
            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 CreateFindingsReport where
  hashWithSalt :: Int -> CreateFindingsReport -> Int
hashWithSalt Int
_salt CreateFindingsReport' {Maybe FilterCriteria
Destination
ReportFormat
s3Destination :: Destination
reportFormat :: ReportFormat
filterCriteria :: Maybe FilterCriteria
$sel:s3Destination:CreateFindingsReport' :: CreateFindingsReport -> Destination
$sel:reportFormat:CreateFindingsReport' :: CreateFindingsReport -> ReportFormat
$sel:filterCriteria:CreateFindingsReport' :: CreateFindingsReport -> Maybe FilterCriteria
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FilterCriteria
filterCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ReportFormat
reportFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Destination
s3Destination

instance Prelude.NFData CreateFindingsReport where
  rnf :: CreateFindingsReport -> ()
rnf CreateFindingsReport' {Maybe FilterCriteria
Destination
ReportFormat
s3Destination :: Destination
reportFormat :: ReportFormat
filterCriteria :: Maybe FilterCriteria
$sel:s3Destination:CreateFindingsReport' :: CreateFindingsReport -> Destination
$sel:reportFormat:CreateFindingsReport' :: CreateFindingsReport -> ReportFormat
$sel:filterCriteria:CreateFindingsReport' :: CreateFindingsReport -> Maybe FilterCriteria
..} =
    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 ReportFormat
reportFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Destination
s3Destination

instance Data.ToHeaders CreateFindingsReport where
  toHeaders :: CreateFindingsReport -> 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 CreateFindingsReport where
  toJSON :: CreateFindingsReport -> Value
toJSON CreateFindingsReport' {Maybe FilterCriteria
Destination
ReportFormat
s3Destination :: Destination
reportFormat :: ReportFormat
filterCriteria :: Maybe FilterCriteria
$sel:s3Destination:CreateFindingsReport' :: CreateFindingsReport -> Destination
$sel:reportFormat:CreateFindingsReport' :: CreateFindingsReport -> ReportFormat
$sel:filterCriteria:CreateFindingsReport' :: CreateFindingsReport -> Maybe FilterCriteria
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"filterCriteria" 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 FilterCriteria
filterCriteria,
            forall a. a -> Maybe a
Prelude.Just (Key
"reportFormat" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ReportFormat
reportFormat),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"s3Destination" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Destination
s3Destination)
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateFindingsReportResponse' 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', 'createFindingsReportResponse_reportId' - The ID of the report.
--
-- 'httpStatus', 'createFindingsReportResponse_httpStatus' - The response's http status code.
newCreateFindingsReportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateFindingsReportResponse
newCreateFindingsReportResponse :: Int -> CreateFindingsReportResponse
newCreateFindingsReportResponse Int
pHttpStatus_ =
  CreateFindingsReportResponse'
    { $sel:reportId:CreateFindingsReportResponse' :: Maybe Text
reportId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateFindingsReportResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData CreateFindingsReportResponse where
  rnf :: CreateFindingsReportResponse -> ()
rnf CreateFindingsReportResponse' {Int
Maybe Text
httpStatus :: Int
reportId :: Maybe Text
$sel:httpStatus:CreateFindingsReportResponse' :: CreateFindingsReportResponse -> Int
$sel:reportId:CreateFindingsReportResponse' :: CreateFindingsReportResponse -> Maybe Text
..} =
    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 Int
httpStatus