{-# 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.LookoutVision.DeleteModel
-- 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 an Amazon Lookout for Vision model. You can\'t delete a running
-- model. To stop a running model, use the StopModel operation.
--
-- It might take a few seconds to delete a model. To determine if a model
-- has been deleted, call ListModels and check if the version of the model
-- (@ModelVersion@) is in the @Models@ array.
--
-- This operation requires permissions to perform the
-- @lookoutvision:DeleteModel@ operation.
module Amazonka.LookoutVision.DeleteModel
  ( -- * Creating a Request
    DeleteModel (..),
    newDeleteModel,

    -- * Request Lenses
    deleteModel_clientToken,
    deleteModel_projectName,
    deleteModel_modelVersion,

    -- * Destructuring the Response
    DeleteModelResponse (..),
    newDeleteModelResponse,

    -- * Response Lenses
    deleteModelResponse_modelArn,
    deleteModelResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteModel' smart constructor.
data DeleteModel = DeleteModel'
  { -- | ClientToken is an idempotency token that ensures a call to @DeleteModel@
    -- completes only once. You choose the value to pass. For example, an issue
    -- might prevent you from getting a response from @DeleteModel@. In this
    -- case, safely retry your call to @DeleteModel@ by using the same
    -- @ClientToken@ parameter value.
    --
    -- If you don\'t supply a value for ClientToken, the AWS SDK you are using
    -- inserts a value for you. This prevents retries after a network error
    -- from making multiple model deletion requests. You\'ll need to provide
    -- your own value for other use cases.
    --
    -- An error occurs if the other input parameters are not the same as in the
    -- first request. Using a different value for @ClientToken@ is considered a
    -- new call to @DeleteModel@. An idempotency token is active for 8 hours.
    DeleteModel -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the project that contains the model that you want to delete.
    DeleteModel -> Text
projectName :: Prelude.Text,
    -- | The version of the model that you want to delete.
    DeleteModel -> Text
modelVersion :: Prelude.Text
  }
  deriving (DeleteModel -> DeleteModel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteModel -> DeleteModel -> Bool
$c/= :: DeleteModel -> DeleteModel -> Bool
== :: DeleteModel -> DeleteModel -> Bool
$c== :: DeleteModel -> DeleteModel -> Bool
Prelude.Eq, ReadPrec [DeleteModel]
ReadPrec DeleteModel
Int -> ReadS DeleteModel
ReadS [DeleteModel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteModel]
$creadListPrec :: ReadPrec [DeleteModel]
readPrec :: ReadPrec DeleteModel
$creadPrec :: ReadPrec DeleteModel
readList :: ReadS [DeleteModel]
$creadList :: ReadS [DeleteModel]
readsPrec :: Int -> ReadS DeleteModel
$creadsPrec :: Int -> ReadS DeleteModel
Prelude.Read, Int -> DeleteModel -> ShowS
[DeleteModel] -> ShowS
DeleteModel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteModel] -> ShowS
$cshowList :: [DeleteModel] -> ShowS
show :: DeleteModel -> String
$cshow :: DeleteModel -> String
showsPrec :: Int -> DeleteModel -> ShowS
$cshowsPrec :: Int -> DeleteModel -> ShowS
Prelude.Show, forall x. Rep DeleteModel x -> DeleteModel
forall x. DeleteModel -> Rep DeleteModel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteModel x -> DeleteModel
$cfrom :: forall x. DeleteModel -> Rep DeleteModel x
Prelude.Generic)

-- |
-- Create a value of 'DeleteModel' 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:
--
-- 'clientToken', 'deleteModel_clientToken' - ClientToken is an idempotency token that ensures a call to @DeleteModel@
-- completes only once. You choose the value to pass. For example, an issue
-- might prevent you from getting a response from @DeleteModel@. In this
-- case, safely retry your call to @DeleteModel@ by using the same
-- @ClientToken@ parameter value.
--
-- If you don\'t supply a value for ClientToken, the AWS SDK you are using
-- inserts a value for you. This prevents retries after a network error
-- from making multiple model deletion requests. You\'ll need to provide
-- your own value for other use cases.
--
-- An error occurs if the other input parameters are not the same as in the
-- first request. Using a different value for @ClientToken@ is considered a
-- new call to @DeleteModel@. An idempotency token is active for 8 hours.
--
-- 'projectName', 'deleteModel_projectName' - The name of the project that contains the model that you want to delete.
--
-- 'modelVersion', 'deleteModel_modelVersion' - The version of the model that you want to delete.
newDeleteModel ::
  -- | 'projectName'
  Prelude.Text ->
  -- | 'modelVersion'
  Prelude.Text ->
  DeleteModel
newDeleteModel :: Text -> Text -> DeleteModel
newDeleteModel Text
pProjectName_ Text
pModelVersion_ =
  DeleteModel'
    { $sel:clientToken:DeleteModel' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:DeleteModel' :: Text
projectName = Text
pProjectName_,
      $sel:modelVersion:DeleteModel' :: Text
modelVersion = Text
pModelVersion_
    }

-- | ClientToken is an idempotency token that ensures a call to @DeleteModel@
-- completes only once. You choose the value to pass. For example, an issue
-- might prevent you from getting a response from @DeleteModel@. In this
-- case, safely retry your call to @DeleteModel@ by using the same
-- @ClientToken@ parameter value.
--
-- If you don\'t supply a value for ClientToken, the AWS SDK you are using
-- inserts a value for you. This prevents retries after a network error
-- from making multiple model deletion requests. You\'ll need to provide
-- your own value for other use cases.
--
-- An error occurs if the other input parameters are not the same as in the
-- first request. Using a different value for @ClientToken@ is considered a
-- new call to @DeleteModel@. An idempotency token is active for 8 hours.
deleteModel_clientToken :: Lens.Lens' DeleteModel (Prelude.Maybe Prelude.Text)
deleteModel_clientToken :: Lens' DeleteModel (Maybe Text)
deleteModel_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteModel' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DeleteModel' :: DeleteModel -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DeleteModel
s@DeleteModel' {} Maybe Text
a -> DeleteModel
s {$sel:clientToken:DeleteModel' :: Maybe Text
clientToken = Maybe Text
a} :: DeleteModel)

