{-# 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.StopModel
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops the hosting of a running model. The operation might take a while
-- to complete. To check the current status, call DescribeModel.
--
-- After the model hosting stops, the @Status@ of the model is @TRAINED@.
--
-- This operation requires permissions to perform the
-- @lookoutvision:StopModel@ operation.
module Amazonka.LookoutVision.StopModel
  ( -- * Creating a Request
    StopModel (..),
    newStopModel,

    -- * Request Lenses
    stopModel_clientToken,
    stopModel_projectName,
    stopModel_modelVersion,

    -- * Destructuring the Response
    StopModelResponse (..),
    newStopModelResponse,

    -- * Response Lenses
    stopModelResponse_status,
    stopModelResponse_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:/ 'newStopModel' smart constructor.
data StopModel = StopModel'
  { -- | ClientToken is an idempotency token that ensures a call to @StopModel@
    -- completes only once. You choose the value to pass. For example, An issue
    -- might prevent you from getting a response from @StopModel@. In this
    -- case, safely retry your call to @StopModel@ 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 stop 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 @StopModel@. An idempotency token is active for 8 hours.
    StopModel -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the project that contains the model that you want to stop.
    StopModel -> Text
projectName :: Prelude.Text,
    -- | The version of the model that you want to stop.
    StopModel -> Text
modelVersion :: Prelude.Text
  }
  deriving (StopModel -> StopModel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopModel -> StopModel -> Bool
$c/= :: StopModel -> StopModel -> Bool
== :: StopModel -> StopModel -> Bool
$c== :: StopModel -> StopModel -> Bool
Prelude.Eq, ReadPrec [StopModel]
ReadPrec StopModel
Int -> ReadS StopModel
ReadS [StopModel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopModel]
$creadListPrec :: ReadPrec [StopModel]
readPrec :: ReadPrec StopModel
$creadPrec :: ReadPrec StopModel
readList :: ReadS [StopModel]
$creadList :: ReadS [StopModel]
readsPrec :: Int -> ReadS StopModel
$creadsPrec :: Int -> ReadS StopModel
Prelude.Read, Int -> StopModel -> ShowS
[StopModel] -> ShowS
StopModel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopModel] -> ShowS
$cshowList :: [StopModel] -> ShowS
show :: StopModel -> String
$cshow :: StopModel -> String
showsPrec :: Int -> StopModel -> ShowS
$cshowsPrec :: Int -> StopModel -> ShowS
Prelude.Show, forall x. Rep StopModel x -> StopModel
forall x. StopModel -> Rep StopModel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopModel x -> StopModel
$cfrom :: forall x. StopModel -> Rep StopModel x
Prelude.Generic)

-- |
-- Create a value of 'StopModel' 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', 'stopModel_clientToken' - ClientToken is an idempotency token that ensures a call to @StopModel@
-- completes only once. You choose the value to pass. For example, An issue
-- might prevent you from getting a response from @StopModel@. In this
-- case, safely retry your call to @StopModel@ 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 stop 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 @StopModel@. An idempotency token is active for 8 hours.
--
-- 'projectName', 'stopModel_projectName' - The name of the project that contains the model that you want to stop.
--
-- 'modelVersion', 'stopModel_modelVersion' - The version of the model that you want to stop.
newStopModel ::
  -- | 'projectName'
  Prelude.Text ->
  -- | 'modelVersion'
  Prelude.Text ->
  StopModel
newStopModel :: Text -> Text -> StopModel
newStopModel Text
pProjectName_ Text
pModelVersion_ =
  StopModel'
    { $sel:clientToken:StopModel' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:StopModel' :: Text
projectName = Text
pProjectName_,
      $sel:modelVersion:StopModel' :: Text
modelVersion = Text
pModelVersion_
    }

-- | ClientToken is an idempotency token that ensures a call to @StopModel@
-- completes only once. You choose the value to pass. For example, An issue
-- might prevent you from getting a response from @StopModel@. In this
-- case, safely retry your call to @StopModel@ 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 stop 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 @StopModel@. An idempotency token is active for 8 hours.
stopModel_clientToken :: Lens.Lens' StopModel (Prelude.Maybe Prelude.Text)
stopModel_clientToken :: Lens' StopModel (Maybe Text)
stopModel_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopModel' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:StopModel' :: StopModel -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: StopModel
s@StopModel' {} Maybe Text
a -> StopModel
s {$sel:clientToken:StopModel' :: Maybe Text
clientToken = Maybe Text
a} :: StopModel)

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

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

instance Core.AWSRequest StopModel where
  type AWSResponse StopModel = StopModelResponse
  request :: (Service -> Service) -> StopModel -> Request StopModel
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 StopModel
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopModel)))
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 ModelHostingStatus -> Int -> StopModelResponse
StopModelResponse'
            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
"Status")
            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 StopModel where
  hashWithSalt :: Int -> StopModel -> Int
hashWithSalt Int
_salt StopModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:StopModel' :: StopModel -> Text
$sel:projectName:StopModel' :: StopModel -> Text
$sel:clientToken:StopModel' :: StopModel -> 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 StopModel where
  rnf :: StopModel -> ()
rnf StopModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:StopModel' :: StopModel -> Text
$sel:projectName:StopModel' :: StopModel -> Text
$sel:clientToken:StopModel' :: StopModel -> 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 StopModel where
  toHeaders :: StopModel -> ResponseHeaders
toHeaders StopModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:StopModel' :: StopModel -> Text
$sel:projectName:StopModel' :: StopModel -> Text
$sel:clientToken:StopModel' :: StopModel -> 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.ToJSON StopModel where
  toJSON :: StopModel -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath StopModel where
  toPath :: StopModel -> ByteString
toPath StopModel' {Maybe Text
Text
modelVersion :: Text
projectName :: Text
clientToken :: Maybe Text
$sel:modelVersion:StopModel' :: StopModel -> Text
$sel:projectName:StopModel' :: StopModel -> Text
$sel:clientToken:StopModel' :: StopModel -> 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,
        ByteString
"/stop"
      ]

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

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

-- |
-- Create a value of 'StopModelResponse' 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:
--
-- 'status', 'stopModelResponse_status' - The status of the model.
--
-- 'httpStatus', 'stopModelResponse_httpStatus' - The response's http status code.
newStopModelResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopModelResponse
newStopModelResponse :: Int -> StopModelResponse
newStopModelResponse Int
pHttpStatus_ =
  StopModelResponse'
    { $sel:status:StopModelResponse' :: Maybe ModelHostingStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StopModelResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The status of the model.
stopModelResponse_status :: Lens.Lens' StopModelResponse (Prelude.Maybe ModelHostingStatus)
stopModelResponse_status :: Lens' StopModelResponse (Maybe ModelHostingStatus)
stopModelResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopModelResponse' {Maybe ModelHostingStatus
status :: Maybe ModelHostingStatus
$sel:status:StopModelResponse' :: StopModelResponse -> Maybe ModelHostingStatus
status} -> Maybe ModelHostingStatus
status) (\s :: StopModelResponse
s@StopModelResponse' {} Maybe ModelHostingStatus
a -> StopModelResponse
s {$sel:status:StopModelResponse' :: Maybe ModelHostingStatus
status = Maybe ModelHostingStatus
a} :: StopModelResponse)

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

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