{-# 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.Discovery.StartImportTask
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts an import task, which allows you to import details of your
-- on-premises environment directly into Amazon Web Services Migration Hub
-- without having to use the Application Discovery Service (ADS) tools such
-- as the Discovery Connector or Discovery Agent. This gives you the option
-- to perform migration assessment and planning directly from your imported
-- data, including the ability to group your devices as applications and
-- track their migration status.
--
-- To start an import request, do this:
--
-- 1.  Download the specially formatted comma separated value (CSV) import
--     template, which you can find here:
--     <https://s3.us-west-2.amazonaws.com/templates-7cffcf56-bd96-4b1c-b45b-a5b42f282e46/import_template.csv>.
--
-- 2.  Fill out the template with your server and application data.
--
-- 3.  Upload your import file to an Amazon S3 bucket, and make a note of
--     it\'s Object URL. Your import file must be in the CSV format.
--
-- 4.  Use the console or the @StartImportTask@ command with the Amazon Web
--     Services CLI or one of the Amazon Web Services SDKs to import the
--     records from your file.
--
-- For more information, including step-by-step procedures, see
-- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-import.html Migration Hub Import>
-- in the /Amazon Web Services Application Discovery Service User Guide/.
--
-- There are limits to the number of import tasks you can create (and
-- delete) in an Amazon Web Services account. For more information, see
-- <https://docs.aws.amazon.com/application-discovery/latest/userguide/ads_service_limits.html Amazon Web Services Application Discovery Service Limits>
-- in the /Amazon Web Services Application Discovery Service User Guide/.
module Amazonka.Discovery.StartImportTask
  ( -- * Creating a Request
    StartImportTask (..),
    newStartImportTask,

    -- * Request Lenses
    startImportTask_clientRequestToken,
    startImportTask_name,
    startImportTask_importUrl,

    -- * Destructuring the Response
    StartImportTaskResponse (..),
    newStartImportTaskResponse,

    -- * Response Lenses
    startImportTaskResponse_task,
    startImportTaskResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartImportTask' smart constructor.
data StartImportTask = StartImportTask'
  { -- | Optional. A unique token that you can provide to prevent the same import
    -- request from occurring more than once. If you don\'t provide a token, a
    -- token is automatically generated.
    --
    -- Sending more than one @StartImportTask@ request with the same client
    -- request token will return information about the original import task
    -- with that client request token.
    StartImportTask -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | A descriptive name for this request. You can use this name to filter
    -- future requests related to this import task, such as identifying
    -- applications and servers that were included in this import task. We
    -- recommend that you use a meaningful name for each import task.
    StartImportTask -> Text
name :: Prelude.Text,
    -- | The URL for your import file that you\'ve uploaded to Amazon S3.
    --
    -- If you\'re using the Amazon Web Services CLI, this URL is structured as
    -- follows: @s3:\/\/BucketName\/ImportFileName.CSV@
    StartImportTask -> Text
importUrl :: Prelude.Text
  }
  deriving (StartImportTask -> StartImportTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImportTask -> StartImportTask -> Bool
$c/= :: StartImportTask -> StartImportTask -> Bool
== :: StartImportTask -> StartImportTask -> Bool
$c== :: StartImportTask -> StartImportTask -> Bool
Prelude.Eq, ReadPrec [StartImportTask]
ReadPrec StartImportTask
Int -> ReadS StartImportTask
ReadS [StartImportTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImportTask]
$creadListPrec :: ReadPrec [StartImportTask]
readPrec :: ReadPrec StartImportTask
$creadPrec :: ReadPrec StartImportTask
readList :: ReadS [StartImportTask]
$creadList :: ReadS [StartImportTask]
readsPrec :: Int -> ReadS StartImportTask
$creadsPrec :: Int -> ReadS StartImportTask
Prelude.Read, Int -> StartImportTask -> ShowS
[StartImportTask] -> ShowS
StartImportTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImportTask] -> ShowS
$cshowList :: [StartImportTask] -> ShowS
show :: StartImportTask -> String
$cshow :: StartImportTask -> String
showsPrec :: Int -> StartImportTask -> ShowS
$cshowsPrec :: Int -> StartImportTask -> ShowS
Prelude.Show, forall x. Rep StartImportTask x -> StartImportTask
forall x. StartImportTask -> Rep StartImportTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartImportTask x -> StartImportTask
$cfrom :: forall x. StartImportTask -> Rep StartImportTask x
Prelude.Generic)

-- |
-- Create a value of 'StartImportTask' 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:
--
-- 'clientRequestToken', 'startImportTask_clientRequestToken' - Optional. A unique token that you can provide to prevent the same import
-- request from occurring more than once. If you don\'t provide a token, a
-- token is automatically generated.
--
-- Sending more than one @StartImportTask@ request with the same client
-- request token will return information about the original import task
-- with that client request token.
--
-- 'name', 'startImportTask_name' - A descriptive name for this request. You can use this name to filter
-- future requests related to this import task, such as identifying
-- applications and servers that were included in this import task. We
-- recommend that you use a meaningful name for each import task.
--
-- 'importUrl', 'startImportTask_importUrl' - The URL for your import file that you\'ve uploaded to Amazon S3.
--
-- If you\'re using the Amazon Web Services CLI, this URL is structured as
-- follows: @s3:\/\/BucketName\/ImportFileName.CSV@
newStartImportTask ::
  -- | 'name'
  Prelude.Text ->
  -- | 'importUrl'
  Prelude.Text ->
  StartImportTask
newStartImportTask :: Text -> Text -> StartImportTask
newStartImportTask Text
pName_ Text
pImportUrl_ =
  StartImportTask'
    { $sel:clientRequestToken:StartImportTask' :: Maybe Text
clientRequestToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:name:StartImportTask' :: Text
name = Text
pName_,
      $sel:importUrl:StartImportTask' :: Text
importUrl = Text
pImportUrl_
    }

-- | Optional. A unique token that you can provide to prevent the same import
-- request from occurring more than once. If you don\'t provide a token, a
-- token is automatically generated.
--
-- Sending more than one @StartImportTask@ request with the same client
-- request token will return information about the original import task
-- with that client request token.
startImportTask_clientRequestToken :: Lens.Lens' StartImportTask (Prelude.Maybe Prelude.Text)
startImportTask_clientRequestToken :: Lens' StartImportTask (Maybe Text)
startImportTask_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportTask' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:StartImportTask' :: StartImportTask -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: StartImportTask
s@StartImportTask' {} Maybe Text
a -> StartImportTask
s {$sel:clientRequestToken:StartImportTask' :: Maybe Text
clientRequestToken = Maybe Text
a} :: StartImportTask)

-- | A descriptive name for this request. You can use this name to filter
-- future requests related to this import task, such as identifying
-- applications and servers that were included in this import task. We
-- recommend that you use a meaningful name for each import task.
startImportTask_name :: Lens.Lens' StartImportTask Prelude.Text
startImportTask_name :: Lens' StartImportTask Text
startImportTask_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportTask' {Text
name :: Text
$sel:name:StartImportTask' :: StartImportTask -> Text
name} -> Text
name) (\s :: StartImportTask
s@StartImportTask' {} Text
a -> StartImportTask
s {$sel:name:StartImportTask' :: Text
name = Text
a} :: StartImportTask)

-- | The URL for your import file that you\'ve uploaded to Amazon S3.
--
-- If you\'re using the Amazon Web Services CLI, this URL is structured as
-- follows: @s3:\/\/BucketName\/ImportFileName.CSV@
startImportTask_importUrl :: Lens.Lens' StartImportTask Prelude.Text
startImportTask_importUrl :: Lens' StartImportTask Text
startImportTask_importUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportTask' {Text
importUrl :: Text
$sel:importUrl:StartImportTask' :: StartImportTask -> Text
importUrl} -> Text
importUrl) (\s :: StartImportTask
s@StartImportTask' {} Text
a -> StartImportTask
s {$sel:importUrl:StartImportTask' :: Text
importUrl = Text
a} :: StartImportTask)

instance Core.AWSRequest StartImportTask where
  type
    AWSResponse StartImportTask =
      StartImportTaskResponse
  request :: (Service -> Service) -> StartImportTask -> Request StartImportTask
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 StartImportTask
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartImportTask)))
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 ImportTask -> Int -> StartImportTaskResponse
StartImportTaskResponse'
            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
"task")
            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 StartImportTask where
  hashWithSalt :: Int -> StartImportTask -> Int
hashWithSalt Int
_salt StartImportTask' {Maybe Text
Text
importUrl :: Text
name :: Text
clientRequestToken :: Maybe Text
$sel:importUrl:StartImportTask' :: StartImportTask -> Text
$sel:name:StartImportTask' :: StartImportTask -> Text
$sel:clientRequestToken:StartImportTask' :: StartImportTask -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
importUrl

instance Prelude.NFData StartImportTask where
  rnf :: StartImportTask -> ()
rnf StartImportTask' {Maybe Text
Text
importUrl :: Text
name :: Text
clientRequestToken :: Maybe Text
$sel:importUrl:StartImportTask' :: StartImportTask -> Text
$sel:name:StartImportTask' :: StartImportTask -> Text
$sel:clientRequestToken:StartImportTask' :: StartImportTask -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
importUrl

