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

    -- * Request Lenses
    cancelFindingsReport_reportId,

    -- * Destructuring the Response
    CancelFindingsReportResponse (..),
    newCancelFindingsReportResponse,

    -- * Response Lenses
    cancelFindingsReportResponse_httpStatus,
    cancelFindingsReportResponse_reportId,
  )
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:/ 'newCancelFindingsReport' smart constructor.
data CancelFindingsReport = CancelFindingsReport'
  { -- | The ID of the report to be canceled.
    CancelFindingsReport -> Text
reportId :: Prelude.Text
  }
  deriving (CancelFindingsReport -> CancelFindingsReport -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelFindingsReport -> CancelFindingsReport -> Bool
$c/= :: CancelFindingsReport -> CancelFindingsReport -> Bool
== :: CancelFindingsReport -> CancelFindingsReport -> Bool
$c== :: CancelFindingsReport -> CancelFindingsReport -> Bool
Prelude.Eq, ReadPrec [CancelFindingsReport]
ReadPrec CancelFindingsReport
Int -> ReadS CancelFindingsReport
ReadS [CancelFindingsReport]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelFindingsReport]
$creadListPrec :: ReadPrec [CancelFindingsReport]
readPrec :: ReadPrec CancelFindingsReport
$creadPrec :: ReadPrec CancelFindingsReport
readList :: ReadS [CancelFindingsReport]
$creadList :: ReadS [CancelFindingsReport]
readsPrec :: Int -> ReadS CancelFindingsReport
$creadsPrec :: Int -> ReadS CancelFindingsReport
Prelude.Read, Int -> CancelFindingsReport -> ShowS
[CancelFindingsReport] -> ShowS
CancelFindingsReport -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelFindingsReport] -> ShowS
$cshowList :: [CancelFindingsReport] -> ShowS
show :: CancelFindingsReport -> String
$cshow :: CancelFindingsReport -> String
showsPrec :: Int -> CancelFindingsReport -> ShowS
$cshowsPrec :: Int -> CancelFindingsReport -> ShowS
Prelude.Show, forall x. Rep CancelFindingsReport x -> CancelFindingsReport
forall x. CancelFindingsReport -> Rep CancelFindingsReport x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelFindingsReport x -> CancelFindingsReport
$cfrom :: forall x. CancelFindingsReport -> Rep CancelFindingsReport x
Prelude.Generic)

-- |
-- Create a value of 'CancelFindingsReport' 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', 'cancelFindingsReport_reportId' - The ID of the report to be canceled.
newCancelFindingsReport ::
  -- | 'reportId'
  Prelude.Text ->
  CancelFindingsReport
newCancelFindingsReport :: Text -> CancelFindingsReport
newCancelFindingsReport Text
pReportId_ =
  CancelFindingsReport' {$sel:reportId:CancelFindingsReport' :: Text
reportId = Text
pReportId_}

-- | The ID of the report to be canceled.
cancelFindingsReport_reportId :: Lens.Lens' CancelFindingsReport Prelude.Text
cancelFindingsReport_reportId :: Lens' CancelFindingsReport Text
cancelFindingsReport_reportId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelFindingsReport' {Text
reportId :: Text
$sel:reportId:CancelFindingsReport' :: CancelFindingsReport -> Text
reportId} -> Text
reportId) (\s :: CancelFindingsReport
s@CancelFindingsReport' {} Text
a -> CancelFindingsReport
s {$sel:reportId:CancelFindingsReport' :: Text
reportId = Text
a} :: CancelFindingsReport)

instance Core.AWSRequest CancelFindingsReport where
  type
    AWSResponse CancelFindingsReport =
      CancelFindingsReportResponse
  request :: (Service -> Service)
-> CancelFindingsReport -> Request CancelFindingsReport
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 CancelFindingsReport
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CancelFindingsReport)))
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 ->
          Int -> Text -> CancelFindingsReportResponse
CancelFindingsReportResponse'
            forall (f :: * -> *) a b. Functor 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
"reportId")
      )

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

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

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

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

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

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

-- |
-- Create a value of 'CancelFindingsReportResponse' 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:
--
-- 'httpStatus', 'cancelFindingsReportResponse_httpStatus' - The response's http status code.
--
-- 'reportId', 'cancelFindingsReportResponse_reportId' - The ID of the canceled report.
newCancelFindingsReportResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'reportId'
  Prelude.Text ->
  CancelFindingsReportResponse
newCancelFindingsReportResponse :: Int -> Text -> CancelFindingsReportResponse
newCancelFindingsReportResponse
  Int
pHttpStatus_
  Text
pReportId_ =
    CancelFindingsReportResponse'
      { $sel:httpStatus:CancelFindingsReportResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:reportId:CancelFindingsReportResponse' :: Text
reportId = Text
pReportId_
      }

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

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

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