{-# 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.UpdateBatchPrediction
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the @BatchPredictionName@ of a @BatchPrediction@.
--
-- You can use the @GetBatchPrediction@ operation to view the contents of
-- the updated data element.
module Amazonka.MachineLearning.UpdateBatchPrediction
  ( -- * Creating a Request
    UpdateBatchPrediction (..),
    newUpdateBatchPrediction,

    -- * Request Lenses
    updateBatchPrediction_batchPredictionId,
    updateBatchPrediction_batchPredictionName,

    -- * Destructuring the Response
    UpdateBatchPredictionResponse (..),
    newUpdateBatchPredictionResponse,

    -- * Response Lenses
    updateBatchPredictionResponse_batchPredictionId,
    updateBatchPredictionResponse_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:/ 'newUpdateBatchPrediction' smart constructor.
data UpdateBatchPrediction = UpdateBatchPrediction'
  { -- | The ID assigned to the @BatchPrediction@ during creation.
    UpdateBatchPrediction -> Text
batchPredictionId :: Prelude.Text,
    -- | A new user-supplied name or description of the @BatchPrediction@.
    UpdateBatchPrediction -> Text
batchPredictionName :: Prelude.Text
  }
  deriving (UpdateBatchPrediction -> UpdateBatchPrediction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateBatchPrediction -> UpdateBatchPrediction -> Bool
$c/= :: UpdateBatchPrediction -> UpdateBatchPrediction -> Bool
== :: UpdateBatchPrediction -> UpdateBatchPrediction -> Bool
$c== :: UpdateBatchPrediction -> UpdateBatchPrediction -> Bool
Prelude.Eq, ReadPrec [UpdateBatchPrediction]
ReadPrec UpdateBatchPrediction
Int -> ReadS UpdateBatchPrediction
ReadS [UpdateBatchPrediction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateBatchPrediction]
$creadListPrec :: ReadPrec [UpdateBatchPrediction]
readPrec :: ReadPrec UpdateBatchPrediction
$creadPrec :: ReadPrec UpdateBatchPrediction
readList :: ReadS [UpdateBatchPrediction]
$creadList :: ReadS [UpdateBatchPrediction]
readsPrec :: Int -> ReadS UpdateBatchPrediction
$creadsPrec :: Int -> ReadS UpdateBatchPrediction
Prelude.Read, Int -> UpdateBatchPrediction -> ShowS
[UpdateBatchPrediction] -> ShowS
UpdateBatchPrediction -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateBatchPrediction] -> ShowS
$cshowList :: [UpdateBatchPrediction] -> ShowS
show :: UpdateBatchPrediction -> String
$cshow :: UpdateBatchPrediction -> String
showsPrec :: Int -> UpdateBatchPrediction -> ShowS
$cshowsPrec :: Int -> UpdateBatchPrediction -> ShowS
Prelude.Show, forall x. Rep UpdateBatchPrediction x -> UpdateBatchPrediction
forall x. UpdateBatchPrediction -> Rep UpdateBatchPrediction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateBatchPrediction x -> UpdateBatchPrediction
$cfrom :: forall x. UpdateBatchPrediction -> Rep UpdateBatchPrediction x
Prelude.Generic)

-- |
-- Create a value of 'UpdateBatchPrediction' 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', 'updateBatchPrediction_batchPredictionId' - The ID assigned to the @BatchPrediction@ during creation.
--
-- 'batchPredictionName', 'updateBatchPrediction_batchPredictionName' - A new user-supplied name or description of the @BatchPrediction@.
newUpdateBatchPrediction ::
  -- | 'batchPredictionId'
  Prelude.Text ->
  -- | 'batchPredictionName'
  Prelude.Text ->
  UpdateBatchPrediction
newUpdateBatchPrediction :: Text -> Text -> UpdateBatchPrediction
newUpdateBatchPrediction
  Text
pBatchPredictionId_
  Text
pBatchPredictionName_ =
    UpdateBatchPrediction'
      { $sel:batchPredictionId:UpdateBatchPrediction' :: Text
batchPredictionId =
          Text
pBatchPredictionId_,
        $sel:batchPredictionName:UpdateBatchPrediction' :: Text
batchPredictionName = Text
pBatchPredictionName_
      }

-- | The ID assigned to the @BatchPrediction@ during creation.
updateBatchPrediction_batchPredictionId :: Lens.Lens' UpdateBatchPrediction Prelude.Text
updateBatchPrediction_batchPredictionId :: Lens' UpdateBatchPrediction Text
updateBatchPrediction_batchPredictionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBatchPrediction' {Text
batchPredictionId :: Text
$sel:batchPredictionId:UpdateBatchPrediction' :: UpdateBatchPrediction -> Text
batchPredictionId} -> Text
batchPredictionId) (\s :: UpdateBatchPrediction
s@UpdateBatchPrediction' {} Text
a -> UpdateBatchPrediction
s {$sel:batchPredictionId:UpdateBatchPrediction' :: Text
batchPredictionId = Text
a} :: UpdateBatchPrediction)

-- | A new user-supplied name or description of the @BatchPrediction@.
updateBatchPrediction_batchPredictionName :: Lens.Lens' UpdateBatchPrediction Prelude.Text
updateBatchPrediction_batchPredictionName :: Lens' UpdateBatchPrediction Text
updateBatchPrediction_batchPredictionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBatchPrediction' {Text
batchPredictionName :: Text
$sel:batchPredictionName:UpdateBatchPrediction' :: UpdateBatchPrediction -> Text
batchPredictionName} -> Text
batchPredictionName) (\s :: UpdateBatchPrediction
s@UpdateBatchPrediction' {} Text
a -> UpdateBatchPrediction
s {$sel:batchPredictionName:UpdateBatchPrediction' :: Text
batchPredictionName = Text
a} :: UpdateBatchPrediction)

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

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

instance Data.ToHeaders UpdateBatchPrediction where
  toHeaders :: UpdateBatchPrediction -> 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.UpdateBatchPrediction" ::
                          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 UpdateBatchPrediction where
  toJSON :: UpdateBatchPrediction -> Value
toJSON UpdateBatchPrediction' {Text
batchPredictionName :: Text
batchPredictionId :: Text
$sel:batchPredictionName:UpdateBatchPrediction' :: UpdateBatchPrediction -> Text
$sel:batchPredictionId:UpdateBatchPrediction' :: UpdateBatchPrediction -> 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),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"BatchPredictionName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
batchPredictionName)
          ]
      )

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

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

-- | Represents the output of an @UpdateBatchPrediction@ operation.
--
-- You can see the updated content by using the @GetBatchPrediction@
-- operation.
--
-- /See:/ 'newUpdateBatchPredictionResponse' smart constructor.
data UpdateBatchPredictionResponse = UpdateBatchPredictionResponse'
  { -- | The ID assigned to the @BatchPrediction@ during creation. This value
    -- should be identical to the value of the @BatchPredictionId@ in the
    -- request.
    UpdateBatchPredictionResponse -> Maybe Text
batchPredictionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateBatchPredictionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateBatchPredictionResponse
-> UpdateBatchPredictionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateBatchPredictionResponse
-> UpdateBatchPredictionResponse -> Bool
$c/= :: UpdateBatchPredictionResponse
-> UpdateBatchPredictionResponse -> Bool
== :: UpdateBatchPredictionResponse
-> UpdateBatchPredictionResponse -> Bool
$c== :: UpdateBatchPredictionResponse
-> UpdateBatchPredictionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateBatchPredictionResponse]
ReadPrec UpdateBatchPredictionResponse
Int -> ReadS UpdateBatchPredictionResponse
ReadS [UpdateBatchPredictionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateBatchPredictionResponse]
$creadListPrec :: ReadPrec [UpdateBatchPredictionResponse]
readPrec :: ReadPrec UpdateBatchPredictionResponse
$creadPrec :: ReadPrec UpdateBatchPredictionResponse
readList :: ReadS [UpdateBatchPredictionResponse]
$creadList :: ReadS [UpdateBatchPredictionResponse]
readsPrec :: Int -> ReadS UpdateBatchPredictionResponse
$creadsPrec :: Int -> ReadS UpdateBatchPredictionResponse
Prelude.Read, Int -> UpdateBatchPredictionResponse -> ShowS
[UpdateBatchPredictionResponse] -> ShowS
UpdateBatchPredictionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateBatchPredictionResponse] -> ShowS
$cshowList :: [UpdateBatchPredictionResponse] -> ShowS
show :: UpdateBatchPredictionResponse -> String
$cshow :: UpdateBatchPredictionResponse -> String
showsPrec :: Int -> UpdateBatchPredictionResponse -> ShowS
$cshowsPrec :: Int -> UpdateBatchPredictionResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateBatchPredictionResponse x
-> UpdateBatchPredictionResponse
forall x.
UpdateBatchPredictionResponse
-> Rep UpdateBatchPredictionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateBatchPredictionResponse x
-> UpdateBatchPredictionResponse
$cfrom :: forall x.
UpdateBatchPredictionResponse
-> Rep UpdateBatchPredictionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateBatchPredictionResponse' 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', 'updateBatchPredictionResponse_batchPredictionId' - The ID assigned to the @BatchPrediction@ during creation. This value
-- should be identical to the value of the @BatchPredictionId@ in the
-- request.
--
-- 'httpStatus', 'updateBatchPredictionResponse_httpStatus' - The response's http status code.
newUpdateBatchPredictionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateBatchPredictionResponse
newUpdateBatchPredictionResponse :: Int -> UpdateBatchPredictionResponse
newUpdateBatchPredictionResponse Int
pHttpStatus_ =
  UpdateBatchPredictionResponse'
    { $sel:batchPredictionId:UpdateBatchPredictionResponse' :: Maybe Text
batchPredictionId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateBatchPredictionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID assigned to the @BatchPrediction@ during creation. This value
-- should be identical to the value of the @BatchPredictionId@ in the
-- request.
updateBatchPredictionResponse_batchPredictionId :: Lens.Lens' UpdateBatchPredictionResponse (Prelude.Maybe Prelude.Text)
updateBatchPredictionResponse_batchPredictionId :: Lens' UpdateBatchPredictionResponse (Maybe Text)
updateBatchPredictionResponse_batchPredictionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateBatchPredictionResponse' {Maybe Text
batchPredictionId :: Maybe Text
$sel:batchPredictionId:UpdateBatchPredictionResponse' :: UpdateBatchPredictionResponse -> Maybe Text
batchPredictionId} -> Maybe Text
batchPredictionId) (\s :: UpdateBatchPredictionResponse
s@UpdateBatchPredictionResponse' {} Maybe Text
a -> UpdateBatchPredictionResponse
s {$sel:batchPredictionId:UpdateBatchPredictionResponse' :: Maybe Text
batchPredictionId = Maybe Text
a} :: UpdateBatchPredictionResponse)

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

instance Prelude.NFData UpdateBatchPredictionResponse where
  rnf :: UpdateBatchPredictionResponse -> ()
rnf UpdateBatchPredictionResponse' {Int
Maybe Text
httpStatus :: Int
batchPredictionId :: Maybe Text
$sel:httpStatus:UpdateBatchPredictionResponse' :: UpdateBatchPredictionResponse -> Int
$sel:batchPredictionId:UpdateBatchPredictionResponse' :: UpdateBatchPredictionResponse -> 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