instance Data.ToHeaders StartImportTask where
  toHeaders :: StartImportTask -> 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
"AWSPoseidonService_V2015_11_01.StartImportTask" ::
                          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 StartImportTask where
  toJSON :: StartImportTask -> Value
toJSON StartImportTask' {Maybe Text
Text
importUrl :: Text
name :: Text
clientRequestToken :: Maybe Text
$sel:importUrl:StartImportTask' :: StartImportTask -> Text
$sel:name:StartImportTask' :: StartImportTask -> Text
$sel:clientRequestToken:StartImportTask' :: StartImportTask -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientRequestToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
clientRequestToken,
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"importUrl" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
importUrl)
          ]
      )

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

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

-- | /See:/ 'newStartImportTaskResponse' smart constructor.
data StartImportTaskResponse = StartImportTaskResponse'
  { -- | An array of information related to the import task request including
    -- status information, times, IDs, the Amazon S3 Object URL for the import
    -- file, and more.
    StartImportTaskResponse -> Maybe ImportTask
task :: Prelude.Maybe ImportTask,
    -- | The response's http status code.
    StartImportTaskResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartImportTaskResponse -> StartImportTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImportTaskResponse -> StartImportTaskResponse -> Bool
$c/= :: StartImportTaskResponse -> StartImportTaskResponse -> Bool
== :: StartImportTaskResponse -> StartImportTaskResponse -> Bool
$c== :: StartImportTaskResponse -> StartImportTaskResponse -> Bool
Prelude.Eq, ReadPrec [StartImportTaskResponse]
ReadPrec StartImportTaskResponse
Int -> ReadS StartImportTaskResponse
ReadS [StartImportTaskResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImportTaskResponse]
$creadListPrec :: ReadPrec [StartImportTaskResponse]
readPrec :: ReadPrec StartImportTaskResponse
$creadPrec :: ReadPrec StartImportTaskResponse
readList :: ReadS [StartImportTaskResponse]
$creadList :: ReadS [StartImportTaskResponse]
readsPrec :: Int -> ReadS StartImportTaskResponse
$creadsPrec :: Int -> ReadS StartImportTaskResponse
Prelude.Read, Int -> StartImportTaskResponse -> ShowS
[StartImportTaskResponse] -> ShowS
StartImportTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImportTaskResponse] -> ShowS
$cshowList :: [StartImportTaskResponse] -> ShowS
show :: StartImportTaskResponse -> String
$cshow :: StartImportTaskResponse -> String
showsPrec :: Int -> StartImportTaskResponse -> ShowS
$cshowsPrec :: Int -> StartImportTaskResponse -> ShowS
Prelude.Show, forall x. Rep StartImportTaskResponse x -> StartImportTaskResponse
forall x. StartImportTaskResponse -> Rep StartImportTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartImportTaskResponse x -> StartImportTaskResponse
$cfrom :: forall x. StartImportTaskResponse -> Rep StartImportTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartImportTaskResponse' 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:
--
-- 'task', 'startImportTaskResponse_task' - An array of information related to the import task request including
-- status information, times, IDs, the Amazon S3 Object URL for the import
-- file, and more.
--
-- 'httpStatus', 'startImportTaskResponse_httpStatus' - The response's http status code.
newStartImportTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartImportTaskResponse
newStartImportTaskResponse :: Int -> StartImportTaskResponse
newStartImportTaskResponse Int
pHttpStatus_ =
  StartImportTaskResponse'
    { $sel:task:StartImportTaskResponse' :: Maybe ImportTask
task = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartImportTaskResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of information related to the import task request including
-- status information, times, IDs, the Amazon S3 Object URL for the import
-- file, and more.
startImportTaskResponse_task :: Lens.Lens' StartImportTaskResponse (Prelude.Maybe ImportTask)
startImportTaskResponse_task :: Lens' StartImportTaskResponse (Maybe ImportTask)
startImportTaskResponse_task = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportTaskResponse' {Maybe ImportTask
task :: Maybe ImportTask
$sel:task:StartImportTaskResponse' :: StartImportTaskResponse -> Maybe ImportTask
task} -> Maybe ImportTask
task) (\s :: StartImportTaskResponse
s@StartImportTaskResponse' {} Maybe ImportTask
a -> StartImportTaskResponse
s {$sel:task:StartImportTaskResponse' :: Maybe ImportTask
task = Maybe ImportTask
a} :: StartImportTaskResponse)

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

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