{-# 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.Discovery.BatchDeleteImportData
-- 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 one or more import tasks, each identified by their import ID.
-- Each import task has a number of records that can identify servers or
-- applications.
--
-- Amazon Web Services Application Discovery Service has built-in matching
-- logic that will identify when discovered servers match existing entries
-- that you\'ve previously discovered, the information for the
-- already-existing discovered server is updated. When you delete an import
-- task that contains records that were used to match, the information in
-- those matched records that comes from the deleted records will also be
-- deleted.
module Amazonka.Discovery.BatchDeleteImportData
  ( -- * Creating a Request
    BatchDeleteImportData (..),
    newBatchDeleteImportData,

    -- * Request Lenses
    batchDeleteImportData_importTaskIds,

    -- * Destructuring the Response
    BatchDeleteImportDataResponse (..),
    newBatchDeleteImportDataResponse,

    -- * Response Lenses
    batchDeleteImportDataResponse_errors,
    batchDeleteImportDataResponse_httpStatus,
  )
where

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

-- | /See:/ 'newBatchDeleteImportData' smart constructor.
data BatchDeleteImportData = BatchDeleteImportData'
  { -- | The IDs for the import tasks that you want to delete.
    BatchDeleteImportData -> NonEmpty Text
importTaskIds :: Prelude.NonEmpty Prelude.Text
  }
  deriving (BatchDeleteImportData -> BatchDeleteImportData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDeleteImportData -> BatchDeleteImportData -> Bool
$c/= :: BatchDeleteImportData -> BatchDeleteImportData -> Bool
== :: BatchDeleteImportData -> BatchDeleteImportData -> Bool
$c== :: BatchDeleteImportData -> BatchDeleteImportData -> Bool
Prelude.Eq, ReadPrec [BatchDeleteImportData]
ReadPrec BatchDeleteImportData
Int -> ReadS BatchDeleteImportData
ReadS [BatchDeleteImportData]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDeleteImportData]
$creadListPrec :: ReadPrec [BatchDeleteImportData]
readPrec :: ReadPrec BatchDeleteImportData
$creadPrec :: ReadPrec BatchDeleteImportData
readList :: ReadS [BatchDeleteImportData]
$creadList :: ReadS [BatchDeleteImportData]
readsPrec :: Int -> ReadS BatchDeleteImportData
$creadsPrec :: Int -> ReadS BatchDeleteImportData
Prelude.Read, Int -> BatchDeleteImportData -> ShowS
[BatchDeleteImportData] -> ShowS
BatchDeleteImportData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDeleteImportData] -> ShowS
$cshowList :: [BatchDeleteImportData] -> ShowS
show :: BatchDeleteImportData -> String
$cshow :: BatchDeleteImportData -> String
showsPrec :: Int -> BatchDeleteImportData -> ShowS
$cshowsPrec :: Int -> BatchDeleteImportData -> ShowS
Prelude.Show, forall x. Rep BatchDeleteImportData x -> BatchDeleteImportData
forall x. BatchDeleteImportData -> Rep BatchDeleteImportData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchDeleteImportData x -> BatchDeleteImportData
$cfrom :: forall x. BatchDeleteImportData -> Rep BatchDeleteImportData x
Prelude.Generic)

-- |
-- Create a value of 'BatchDeleteImportData' 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:
--
-- 'importTaskIds', 'batchDeleteImportData_importTaskIds' - The IDs for the import tasks that you want to delete.
newBatchDeleteImportData ::
  -- | 'importTaskIds'
  Prelude.NonEmpty Prelude.Text ->
  BatchDeleteImportData
newBatchDeleteImportData :: NonEmpty Text -> BatchDeleteImportData
newBatchDeleteImportData NonEmpty Text
pImportTaskIds_ =
  BatchDeleteImportData'
    { $sel:importTaskIds:BatchDeleteImportData' :: NonEmpty Text
importTaskIds =
        forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pImportTaskIds_
    }

-- | The IDs for the import tasks that you want to delete.
batchDeleteImportData_importTaskIds :: Lens.Lens' BatchDeleteImportData (Prelude.NonEmpty Prelude.Text)
batchDeleteImportData_importTaskIds :: Lens' BatchDeleteImportData (NonEmpty Text)
batchDeleteImportData_importTaskIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDeleteImportData' {NonEmpty Text
importTaskIds :: NonEmpty Text
$sel:importTaskIds:BatchDeleteImportData' :: BatchDeleteImportData -> NonEmpty Text
importTaskIds} -> NonEmpty Text
importTaskIds) (\s :: BatchDeleteImportData
s@BatchDeleteImportData' {} NonEmpty Text
a -> BatchDeleteImportData
s {$sel:importTaskIds:BatchDeleteImportData' :: NonEmpty Text
importTaskIds = NonEmpty Text
a} :: BatchDeleteImportData) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest BatchDeleteImportData where
  type
    AWSResponse BatchDeleteImportData =
      BatchDeleteImportDataResponse
  request :: (Service -> Service)
-> BatchDeleteImportData -> Request BatchDeleteImportData
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 BatchDeleteImportData
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchDeleteImportData)))
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 [BatchDeleteImportDataError]
-> Int -> BatchDeleteImportDataResponse
BatchDeleteImportDataResponse'
            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
"errors" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 BatchDeleteImportData where
  hashWithSalt :: Int -> BatchDeleteImportData -> Int
