{-# 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.Backup.StartReportJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts an on-demand report job for the specified report plan.
module Amazonka.Backup.StartReportJob
  ( -- * Creating a Request
    StartReportJob (..),
    newStartReportJob,

    -- * Request Lenses
    startReportJob_idempotencyToken,
    startReportJob_reportPlanName,

    -- * Destructuring the Response
    StartReportJobResponse (..),
    newStartReportJobResponse,

    -- * Response Lenses
    startReportJobResponse_reportJobId,
    startReportJobResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartReportJob' smart constructor.
data StartReportJob = StartReportJob'
  { -- | A customer-chosen string that you can use to distinguish between
    -- otherwise identical calls to @StartReportJobInput@. Retrying a
    -- successful request with the same idempotency token results in a success
    -- message with no action taken.
    StartReportJob -> Maybe Text
idempotencyToken :: Prelude.Maybe Prelude.Text,
    -- | The unique name of a report plan.
    StartReportJob -> Text
reportPlanName :: Prelude.Text
  }
  deriving (StartReportJob -> StartReportJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartReportJob -> StartReportJob -> Bool
$c/= :: StartReportJob -> StartReportJob -> Bool
== :: StartReportJob -> StartReportJob -> Bool
$c== :: StartReportJob -> StartReportJob -> Bool
Prelude.Eq, ReadPrec [StartReportJob]
ReadPrec StartReportJob
Int -> ReadS StartReportJob
ReadS [StartReportJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartReportJob]
$creadListPrec :: ReadPrec [StartReportJob]
readPrec :: ReadPrec StartReportJob
$creadPrec :: ReadPrec StartReportJob
readList :: ReadS [StartReportJob]
$creadList :: ReadS [StartReportJob]
readsPrec :: Int -> ReadS StartReportJob
$creadsPrec :: Int -> ReadS StartReportJob
Prelude.Read, Int -> StartReportJob -> ShowS
[StartReportJob] -> ShowS
StartReportJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartReportJob] -> ShowS
$cshowList :: [StartReportJob] -> ShowS
show :: StartReportJob -> String
$cshow :: StartReportJob -> String
showsPrec :: Int -> StartReportJob -> ShowS
$cshowsPrec :: Int -> StartReportJob -> ShowS
Prelude.Show, forall x. Rep StartReportJob x -> StartReportJob
forall x. StartReportJob -> Rep StartReportJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartReportJob x -> StartReportJob
$cfrom :: forall x. StartReportJob -> Rep StartReportJob x
Prelude.Generic)

-- |
-- Create a value of 'StartReportJob' 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:
--
-- 'idempotencyToken', 'startReportJob_idempotencyToken' - A customer-chosen string that you can use to distinguish between
-- otherwise identical calls to @StartReportJobInput@. Retrying a
-- successful request with the same idempotency token results in a success
-- message with no action taken.
--
-- 'reportPlanName', 'startReportJob_reportPlanName' - The unique name of a report plan.
newStartReportJob ::
  -- | 'reportPlanName'
  Prelude.Text ->
  StartReportJob
newStartReportJob :: Text -> StartReportJob
newStartReportJob Text
pReportPlanName_ =
  StartReportJob'
    { $sel:idempotencyToken:StartReportJob' :: Maybe Text
idempotencyToken = forall a. Maybe a
Prelude.Nothing,
      $sel:reportPlanName:StartReportJob' :: Text
reportPlanName = Text
pReportPlanName_
    }

-- | A customer-chosen string that you can use to distinguish between
-- otherwise identical calls to @StartReportJobInput@. Retrying a
-- successful request with the same idempotency token results in a success
-- message with no action taken.
startReportJob_idempotencyToken :: Lens.Lens' StartReportJob (Prelude.Maybe Prelude.Text)
startReportJob_idempotencyToken :: Lens' StartReportJob (Maybe Text)
startReportJob_idempotencyToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartReportJob' {Maybe Text
idempotencyToken :: Maybe Text
$sel:idempotencyToken:StartReportJob' :: StartReportJob -> Maybe Text
idempotencyToken} -> Maybe Text
idempotencyToken) (\s :: StartReportJob
s@StartReportJob' {} Maybe Text
a -> StartReportJob
s {$sel:idempotencyToken:StartReportJob' :: Maybe Text
idempotencyToken = Maybe Text
a} :: StartReportJob)

-- | The unique name of a report plan.
startReportJob_reportPlanName :: Lens.Lens' StartReportJob Prelude.Text
startReportJob_reportPlanName :: Lens' StartReportJob Text
startReportJob_reportPlanName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartReportJob' {Text
reportPlanName :: Text
$sel:reportPlanName:StartReportJob' :: StartReportJob -> Text
reportPlanName} -> Text
reportPlanName) (\s :: StartReportJob
s@StartReportJob' {} Text
a -> StartReportJob
s {$sel:reportPlanName:StartReportJob' :: Text
reportPlanName = Text
a} :: StartReportJob)

instance Core.AWSRequest StartReportJob where
  type
    AWSResponse StartReportJob =
      StartReportJobResponse
  request :: (Service -> Service) -> StartReportJob -> Request StartReportJob
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 StartReportJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartReportJob)))
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 -> StartReportJobResponse
StartReportJobResponse'
            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
"ReportJobId")
            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 StartReportJob where
  hashWithSalt :: Int -> StartReportJob -> Int
hashWithSalt Int
_salt StartReportJob' {Maybe Text
Text
reportPlanName :: Text
idempotencyToken :: Maybe Text
$sel:reportPlanName:StartReportJob' :: StartReportJob -> Text
$sel:idempotencyToken:StartReportJob' :: StartReportJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
idempotencyToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
reportPlanName

instance Prelude.NFData StartReportJob where
  rnf :: StartReportJob -> ()
rnf StartReportJob' {Maybe Text
Text
reportPlanName :: Text
idempotencyToken :: Maybe Text
$sel:reportPlanName:StartReportJob' :: StartReportJob -> Text
$sel:idempotencyToken:StartReportJob' :: StartReportJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
idempotencyToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
reportPlanName

instance Data.ToHeaders StartReportJob where
  toHeaders :: StartReportJob -> 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 StartReportJob where
  toJSON :: StartReportJob -> Value
toJSON StartReportJob' {Maybe Text
Text
reportPlanName :: Text
idempotencyToken :: Maybe Text
$sel:reportPlanName:StartReportJob' :: StartReportJob -> Text
$sel:idempotencyToken:StartReportJob' :: StartReportJob -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"IdempotencyToken" 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
idempotencyToken
          ]
      )

instance Data.ToPath StartReportJob where
  toPath :: StartReportJob -> ByteString
toPath StartReportJob' {Maybe Text
Text
reportPlanName :: Text
idempotencyToken :: Maybe Text
$sel:reportPlanName:StartReportJob' :: StartReportJob -> Text
$sel:idempotencyToken:StartReportJob' :: StartReportJob -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/audit/report-jobs/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
reportPlanName]

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

-- | /See:/ 'newStartReportJobResponse' smart constructor.
data StartReportJobResponse = StartReportJobResponse'
  { -- | The identifier of the report job. A unique, randomly generated, Unicode,
    -- UTF-8 encoded string that is at most 1,024 bytes long. The report job ID
    -- cannot be edited.
    StartReportJobResponse -> Maybe Text
reportJobId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartReportJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartReportJobResponse -> StartReportJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartReportJobResponse -> StartReportJobResponse -> Bool
$c/= :: StartReportJobResponse -> StartReportJobResponse -> Bool
== :: StartReportJobResponse -> StartReportJobResponse -> Bool
$c== :: StartReportJobResponse -> StartReportJobResponse -> Bool
Prelude.Eq, ReadPrec [StartReportJobResponse]
ReadPrec StartReportJobResponse
Int -> ReadS StartReportJobResponse
ReadS [StartReportJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartReportJobResponse]
$creadListPrec :: ReadPrec [StartReportJobResponse]
readPrec :: ReadPrec StartReportJobResponse
$creadPrec :: ReadPrec StartReportJobResponse
readList :: ReadS [StartReportJobResponse]
$creadList :: ReadS [StartReportJobResponse]
readsPrec :: Int -> ReadS StartReportJobResponse
$creadsPrec :: Int -> ReadS StartReportJobResponse
Prelude.Read, Int -> StartReportJobResponse -> ShowS
[StartReportJobResponse] -> ShowS
StartReportJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartReportJobResponse] -> ShowS
$cshowList :: [StartReportJobResponse] -> ShowS
show :: StartReportJobResponse -> String
$cshow :: StartReportJobResponse -> String
showsPrec :: Int -> StartReportJobResponse -> ShowS
$cshowsPrec :: Int -> StartReportJobResponse -> ShowS
Prelude.Show, forall x. Rep StartReportJobResponse x -> StartReportJobResponse
forall x. StartReportJobResponse -> Rep StartReportJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartReportJobResponse x -> StartReportJobResponse
$cfrom :: forall x. StartReportJobResponse -> Rep StartReportJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartReportJobResponse' 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:
--
-- 'reportJobId', 'startReportJobResponse_reportJobId' - The identifier of the report job. A unique, randomly generated, Unicode,
-- UTF-8 encoded string that is at most 1,024 bytes long. The report job ID
-- cannot be edited.
--
-- 'httpStatus', 'startReportJobResponse_httpStatus' - The response's http status code.
newStartReportJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartReportJobResponse
newStartReportJobResponse :: Int -> StartReportJobResponse
newStartReportJobResponse Int
pHttpStatus_ =
  StartReportJobResponse'
    { $sel:reportJobId:StartReportJobResponse' :: Maybe Text
reportJobId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartReportJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier of the report job. A unique, randomly generated, Unicode,
-- UTF-8 encoded string that is at most 1,024 bytes long. The report job ID
-- cannot be edited.
startReportJobResponse_reportJobId :: Lens.Lens' StartReportJobResponse (Prelude.Maybe Prelude.Text)
startReportJobResponse_reportJobId :: Lens' StartReportJobResponse (Maybe Text)
startReportJobResponse_reportJobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartReportJobResponse' {Maybe Text
reportJobId :: Maybe Text
$sel:reportJobId:StartReportJobResponse' :: StartReportJobResponse -> Maybe Text
reportJobId} -> Maybe Text
reportJobId) (\s :: StartReportJobResponse
s@StartReportJobResponse' {} Maybe Text
a -> StartReportJobResponse
s {$sel:reportJobId:StartReportJobResponse' :: Maybe Text
reportJobId = Maybe Text
a} :: StartReportJobResponse)

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

instance Prelude.NFData StartReportJobResponse where
  rnf :: StartReportJobResponse -> ()
rnf StartReportJobResponse' {Int
Maybe Text
httpStatus :: Int
reportJobId :: Maybe Text
$sel:httpStatus:StartReportJobResponse' :: StartReportJobResponse -> Int
$sel:reportJobId:StartReportJobResponse' :: StartReportJobResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reportJobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus