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

    -- * Request Lenses
    deleteDataSource_dataSourceId,

    -- * Destructuring the Response
    DeleteDataSourceResponse (..),
    newDeleteDataSourceResponse,

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

-- |
-- Create a value of 'DeleteDataSource' 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', 'deleteDataSource_dataSourceId' - A user-supplied ID that uniquely identifies the @DataSource@.
newDeleteDataSource ::
  -- | 'dataSourceId'
  Prelude.Text ->
  DeleteDataSource
newDeleteDataSource :: Text -> DeleteDataSource
newDeleteDataSource Text
pDataSourceId_ =
  DeleteDataSource' {$sel:dataSourceId:DeleteDataSource' :: Text
dataSourceId = Text
pDataSourceId_}

-- | A user-supplied ID that uniquely identifies the @DataSource@.
deleteDataSource_dataSourceId :: Lens.Lens' DeleteDataSource Prelude.Text
deleteDataSource_dataSourceId :: Lens' DeleteDataSource Text
deleteDataSource_dataSourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDataSource' {Text
dataSourceId :: Text
$sel:dataSourceId:DeleteDataSource' :: DeleteDataSource -> Text
dataSourceId} -> Text
dataSourceId) (\s :: DeleteDataSource
s@DeleteDataSource' {} Text
a -> DeleteDataSource
s {$sel:dataSourceId:DeleteDataSource' :: Text
dataSourceId = Text
a} :: DeleteDataSource)

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

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

instance Data.ToHeaders DeleteDataSource where
  toHeaders :: DeleteDataSource -> 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.DeleteDataSource" ::
                          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 DeleteDataSource where
  toJSON :: DeleteDataSource -> Value
toJSON DeleteDataSource' {Text
dataSourceId :: Text
$sel:dataSourceId:DeleteDataSource' :: DeleteDataSource -> 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)]
      )

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

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

-- | Represents the output of a @DeleteDataSource@ operation.
--
-- /See:/ 'newDeleteDataSourceResponse' smart constructor.
data DeleteDataSourceResponse = DeleteDataSourceResponse'
  { -- | A user-supplied ID that uniquely identifies the @DataSource@. This value
    -- should be identical to the value of the @DataSourceID@ in the request.
    DeleteDataSourceResponse -> Maybe Text
dataSourceId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteDataSourceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
$c/= :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
== :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
$c== :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
Prelude.Eq, ReadPrec [DeleteDataSourceResponse]
ReadPrec DeleteDataSourceResponse
Int -> ReadS DeleteDataSourceResponse
ReadS [DeleteDataSourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDataSourceResponse]
$creadListPrec :: ReadPrec [DeleteDataSourceResponse]
readPrec :: ReadPrec DeleteDataSourceResponse
$creadPrec :: ReadPrec DeleteDataSourceResponse
readList :: ReadS [DeleteDataSourceResponse]
$creadList :: ReadS [DeleteDataSourceResponse]
readsPrec :: Int -> ReadS DeleteDataSourceResponse
$creadsPrec :: Int -> ReadS DeleteDataSourceResponse
Prelude.Read, Int -> DeleteDataSourceResponse -> ShowS
[DeleteDataSourceResponse] -> ShowS
DeleteDataSourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDataSourceResponse] -> ShowS
$cshowList :: [DeleteDataSourceResponse] -> ShowS
show :: DeleteDataSourceResponse -> String
$cshow :: DeleteDataSourceResponse -> String
showsPrec :: Int -> DeleteDataSourceResponse -> ShowS
$cshowsPrec :: Int -> DeleteDataSourceResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteDataSourceResponse x -> DeleteDataSourceResponse
forall x.
DeleteDataSourceResponse -> Rep DeleteDataSourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteDataSourceResponse x -> DeleteDataSourceResponse
$cfrom :: forall x.
DeleteDataSourceResponse -> Rep DeleteDataSourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDataSourceResponse' 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', 'deleteDataSourceResponse_dataSourceId' - A user-supplied ID that uniquely identifies the @DataSource@. This value
-- should be identical to the value of the @DataSourceID@ in the request.
--
-- 'httpStatus', 'deleteDataSourceResponse_httpStatus' - The response's http status code.
newDeleteDataSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteDataSourceResponse
newDeleteDataSourceResponse :: Int -> DeleteDataSourceResponse
newDeleteDataSourceResponse Int
pHttpStatus_ =
  DeleteDataSourceResponse'
    { $sel:dataSourceId:DeleteDataSourceResponse' :: Maybe Text
dataSourceId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteDataSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

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