hashWithSalt Int
_salt BatchDeleteImportData' {NonEmpty Text
importTaskIds :: NonEmpty Text
$sel:importTaskIds:BatchDeleteImportData' :: BatchDeleteImportData -> NonEmpty Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
importTaskIds

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

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

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

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

-- | /See:/ 'newBatchDeleteImportDataResponse' smart constructor.
data BatchDeleteImportDataResponse = BatchDeleteImportDataResponse'
  { -- | Error messages returned for each import task that you deleted as a
    -- response for this command.
    BatchDeleteImportDataResponse -> Maybe [BatchDeleteImportDataError]
errors :: Prelude.Maybe [BatchDeleteImportDataError],
    -- | The response's http status code.
    BatchDeleteImportDataResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchDeleteImportDataResponse
-> BatchDeleteImportDataResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchDeleteImportDataResponse
-> BatchDeleteImportDataResponse -> Bool
$c/= :: BatchDeleteImportDataResponse
-> BatchDeleteImportDataResponse -> Bool
== :: BatchDeleteImportDataResponse
-> BatchDeleteImportDataResponse -> Bool
$c== :: BatchDeleteImportDataResponse
-> BatchDeleteImportDataResponse -> Bool
Prelude.Eq, ReadPrec [BatchDeleteImportDataResponse]
ReadPrec BatchDeleteImportDataResponse
Int -> ReadS BatchDeleteImportDataResponse
ReadS [BatchDeleteImportDataResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchDeleteImportDataResponse]
$creadListPrec :: ReadPrec [BatchDeleteImportDataResponse]
readPrec :: ReadPrec BatchDeleteImportDataResponse
$creadPrec :: ReadPrec BatchDeleteImportDataResponse
readList :: ReadS [BatchDeleteImportDataResponse]
$creadList :: ReadS [BatchDeleteImportDataResponse]
readsPrec :: Int -> ReadS BatchDeleteImportDataResponse
$creadsPrec :: Int -> ReadS BatchDeleteImportDataResponse
Prelude.Read, Int -> BatchDeleteImportDataResponse -> ShowS
[BatchDeleteImportDataResponse] -> ShowS
BatchDeleteImportDataResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchDeleteImportDataResponse] -> ShowS
$cshowList :: [BatchDeleteImportDataResponse] -> ShowS
show :: BatchDeleteImportDataResponse -> String
$cshow :: BatchDeleteImportDataResponse -> String
showsPrec :: Int -> BatchDeleteImportDataResponse -> ShowS
$cshowsPrec :: Int -> BatchDeleteImportDataResponse -> ShowS
Prelude.Show, forall x.
Rep BatchDeleteImportDataResponse x
-> BatchDeleteImportDataResponse
forall x.
BatchDeleteImportDataResponse
-> Rep BatchDeleteImportDataResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchDeleteImportDataResponse x
-> BatchDeleteImportDataResponse
$cfrom :: forall x.
BatchDeleteImportDataResponse
-> Rep BatchDeleteImportDataResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchDeleteImportDataResponse' 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:
--
-- 'errors', 'batchDeleteImportDataResponse_errors' - Error messages returned for each import task that you deleted as a
-- response for this command.
--
-- 'httpStatus', 'batchDeleteImportDataResponse_httpStatus' - The response's http status code.
newBatchDeleteImportDataResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchDeleteImportDataResponse
newBatchDeleteImportDataResponse :: Int -> BatchDeleteImportDataResponse
newBatchDeleteImportDataResponse Int
pHttpStatus_ =
  BatchDeleteImportDataResponse'
    { $sel:errors:BatchDeleteImportDataResponse' :: Maybe [BatchDeleteImportDataError]
errors =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchDeleteImportDataResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Error messages returned for each import task that you deleted as a
-- response for this command.
batchDeleteImportDataResponse_errors :: Lens.Lens' BatchDeleteImportDataResponse (Prelude.Maybe [BatchDeleteImportDataError])
batchDeleteImportDataResponse_errors :: Lens'
  BatchDeleteImportDataResponse (Maybe [BatchDeleteImportDataError])
batchDeleteImportDataResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchDeleteImportDataResponse' {Maybe [BatchDeleteImportDataError]
errors :: Maybe [BatchDeleteImportDataError]
$sel:errors:BatchDeleteImportDataResponse' :: BatchDeleteImportDataResponse -> Maybe [BatchDeleteImportDataError]
errors} -> Maybe [BatchDeleteImportDataError]
errors) (\s :: BatchDeleteImportDataResponse
s@BatchDeleteImportDataResponse' {} Maybe [BatchDeleteImportDataError]
a -> BatchDeleteImportDataResponse
s {$sel:errors:BatchDeleteImportDataResponse' :: Maybe [BatchDeleteImportDataError]
errors = Maybe [BatchDeleteImportDataError]
a} :: BatchDeleteImportDataResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData BatchDeleteImportDataResponse where
  rnf :: BatchDeleteImportDataResponse -> ()
rnf BatchDeleteImportDataResponse' {Int
Maybe [BatchDeleteImportDataError]
httpStatus :: Int
errors :: Maybe [BatchDeleteImportDataError]
$sel:httpStatus:BatchDeleteImportDataResponse' :: BatchDeleteImportDataResponse -> Int
$sel:errors:BatchDeleteImportDataResponse' :: BatchDeleteImportDataResponse -> Maybe [BatchDeleteImportDataError]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [BatchDeleteImportDataError]
errors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus