{-# 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.UpdateDataSource
-- 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 @DataSourceName@ of a @DataSource@.
--
-- You can use the @GetDataSource@ operation to view the contents of the
-- updated data element.
module Amazonka.MachineLearning.UpdateDataSource
  ( -- * Creating a Request
    UpdateDataSource (..),
    newUpdateDataSource,

    -- * Request Lenses
    updateDataSource_dataSourceId,
    updateDataSource_dataSourceName,

    -- * Destructuring the Response
    UpdateDataSourceResponse (..),
    newUpdateDataSourceResponse,

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

-- |
-- Create a value of 'UpdateDataSource' 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:
--
-- 'dataSourceId', 'updateDataSource_dataSourceId' - The ID assigned to the @DataSource@ during creation.
--
-- 'dataSourceName', 'updateDataSource_dataSourceName' - A new user-supplied name or description of the @DataSource@ that will
-- replace the current description.
newUpdateDataSource ::
  -- | 'dataSourceId'
  Prelude.Text ->
  -- | 'dataSourceName'
  Prelude.Text ->
  UpdateDataSource
newUpdateDataSource :: Text -> Text -> UpdateDataSource
newUpdateDataSource Text
pDataSourceId_ Text
pDataSourceName_ =
  UpdateDataSource'
    { $sel:dataSourceId:UpdateDataSource' :: Text
dataSourceId = Text
pDataSourceId_,
      $sel:dataSourceName:UpdateDataSource' :: Text
dataSourceName = Text
pDataSourceName_
    }

-- | The ID assigned to the @DataSource@ during creation.
updateDataSource_dataSourceId :: Lens.Lens' UpdateDataSource Prelude.Text
updateDataSource_dataSourceId :: Lens' UpdateDataSource Text
updateDataSource_dataSourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDataSource' {Text
dataSourceId :: Text
$sel:dataSourceId:UpdateDataSource' :: UpdateDataSource -> Text
dataSourceId} -> Text
dataSourceId) (\s :: UpdateDataSource
s@UpdateDataSource' {} Text
a -> UpdateDataSource
s {$sel:dataSourceId:UpdateDataSource' :: Text
dataSourceId = Text
a} :: UpdateDataSource)

-- | A new user-supplied name or description of the @DataSource@ that will
-- replace the current description.
updateDataSource_dataSourceName :: Lens.Lens' UpdateDataSource Prelude.Text
updateDataSource_dataSourceName :: Lens' UpdateDataSource Text
updateDataSource_dataSourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateDataSource' {Text
dataSourceName :: Text
$sel:dataSourceName:UpdateDataSource' :: UpdateDataSource -> Text
dataSourceName} -> Text
dataSourceName) (\s :: UpdateDataSource
s@UpdateDataSource' {} Text
a -> UpdateDataSource
s {$sel:dataSourceName:UpdateDataSource' :: Text
dataSourceName = Text
a} :: UpdateDataSource)

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

instance Prelude.NFData UpdateDataSource where
  rnf :: UpdateDataSource -> ()
rnf UpdateDataSource' {Text
dataSourceName :: Text
dataSourceId :: Text
$sel:dataSourceName:UpdateDataSource' :: UpdateDataSource -> Text
$sel:dataSourceId:UpdateDataSource' :: UpdateDataSource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
dataSourceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dataSourceName

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

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

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

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

-- |
-- Create a value of 'UpdateDataSourceResponse' 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:
--
-- 'dataSourceId', 'updateDataSourceResponse_dataSourceId' - The ID assigned to the @DataSource@ during creation. This value should
-- be identical to the value of the @DataSourceID@ in the request.
--
-- 'httpStatus', 'updateDataSourceResponse_httpStatus' - The response's http status code.
newUpdateDataSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateDataSourceResponse
newUpdateDataSourceResponse :: Int -> UpdateDataSourceResponse
newUpdateDataSourceResponse Int
pHttpStatus_ =
  UpdateDataSourceResponse'
    { $sel:dataSourceId:UpdateDataSourceResponse' :: Maybe Text
dataSourceId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateDataSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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