{-# 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.CodeBuild.DeleteReportGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a report group. Before you delete a report group, you must
-- delete its reports.
module Amazonka.CodeBuild.DeleteReportGroup
  ( -- * Creating a Request
    DeleteReportGroup (..),
    newDeleteReportGroup,

    -- * Request Lenses
    deleteReportGroup_deleteReports,
    deleteReportGroup_arn,

    -- * Destructuring the Response
    DeleteReportGroupResponse (..),
    newDeleteReportGroupResponse,

    -- * Response Lenses
    deleteReportGroupResponse_httpStatus,
  )
where

import Amazonka.CodeBuild.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:/ 'newDeleteReportGroup' smart constructor.
data DeleteReportGroup = DeleteReportGroup'
  { -- | If @true@, deletes any reports that belong to a report group before
    -- deleting the report group.
    --
    -- If @false@, you must delete any reports in the report group. Use
    -- <https://docs.aws.amazon.com/codebuild/latest/APIReference/API_ListReportsForReportGroup.html ListReportsForReportGroup>
    -- to get the reports in a report group. Use
    -- <https://docs.aws.amazon.com/codebuild/latest/APIReference/API_DeleteReport.html DeleteReport>
    -- to delete the reports. If you call @DeleteReportGroup@ for a report
    -- group that contains one or more reports, an exception is thrown.
    DeleteReportGroup -> Maybe Bool
deleteReports :: Prelude.Maybe Prelude.Bool,
    -- | The ARN of the report group to delete.
    DeleteReportGroup -> Text
arn :: Prelude.Text
  }
  deriving (DeleteReportGroup -> DeleteReportGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteReportGroup -> DeleteReportGroup -> Bool
$c/= :: DeleteReportGroup -> DeleteReportGroup -> Bool
== :: DeleteReportGroup -> DeleteReportGroup -> Bool
$c== :: DeleteReportGroup -> DeleteReportGroup -> Bool
Prelude.Eq, ReadPrec [DeleteReportGroup]
ReadPrec DeleteReportGroup
Int -> ReadS DeleteReportGroup
ReadS [DeleteReportGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteReportGroup]
$creadListPrec :: ReadPrec [DeleteReportGroup]
readPrec :: ReadPrec DeleteReportGroup
$creadPrec :: ReadPrec DeleteReportGroup
readList :: ReadS [DeleteReportGroup]
$creadList :: ReadS [DeleteReportGroup]
readsPrec :: Int -> ReadS DeleteReportGroup
$creadsPrec :: Int -> ReadS DeleteReportGroup
Prelude.Read, Int -> DeleteReportGroup -> ShowS
[DeleteReportGroup] -> ShowS
DeleteReportGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteReportGroup] -> ShowS
$cshowList :: [DeleteReportGroup] -> ShowS
show :: DeleteReportGroup -> String
$cshow :: DeleteReportGroup -> String
showsPrec :: Int -> DeleteReportGroup -> ShowS
$cshowsPrec :: Int -> DeleteReportGroup -> ShowS
Prelude.Show, forall x. Rep DeleteReportGroup x -> DeleteReportGroup
forall x. DeleteReportGroup -> Rep DeleteReportGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteReportGroup x -> DeleteReportGroup
$cfrom :: forall x. DeleteReportGroup -> Rep DeleteReportGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteReportGroup' 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:
--
-- 'deleteReports', 'deleteReportGroup_deleteReports' - If @true@, deletes any reports that belong to a report group before
-- deleting the report group.
--
-- If @false@, you must delete any reports in the report group. Use
-- <https://docs.aws.amazon.com/codebuild/latest/APIReference/API_ListReportsForReportGroup.html ListReportsForReportGroup>
-- to get the reports in a report group. Use
-- <https://docs.aws.amazon.com/codebuild/latest/APIReference/API_DeleteReport.html DeleteReport>
-- to delete the reports. If you call @DeleteReportGroup@ for a report
-- group that contains one or more reports, an exception is thrown.
--
-- 'arn', 'deleteReportGroup_arn' - The ARN of the report group to delete.
newDeleteReportGroup ::
  -- | 'arn'
  Prelude.Text ->
  DeleteReportGroup
newDeleteReportGroup :: Text -> DeleteReportGroup
newDeleteReportGroup Text
pArn_ =
  DeleteReportGroup'
    { $sel:deleteReports:DeleteReportGroup' :: Maybe Bool
deleteReports = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:DeleteReportGroup' :: Text
arn = Text
pArn_
    }

-- | If @true@, deletes any reports that belong to a report group before
-- deleting the report group.
--
-- If @false@, you must delete any reports in the report group. Use
-- <https://docs.aws.amazon.com/codebuild/latest/APIReference/API_ListReportsForReportGroup.html ListReportsForReportGroup>
-- to get the reports in a report group. Use
-- <https://docs.aws.amazon.com/codebuild/latest/APIReference/API_DeleteReport.html DeleteReport>
-- to delete the reports. If you call @DeleteReportGroup@ for a report
-- group that contains one or more reports, an exception is thrown.
deleteReportGroup_deleteReports :: Lens.Lens' DeleteReportGroup (Prelude.Maybe Prelude.Bool)
deleteReportGroup_deleteReports :: Lens' DeleteReportGroup (Maybe Bool)
deleteReportGroup_deleteReports = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteReportGroup' {Maybe Bool
deleteReports :: Maybe Bool
$sel:deleteReports:DeleteReportGroup' :: DeleteReportGroup -> Maybe Bool
deleteReports} -> Maybe Bool
deleteReports) (\s :: DeleteReportGroup
s@DeleteReportGroup' {} Maybe Bool
a -> DeleteReportGroup
s {$sel:deleteReports:DeleteReportGroup' :: Maybe Bool
deleteReports = Maybe Bool
a} :: DeleteReportGroup)