-- | The name of the project that contains the model that you want to delete.
deleteModel_projectName :: Lens.Lens' DeleteModel Prelude.Text
deleteModel_projectName :: Lens' DeleteModel Text
deleteModel_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteModel' {Text
projectName :: Text
$sel:projectName:DeleteModel' :: DeleteModel -> Text
projectName} -> Text
projectName) (\s :: DeleteModel
s@DeleteModel' {} Text
a -> DeleteModel
s {$sel:projectName:DeleteModel' :: Text
projectName = Text
a} :: DeleteModel)

-- | The version of the model that you want to delete.
deleteModel_modelVersion :: Lens.Lens' DeleteModel Prelude.Text
deleteModel_modelVersion :: Lens' DeleteModel Text
deleteModel_modelVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteModel' {Text
modelVersion :: Text
$sel:modelVersion:DeleteModel' :: DeleteModel -> Text
modelVersion} -> Text
modelVersion) (\s :: DeleteModel
s@DeleteModel' {} Text
a -> DeleteModel
s {$sel:modelVersion:DeleteModel' :: Text
modelVersion = Text
a} :: DeleteModel)

instance Core.AWSRequest DeleteModel where
  type AWSResponse DeleteModel = DeleteModelResponse
  request :: (Service -> Service) -> DeleteModel -> Request DeleteModel
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteModel
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteModel)))
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 -> DeleteModelResponse
DeleteModelResponse'
            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
"ModelArn")
            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 DeleteModel where
  hashWithSalt :: Int -> DeleteModel -> Int
hashWithSalt Int
_salt DeleteModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:DeleteModel' :: DeleteModel -> Text
$sel:projectName:DeleteModel' :: DeleteModel -> Text
$sel:clientToken:DeleteModel' :: DeleteModel -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
modelVersion

instance Prelude.NFData DeleteModel where
  rnf :: DeleteModel -> ()
rnf DeleteModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:DeleteModel' :: DeleteModel -> Text
$sel:projectName:DeleteModel' :: DeleteModel -> Text
$sel:clientToken:DeleteModel' :: DeleteModel -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
modelVersion

