{-# 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.DeleteEvaluation
-- 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 an @Evaluation@, rendering it unusable.
--
-- After invoking the @DeleteEvaluation@ operation, you can use the
-- @GetEvaluation@ operation to verify that the status of the @Evaluation@
-- changed to @DELETED@.
--
-- __Caution:__ The results of the @DeleteEvaluation@ operation are
-- irreversible.
module Amazonka.MachineLearning.DeleteEvaluation
  ( -- * Creating a Request
    DeleteEvaluation (..),
    newDeleteEvaluation,

    -- * Request Lenses
    deleteEvaluation_evaluationId,

    -- * Destructuring the Response
    DeleteEvaluationResponse (..),
    newDeleteEvaluationResponse,

    -- * Response Lenses
    deleteEvaluationResponse_evaluationId,
    deleteEvaluationResponse_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:/ 'newDeleteEvaluation' smart constructor.
data DeleteEvaluation = DeleteEvaluation'
  { -- | A user-supplied ID that uniquely identifies the @Evaluation@ to delete.
    DeleteEvaluation -> Text
evaluationId :: Prelude.Text
  }
  deriving (DeleteEvaluation -> DeleteEvaluation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEvaluation -> DeleteEvaluation -> Bool
$c/= :: DeleteEvaluation -> DeleteEvaluation -> Bool
== :: DeleteEvaluation -> DeleteEvaluation -> Bool
$c== :: DeleteEvaluation -> DeleteEvaluation -> Bool
Prelude.Eq, ReadPrec [DeleteEvaluation]
ReadPrec DeleteEvaluation
Int -> ReadS DeleteEvaluation
ReadS [DeleteEvaluation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteEvaluation]
$creadListPrec :: ReadPrec [DeleteEvaluation]
readPrec :: ReadPrec DeleteEvaluation
$creadPrec :: ReadPrec DeleteEvaluation
readList :: ReadS [DeleteEvaluation]
$creadList :: ReadS [DeleteEvaluation]
readsPrec :: Int -> ReadS DeleteEvaluation
$creadsPrec :: Int -> ReadS DeleteEvaluation
Prelude.Read, Int -> DeleteEvaluation -> ShowS
[DeleteEvaluation] -> ShowS
DeleteEvaluation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEvaluation] -> ShowS
$cshowList :: [DeleteEvaluation] -> ShowS
show :: DeleteEvaluation -> String
$cshow :: DeleteEvaluation -> String
showsPrec :: Int -> DeleteEvaluation -> ShowS
$cshowsPrec :: Int -> DeleteEvaluation -> ShowS
Prelude.Show, forall x. Rep DeleteEvaluation x -> DeleteEvaluation
forall x. DeleteEvaluation -> Rep DeleteEvaluation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteEvaluation x -> DeleteEvaluation
$cfrom :: forall x. DeleteEvaluation -> Rep DeleteEvaluation x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEvaluation' 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:
--
-- 'evaluationId', 'deleteEvaluation_evaluationId' - A user-supplied ID that uniquely identifies the @Evaluation@ to delete.
newDeleteEvaluation ::
  -- | 'evaluationId'
  Prelude.Text ->
  DeleteEvaluation
newDeleteEvaluation :: Text -> DeleteEvaluation
newDeleteEvaluation Text
pEvaluationId_ =
  DeleteEvaluation' {$sel:evaluationId:DeleteEvaluation' :: Text
evaluationId = Text
pEvaluationId_}

-- | A user-supplied ID that uniquely identifies the @Evaluation@ to delete.
deleteEvaluation_evaluationId :: Lens.Lens' DeleteEvaluation Prelude.Text
deleteEvaluation_evaluationId :: Lens' DeleteEvaluation Text
deleteEvaluation_evaluationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEvaluation' {Text
evaluationId :: Text
$sel:evaluationId:DeleteEvaluation' :: DeleteEvaluation -> Text
evaluationId} -> Text
evaluationId) (\s :: DeleteEvaluation
s@DeleteEvaluation' {} Text
a -> DeleteEvaluation
s {$sel:evaluationId:DeleteEvaluation' :: Text
evaluationId = Text
a} :: DeleteEvaluation)

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

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

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

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

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

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

-- |
-- Create a value of 'DeleteEvaluationResponse' 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:
--
-- 'evaluationId', 'deleteEvaluationResponse_evaluationId' - A user-supplied ID that uniquely identifies the @Evaluation@. This value
-- should be identical to the value of the @EvaluationId@ in the request.
--
-- 'httpStatus', 'deleteEvaluationResponse_httpStatus' - The response's http status code.
newDeleteEvaluationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteEvaluationResponse
newDeleteEvaluationResponse :: Int -> DeleteEvaluationResponse
newDeleteEvaluationResponse Int
pHttpStatus_ =
  DeleteEvaluationResponse'
    { $sel:evaluationId:DeleteEvaluationResponse' :: Maybe Text
evaluationId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteEvaluationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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