-- | The ARN of the report group to delete.
deleteReportGroup_arn :: Lens.Lens' DeleteReportGroup Prelude.Text
deleteReportGroup_arn :: Lens' DeleteReportGroup Text
deleteReportGroup_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteReportGroup' {Text
arn :: Text
$sel:arn:DeleteReportGroup' :: DeleteReportGroup -> Text
arn} -> Text
arn) (\s :: DeleteReportGroup
s@DeleteReportGroup' {} Text
a -> DeleteReportGroup
s {$sel:arn:DeleteReportGroup' :: Text
arn = Text
a} :: DeleteReportGroup)

instance Core.AWSRequest DeleteReportGroup where
  type
    AWSResponse DeleteReportGroup =
      DeleteReportGroupResponse
  request :: (Service -> Service)
-> DeleteReportGroup -> Request DeleteReportGroup
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 DeleteReportGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteReportGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteReportGroupResponse
DeleteReportGroupResponse'
            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))
      )

instance Prelude.Hashable DeleteReportGroup where
  hashWithSalt :: Int -> DeleteReportGroup -> Int
hashWithSalt Int
_salt DeleteReportGroup' {Maybe Bool
Text
arn :: Text
deleteReports :: Maybe Bool
$sel:arn:DeleteReportGroup' :: DeleteReportGroup -> Text
$sel:deleteReports:DeleteReportGroup' :: DeleteReportGroup -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteReports
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn

instance Prelude.NFData DeleteReportGroup where
  rnf :: DeleteReportGroup -> ()
rnf DeleteReportGroup' {Maybe Bool
Text
arn :: Text
deleteReports :: Maybe Bool
$sel:arn:DeleteReportGroup' :: DeleteReportGroup -> Text
$sel:deleteReports:DeleteReportGroup' :: DeleteReportGroup -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteReports
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn

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

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

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

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

-- |
-- Create a value of 'DeleteReportGroupResponse' 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', 'deleteReportGroupResponse_httpStatus' - The response's http status code.
newDeleteReportGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteReportGroupResponse
newDeleteReportGroupResponse :: Int -> DeleteReportGroupResponse
newDeleteReportGroupResponse Int
pHttpStatus_ =
  DeleteReportGroupResponse'
    { $sel:httpStatus:DeleteReportGroupResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DeleteReportGroupResponse where
  rnf :: DeleteReportGroupResponse -> ()
rnf DeleteReportGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteReportGroupResponse' :: DeleteReportGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus