{-# 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.MachineLearning.DeleteBatchPrediction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Assigns the DELETED status to a @BatchPrediction@, rendering it
-- unusable.
--
-- After using the @DeleteBatchPrediction@ operation, you can use the
-- GetBatchPrediction operation to verify that the status of the
-- @BatchPrediction@ changed to DELETED.
--
-- __Caution:__ The result of the @DeleteBatchPrediction@ operation is
-- irreversible.
module Amazonka.MachineLearning.DeleteBatchPrediction
  ( -- * Creating a Request
    DeleteBatchPrediction (..),
    newDeleteBatchPrediction,

    -- * Request Lenses
    deleteBatchPrediction_batchPredictionId,

    -- * Destructuring the Response
    DeleteBatchPredictionResponse (..),
    newDeleteBatchPredictionResponse,

    -- * Response Lenses
    deleteBatchPredictionResponse_batchPredictionId,
    deleteBatchPredictionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteBatchPrediction' smart constructor.
data DeleteBatchPrediction = DeleteBatchPrediction'
  { -- | A user-supplied ID that uniquely identifies the @BatchPrediction@.
    DeleteBatchPrediction -> Text
batchPredictionId :: Prelude.Text
  }
  deriving (DeleteBatchPrediction -> DeleteBatchPrediction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBatchPrediction -> DeleteBatchPrediction -> Bool
$c/= :: DeleteBatchPrediction -> DeleteBatchPrediction -> Bool
== :: DeleteBatchPrediction -> DeleteBatchPrediction -> Bool
$c== :: DeleteBatchPrediction -> DeleteBatchPrediction -> Bool
Prelude.Eq, ReadPrec [DeleteBatchPrediction]
ReadPrec DeleteBatchPrediction
Int -> ReadS DeleteBatchPrediction
ReadS [DeleteBatchPrediction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBatchPrediction]
$creadListPrec :: ReadPrec [DeleteBatchPrediction]
readPrec :: ReadPrec DeleteBatchPrediction
$creadPrec :: ReadPrec DeleteBatchPrediction
readList :: ReadS [DeleteBatchPrediction]
$creadList :: ReadS [DeleteBatchPrediction]
readsPrec :: Int -> ReadS DeleteBatchPrediction
$creadsPrec :: Int -> ReadS DeleteBatchPrediction
Prelude.Read, Int -> DeleteBatchPrediction -> ShowS
[DeleteBatchPrediction] -> ShowS
DeleteBatchPrediction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBatchPrediction] -> ShowS
$cshowList :: [DeleteBatchPrediction] -> ShowS
show :: DeleteBatchPrediction -> String
$cshow :: DeleteBatchPrediction -> String
showsPrec :: Int -> DeleteBatchPrediction -> ShowS
$cshowsPrec :: Int -> DeleteBatchPrediction -> ShowS
Prelude.Show, forall x. Rep DeleteBatchPrediction x -> DeleteBatchPrediction
forall x. DeleteBatchPrediction -> Rep DeleteBatchPrediction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBatchPrediction x -> DeleteBatchPrediction
$cfrom :: forall x. DeleteBatchPrediction -> Rep DeleteBatchPrediction x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBatchPrediction' 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:
--
-- 'batchPredictionId', 'deleteBatchPrediction_batchPredictionId' - A user-supplied ID that uniquely identifies the @BatchPrediction@.
newDeleteBatchPrediction ::
  -- | 'batchPredictionId'
  Prelude.Text ->
  DeleteBatchPrediction
newDeleteBatchPrediction :: Text -> DeleteBatchPrediction
newDeleteBatchPrediction Text
pBatchPredictionId_ =
  DeleteBatchPrediction'
    { $sel:batchPredictionId:DeleteBatchPrediction' :: Text
batchPredictionId =
        Text
pBatchPredictionId_
    }

-- | A user-supplied ID that uniquely identifies the @BatchPrediction@.
deleteBatchPrediction_batchPredictionId :: Lens.Lens' DeleteBatchPrediction Prelude.Text
deleteBatchPrediction_batchPredictionId :: Lens' DeleteBatchPrediction Text
deleteBatchPrediction_batchPredictionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBatchPrediction' {Text
batchPredictionId :: Text
$sel:batchPredictionId:DeleteBatchPrediction' :: DeleteBatchPrediction -> Text
batchPredictionId} -> Text
batchPredictionId) (\s :: DeleteBatchPrediction
s@DeleteBatchPrediction' {} Text
a -> DeleteBatchPrediction
s {$sel:batchPredictionId:DeleteBatchPrediction' :: Text
batchPredictionId = Text
a} :: DeleteBatchPrediction)

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

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

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

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

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

-- | Represents the output of a @DeleteBatchPrediction@ operation.
--
-- You can use the @GetBatchPrediction@ operation and check the value of
-- the @Status@ parameter to see whether a @BatchPrediction@ is marked as
-- @DELETED@.
--
-- /See:/ 'newDeleteBatchPredictionResponse' smart constructor.
data DeleteBatchPredictionResponse = DeleteBatchPredictionResponse'
  { -- | A user-supplied ID that uniquely identifies the @BatchPrediction@. This
    -- value should be identical to the value of the @BatchPredictionID@ in the
    -- request.
    DeleteBatchPredictionResponse -> Maybe Text
batchPredictionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteBatchPredictionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteBatchPredictionResponse
-> DeleteBatchPredictionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBatchPredictionResponse
-> DeleteBatchPredictionResponse -> Bool
$c/= :: DeleteBatchPredictionResponse
-> DeleteBatchPredictionResponse -> Bool
== :: DeleteBatchPredictionResponse
-> DeleteBatchPredictionResponse -> Bool
$c== :: DeleteBatchPredictionResponse
-> DeleteBatchPredictionResponse -> Bool
Prelude.Eq, ReadPrec [DeleteBatchPredictionResponse]
ReadPrec DeleteBatchPredictionResponse
Int -> ReadS DeleteBatchPredictionResponse
ReadS [DeleteBatchPredictionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBatchPredictionResponse]
$creadListPrec :: ReadPrec [DeleteBatchPredictionResponse]
readPrec :: ReadPrec DeleteBatchPredictionResponse
$creadPrec :: ReadPrec DeleteBatchPredictionResponse
readList :: ReadS [DeleteBatchPredictionResponse]
$creadList :: ReadS [DeleteBatchPredictionResponse]
readsPrec :: Int -> ReadS DeleteBatchPredictionResponse
$creadsPrec :: Int -> ReadS DeleteBatchPredictionResponse
Prelude.Read, Int -> DeleteBatchPredictionResponse -> ShowS
[DeleteBatchPredictionResponse] -> ShowS
DeleteBatchPredictionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBatchPredictionResponse] -> ShowS
$cshowList :: [DeleteBatchPredictionResponse] -> ShowS
show :: DeleteBatchPredictionResponse -> String
$cshow :: DeleteBatchPredictionResponse -> String
showsPrec :: Int -> DeleteBatchPredictionResponse -> ShowS
$cshowsPrec :: Int -> DeleteBatchPredictionResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteBatchPredictionResponse x
-> DeleteBatchPredictionResponse
forall x.
DeleteBatchPredictionResponse
-> Rep DeleteBatchPredictionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteBatchPredictionResponse x
-> DeleteBatchPredictionResponse
$cfrom :: forall x.
DeleteBatchPredictionResponse
-> Rep DeleteBatchPredictionResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBatchPredictionResponse' 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:
--
-- 'batchPredictionId', 'deleteBatchPredictionResponse_batchPredictionId' - A user-supplied ID that uniquely identifies the @BatchPrediction@. This
-- value should be identical to the value of the @BatchPredictionID@ in the
-- request.
--
-- 'httpStatus', 'deleteBatchPredictionResponse_httpStatus' - The response's http status code.
newDeleteBatchPredictionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteBatchPredictionResponse
newDeleteBatchPredictionResponse :: Int -> DeleteBatchPredictionResponse
newDeleteBatchPredictionResponse Int
pHttpStatus_ =
  DeleteBatchPredictionResponse'
    { $sel:batchPredictionId:DeleteBatchPredictionResponse' :: Maybe Text
batchPredictionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteBatchPredictionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A user-supplied ID that uniquely identifies the @BatchPrediction@. This
-- value should be identical to the value of the @BatchPredictionID@ in the
-- request.
deleteBatchPredictionResponse_batchPredictionId :: Lens.Lens' DeleteBatchPredictionResponse (Prelude.Maybe Prelude.Text)
deleteBatchPredictionResponse_batchPredictionId :: Lens' DeleteBatchPredictionResponse (Maybe Text)
deleteBatchPredictionResponse_batchPredictionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBatchPredictionResponse' {Maybe Text
batchPredictionId :: Maybe Text
$sel:batchPredictionId:DeleteBatchPredictionResponse' :: DeleteBatchPredictionResponse -> Maybe Text
batchPredictionId} -> Maybe Text
batchPredictionId) (\s :: DeleteBatchPredictionResponse
s@DeleteBatchPredictionResponse' {} Maybe Text
a -> DeleteBatchPredictionResponse
s {$sel:batchPredictionId:DeleteBatchPredictionResponse' :: Maybe Text
batchPredictionId = Maybe Text
a} :: DeleteBatchPredictionResponse)

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

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