instance Data.ToHeaders DeleteModel where
  toHeaders :: DeleteModel -> ResponseHeaders
toHeaders DeleteModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:DeleteModel' :: DeleteModel -> Text
$sel:projectName:DeleteModel' :: DeleteModel -> Text
$sel:clientToken:DeleteModel' :: DeleteModel -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"X-Amzn-Client-Token" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
clientToken,
        HeaderName
"Content-Type"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/x-amz-json-1.1" :: Prelude.ByteString)
      ]

instance Data.ToPath DeleteModel where
  toPath :: DeleteModel -> ByteString
toPath DeleteModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:DeleteModel' :: DeleteModel -> Text
$sel:projectName:DeleteModel' :: DeleteModel -> Text
$sel:clientToken:DeleteModel' :: DeleteModel -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2020-11-20/projects/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
projectName,
        ByteString
"/models/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
modelVersion
      ]

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

-- | /See:/ 'newDeleteModelResponse' smart constructor.
data DeleteModelResponse = DeleteModelResponse'
  { -- | The Amazon Resource Name (ARN) of the model that was deleted.
    DeleteModelResponse -> Maybe Text
modelArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteModelResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteModelResponse -> DeleteModelResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteModelResponse -> DeleteModelResponse -> Bool
$c/= :: DeleteModelResponse -> DeleteModelResponse -> Bool
== :: DeleteModelResponse -> DeleteModelResponse -> Bool
$c== :: DeleteModelResponse -> DeleteModelResponse -> Bool
Prelude.Eq, ReadPrec [DeleteModelResponse]
ReadPrec DeleteModelResponse
Int -> ReadS DeleteModelResponse
ReadS [DeleteModelResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteModelResponse]
$creadListPrec :: ReadPrec [DeleteModelResponse]
readPrec :: ReadPrec DeleteModelResponse
$creadPrec :: ReadPrec DeleteModelResponse
readList :: ReadS [DeleteModelResponse]
$creadList :: ReadS [DeleteModelResponse]
readsPrec :: Int -> ReadS DeleteModelResponse
$creadsPrec :: Int -> ReadS DeleteModelResponse
Prelude.Read, Int -> DeleteModelResponse -> ShowS
[DeleteModelResponse] -> ShowS
DeleteModelResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteModelResponse] -> ShowS
$cshowList :: [DeleteModelResponse] -> ShowS
show :: DeleteModelResponse -> String
$cshow :: DeleteModelResponse -> String
showsPrec :: Int -> DeleteModelResponse -> ShowS
$cshowsPrec :: Int -> DeleteModelResponse -> ShowS
Prelude.Show, forall x. Rep DeleteModelResponse x -> DeleteModelResponse
forall x. DeleteModelResponse -> Rep DeleteModelResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteModelResponse x -> DeleteModelResponse
$cfrom :: forall x. DeleteModelResponse -> Rep DeleteModelResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteModelResponse' 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:
--
-- 'modelArn', 'deleteModelResponse_modelArn' - The Amazon Resource Name (ARN) of the model that was deleted.
--
-- 'httpStatus', 'deleteModelResponse_httpStatus' - The response's http status code.
newDeleteModelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteModelResponse
newDeleteModelResponse :: Int -> DeleteModelResponse
newDeleteModelResponse Int
pHttpStatus_ =
  DeleteModelResponse'
    { $sel:modelArn:DeleteModelResponse' :: Maybe Text
modelArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteModelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the model that was deleted.
deleteModelResponse_modelArn :: Lens.Lens' DeleteModelResponse (Prelude.Maybe Prelude.Text)
deleteModelResponse_modelArn :: Lens' DeleteModelResponse (Maybe Text)
deleteModelResponse_modelArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteModelResponse' {Maybe Text
modelArn :: Maybe Text
$sel:modelArn:DeleteModelResponse' :: DeleteModelResponse -> Maybe Text
modelArn} -> Maybe Text
modelArn) (\s :: DeleteModelResponse
s@DeleteModelResponse' {} Maybe Text
a -> DeleteModelResponse
s {$sel:modelArn:DeleteModelResponse' :: Maybe Text
modelArn = Maybe Text
a} :: DeleteModelResponse)

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

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