{-# 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.MigrationHubStrategy.StartImportFileTask
-- 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 a file import.
module Amazonka.MigrationHubStrategy.StartImportFileTask
  ( -- * Creating a Request
    StartImportFileTask (..),
    newStartImportFileTask,

    -- * Request Lenses
    startImportFileTask_dataSourceType,
    startImportFileTask_groupId,
    startImportFileTask_s3bucketForReportData,
    startImportFileTask_s3Bucket,
    startImportFileTask_name,
    startImportFileTask_s3key,

    -- * Destructuring the Response
    StartImportFileTaskResponse (..),
    newStartImportFileTaskResponse,

    -- * Response Lenses
    startImportFileTaskResponse_id,
    startImportFileTaskResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartImportFileTask' smart constructor.
data StartImportFileTask = StartImportFileTask'
  { -- | Specifies the source that the servers are coming from. By default,
    -- Strategy Recommendations assumes that the servers specified in the
    -- import file are available in AWS Application Discovery Service.
    StartImportFileTask -> Maybe DataSourceType
dataSourceType :: Prelude.Maybe DataSourceType,
    -- | Groups the resources in the import file together with a unique name.
    -- This ID can be as filter in @ListApplicationComponents@ and
    -- @ListServers@.
    StartImportFileTask -> Maybe [Group]
groupId :: Prelude.Maybe [Group],
    -- | The S3 bucket where Strategy Recommendations uploads import results. The
    -- bucket name is required to begin with migrationhub-strategy-.
    StartImportFileTask -> Maybe Text
s3bucketForReportData :: Prelude.Maybe Prelude.Text,
    -- | The S3 bucket where the import file is located. The bucket name is
    -- required to begin with @migrationhub-strategy-@.
    StartImportFileTask -> Text
s3Bucket :: Prelude.Text,
    -- | A descriptive name for the request.
    StartImportFileTask -> Text
name :: Prelude.Text,
    -- | The Amazon S3 key name of the import file.
    StartImportFileTask -> Text
s3key :: Prelude.Text
  }
  deriving (StartImportFileTask -> StartImportFileTask -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImportFileTask -> StartImportFileTask -> Bool
$c/= :: StartImportFileTask -> StartImportFileTask -> Bool
== :: StartImportFileTask -> StartImportFileTask -> Bool
$c== :: StartImportFileTask -> StartImportFileTask -> Bool
Prelude.Eq, ReadPrec [StartImportFileTask]
ReadPrec StartImportFileTask
Int -> ReadS StartImportFileTask
ReadS [StartImportFileTask]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImportFileTask]
$creadListPrec :: ReadPrec [StartImportFileTask]
readPrec :: ReadPrec StartImportFileTask
$creadPrec :: ReadPrec StartImportFileTask
readList :: ReadS [StartImportFileTask]
$creadList :: ReadS [StartImportFileTask]
readsPrec :: Int -> ReadS StartImportFileTask
$creadsPrec :: Int -> ReadS StartImportFileTask
Prelude.Read, Int -> StartImportFileTask -> ShowS
[StartImportFileTask] -> ShowS
StartImportFileTask -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImportFileTask] -> ShowS
$cshowList :: [StartImportFileTask] -> ShowS
show :: StartImportFileTask -> String
$cshow :: StartImportFileTask -> String
showsPrec :: Int -> StartImportFileTask -> ShowS
$cshowsPrec :: Int -> StartImportFileTask -> ShowS
Prelude.Show, forall x. Rep StartImportFileTask x -> StartImportFileTask
forall x. StartImportFileTask -> Rep StartImportFileTask x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartImportFileTask x -> StartImportFileTask
$cfrom :: forall x. StartImportFileTask -> Rep StartImportFileTask x
Prelude.Generic)

-- |
-- Create a value of 'StartImportFileTask' 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:
--
-- 'dataSourceType', 'startImportFileTask_dataSourceType' - Specifies the source that the servers are coming from. By default,
-- Strategy Recommendations assumes that the servers specified in the
-- import file are available in AWS Application Discovery Service.
--
-- 'groupId', 'startImportFileTask_groupId' - Groups the resources in the import file together with a unique name.
-- This ID can be as filter in @ListApplicationComponents@ and
-- @ListServers@.
--
-- 's3bucketForReportData', 'startImportFileTask_s3bucketForReportData' - The S3 bucket where Strategy Recommendations uploads import results. The
-- bucket name is required to begin with migrationhub-strategy-.
--
-- 's3Bucket', 'startImportFileTask_s3Bucket' - The S3 bucket where the import file is located. The bucket name is
-- required to begin with @migrationhub-strategy-@.
--
-- 'name', 'startImportFileTask_name' - A descriptive name for the request.
--
-- 's3key', 'startImportFileTask_s3key' - The Amazon S3 key name of the import file.
newStartImportFileTask ::
  -- | 's3Bucket'
  Prelude.Text ->
  -- | 'name'
  Prelude.Text ->
  -- | 's3key'
  Prelude.Text ->
  StartImportFileTask
newStartImportFileTask :: Text -> Text -> Text -> StartImportFileTask
newStartImportFileTask Text
pS3Bucket_ Text
pName_ Text
pS3key_ =
  StartImportFileTask'
    { $sel:dataSourceType:StartImportFileTask' :: Maybe DataSourceType
dataSourceType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:groupId:StartImportFileTask' :: Maybe [Group]
groupId = forall a. Maybe a
Prelude.Nothing,
      $sel:s3bucketForReportData:StartImportFileTask' :: Maybe Text
s3bucketForReportData = forall a. Maybe a
Prelude.Nothing,
      $sel:s3Bucket:StartImportFileTask' :: Text
s3Bucket = Text
pS3Bucket_,
      $sel:name:StartImportFileTask' :: Text
name = Text
pName_,
      $sel:s3key:StartImportFileTask' :: Text
s3key = Text
pS3key_
    }

-- | Specifies the source that the servers are coming from. By default,
-- Strategy Recommendations assumes that the servers specified in the
-- import file are available in AWS Application Discovery Service.
startImportFileTask_dataSourceType :: Lens.Lens' StartImportFileTask (Prelude.Maybe DataSourceType)
startImportFileTask_dataSourceType :: Lens' StartImportFileTask (Maybe DataSourceType)
startImportFileTask_dataSourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTask' {Maybe DataSourceType
dataSourceType :: Maybe DataSourceType
$sel:dataSourceType:StartImportFileTask' :: StartImportFileTask -> Maybe DataSourceType
dataSourceType} -> Maybe DataSourceType
dataSourceType) (\s :: StartImportFileTask
s@StartImportFileTask' {} Maybe DataSourceType
a -> StartImportFileTask
s {$sel:dataSourceType:StartImportFileTask' :: Maybe DataSourceType
dataSourceType = Maybe DataSourceType
a} :: StartImportFileTask)

-- | Groups the resources in the import file together with a unique name.
-- This ID can be as filter in @ListApplicationComponents@ and
-- @ListServers@.
startImportFileTask_groupId :: Lens.Lens' StartImportFileTask (Prelude.Maybe [Group])
startImportFileTask_groupId :: Lens' StartImportFileTask (Maybe [Group])
startImportFileTask_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTask' {Maybe [Group]
groupId :: Maybe [Group]
$sel:groupId:StartImportFileTask' :: StartImportFileTask -> Maybe [Group]
groupId} -> Maybe [Group]
groupId) (\s :: StartImportFileTask
s@StartImportFileTask' {} Maybe [Group]
a -> StartImportFileTask
s {$sel:groupId:StartImportFileTask' :: Maybe [Group]
groupId = Maybe [Group]
a} :: StartImportFileTask) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The S3 bucket where Strategy Recommendations uploads import results. The
-- bucket name is required to begin with migrationhub-strategy-.
startImportFileTask_s3bucketForReportData :: Lens.Lens' StartImportFileTask (Prelude.Maybe Prelude.Text)
startImportFileTask_s3bucketForReportData :: Lens' StartImportFileTask (Maybe Text)
startImportFileTask_s3bucketForReportData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTask' {Maybe Text
s3bucketForReportData :: Maybe Text
$sel:s3bucketForReportData:StartImportFileTask' :: StartImportFileTask -> Maybe Text
s3bucketForReportData} -> Maybe Text
s3bucketForReportData) (\s :: StartImportFileTask
s@StartImportFileTask' {} Maybe Text
a -> StartImportFileTask
s {$sel:s3bucketForReportData:StartImportFileTask' :: Maybe Text
s3bucketForReportData = Maybe Text
a} :: StartImportFileTask)

-- | The S3 bucket where the import file is located. The bucket name is
-- required to begin with @migrationhub-strategy-@.
startImportFileTask_s3Bucket :: Lens.Lens' StartImportFileTask Prelude.Text
startImportFileTask_s3Bucket :: Lens' StartImportFileTask Text
startImportFileTask_s3Bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTask' {Text
s3Bucket :: Text
$sel:s3Bucket:StartImportFileTask' :: StartImportFileTask -> Text
s3Bucket} -> Text
s3Bucket) (\s :: StartImportFileTask
s@StartImportFileTask' {} Text
a -> StartImportFileTask
s {$sel:s3Bucket:StartImportFileTask' :: Text
s3Bucket = Text
a} :: StartImportFileTask)

-- | A descriptive name for the request.
startImportFileTask_name :: Lens.Lens' StartImportFileTask Prelude.Text
startImportFileTask_name :: Lens' StartImportFileTask Text
startImportFileTask_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTask' {Text
name :: Text
$sel:name:StartImportFileTask' :: StartImportFileTask -> Text
name} -> Text
name) (\s :: StartImportFileTask
s@StartImportFileTask' {} Text
a -> StartImportFileTask
s {$sel:name:StartImportFileTask' :: Text
name = Text
a} :: StartImportFileTask)

-- | The Amazon S3 key name of the import file.
startImportFileTask_s3key :: Lens.Lens' StartImportFileTask Prelude.Text
startImportFileTask_s3key :: Lens' StartImportFileTask Text
startImportFileTask_s3key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTask' {Text
s3key :: Text
$sel:s3key:StartImportFileTask' :: StartImportFileTask -> Text
s3key} -> Text
s3key) (\s :: StartImportFileTask
s@StartImportFileTask' {} Text
a -> StartImportFileTask
s {$sel:s3key:StartImportFileTask' :: Text
s3key = Text
a} :: StartImportFileTask)

instance Core.AWSRequest StartImportFileTask where
  type
    AWSResponse StartImportFileTask =
      StartImportFileTaskResponse
  request :: (Service -> Service)
-> StartImportFileTask -> Request StartImportFileTask
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 StartImportFileTask
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartImportFileTask)))
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 -> StartImportFileTaskResponse
StartImportFileTaskResponse'
            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
"id")
            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 StartImportFileTask where
  hashWithSalt :: Int -> StartImportFileTask -> Int
hashWithSalt Int
_salt StartImportFileTask' {Maybe [Group]
Maybe Text
Maybe DataSourceType
Text
s3key :: Text
name :: Text
s3Bucket :: Text
s3bucketForReportData :: Maybe Text
groupId :: Maybe [Group]
dataSourceType :: Maybe DataSourceType
$sel:s3key:StartImportFileTask' :: StartImportFileTask -> Text
$sel:name:StartImportFileTask' :: StartImportFileTask -> Text
$sel:s3Bucket:StartImportFileTask' :: StartImportFileTask -> Text
$sel:s3bucketForReportData:StartImportFileTask' :: StartImportFileTask -> Maybe Text
$sel:groupId:StartImportFileTask' :: StartImportFileTask -> Maybe [Group]
$sel:dataSourceType:StartImportFileTask' :: StartImportFileTask -> Maybe DataSourceType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataSourceType
dataSourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Group]
groupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3bucketForReportData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3Bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3key

instance Prelude.NFData StartImportFileTask where
  rnf :: StartImportFileTask -> ()
rnf StartImportFileTask' {Maybe [Group]
Maybe Text
Maybe DataSourceType
Text
s3key :: Text
name :: Text
s3Bucket :: Text
s3bucketForReportData :: Maybe Text
groupId :: Maybe [Group]
dataSourceType :: Maybe DataSourceType
$sel:s3key:StartImportFileTask' :: StartImportFileTask -> Text
$sel:name:StartImportFileTask' :: StartImportFileTask -> Text
$sel:s3Bucket:StartImportFileTask' :: StartImportFileTask -> Text
$sel:s3bucketForReportData:StartImportFileTask' :: StartImportFileTask -> Maybe Text
$sel:groupId:StartImportFileTask' :: StartImportFileTask -> Maybe [Group]
$sel:dataSourceType:StartImportFileTask' :: StartImportFileTask -> Maybe DataSourceType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceType
dataSourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Group]
groupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3bucketForReportData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
s3Bucket
      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
s3key

instance Data.ToHeaders StartImportFileTask where
  toHeaders :: StartImportFileTask -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StartImportFileTask where
  toJSON :: StartImportFileTask -> Value
toJSON StartImportFileTask' {Maybe [Group]
Maybe Text
Maybe DataSourceType
Text
s3key :: Text
name :: Text
s3Bucket :: Text
s3bucketForReportData :: Maybe Text
groupId :: Maybe [Group]
dataSourceType :: Maybe DataSourceType
$sel:s3key:StartImportFileTask' :: StartImportFileTask -> Text
$sel:name:StartImportFileTask' :: StartImportFileTask -> Text
$sel:s3Bucket:StartImportFileTask' :: StartImportFileTask -> Text
$sel:s3bucketForReportData:StartImportFileTask' :: StartImportFileTask -> Maybe Text
$sel:groupId:StartImportFileTask' :: StartImportFileTask -> Maybe [Group]
$sel:dataSourceType:StartImportFileTask' :: StartImportFileTask -> Maybe DataSourceType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"dataSourceType" 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 DataSourceType
dataSourceType,
            (Key
"groupId" 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 [Group]
groupId,
            (Key
"s3bucketForReportData" 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
s3bucketForReportData,
            forall a. a -> Maybe a
Prelude.Just (Key
"S3Bucket" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
s3Bucket),
            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
"s3key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
s3key)
          ]
      )

instance Data.ToPath StartImportFileTask where
  toPath :: StartImportFileTask -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/start-import-file-task"

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

-- | /See:/ 'newStartImportFileTaskResponse' smart constructor.
data StartImportFileTaskResponse = StartImportFileTaskResponse'
  { -- | The ID for a specific import task. The ID is unique within an AWS
    -- account.
    StartImportFileTaskResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartImportFileTaskResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartImportFileTaskResponse -> StartImportFileTaskResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartImportFileTaskResponse -> StartImportFileTaskResponse -> Bool
$c/= :: StartImportFileTaskResponse -> StartImportFileTaskResponse -> Bool
== :: StartImportFileTaskResponse -> StartImportFileTaskResponse -> Bool
$c== :: StartImportFileTaskResponse -> StartImportFileTaskResponse -> Bool
Prelude.Eq, ReadPrec [StartImportFileTaskResponse]
ReadPrec StartImportFileTaskResponse
Int -> ReadS StartImportFileTaskResponse
ReadS [StartImportFileTaskResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartImportFileTaskResponse]
$creadListPrec :: ReadPrec [StartImportFileTaskResponse]
readPrec :: ReadPrec StartImportFileTaskResponse
$creadPrec :: ReadPrec StartImportFileTaskResponse
readList :: ReadS [StartImportFileTaskResponse]
$creadList :: ReadS [StartImportFileTaskResponse]
readsPrec :: Int -> ReadS StartImportFileTaskResponse
$creadsPrec :: Int -> ReadS StartImportFileTaskResponse
Prelude.Read, Int -> StartImportFileTaskResponse -> ShowS
[StartImportFileTaskResponse] -> ShowS
StartImportFileTaskResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartImportFileTaskResponse] -> ShowS
$cshowList :: [StartImportFileTaskResponse] -> ShowS
show :: StartImportFileTaskResponse -> String
$cshow :: StartImportFileTaskResponse -> String
showsPrec :: Int -> StartImportFileTaskResponse -> ShowS
$cshowsPrec :: Int -> StartImportFileTaskResponse -> ShowS
Prelude.Show, forall x.
Rep StartImportFileTaskResponse x -> StartImportFileTaskResponse
forall x.
StartImportFileTaskResponse -> Rep StartImportFileTaskResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartImportFileTaskResponse x -> StartImportFileTaskResponse
$cfrom :: forall x.
StartImportFileTaskResponse -> Rep StartImportFileTaskResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartImportFileTaskResponse' 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:
--
-- 'id', 'startImportFileTaskResponse_id' - The ID for a specific import task. The ID is unique within an AWS
-- account.
--
-- 'httpStatus', 'startImportFileTaskResponse_httpStatus' - The response's http status code.
newStartImportFileTaskResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartImportFileTaskResponse
newStartImportFileTaskResponse :: Int -> StartImportFileTaskResponse
newStartImportFileTaskResponse Int
pHttpStatus_ =
  StartImportFileTaskResponse'
    { $sel:id:StartImportFileTaskResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartImportFileTaskResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ID for a specific import task. The ID is unique within an AWS
-- account.
startImportFileTaskResponse_id :: Lens.Lens' StartImportFileTaskResponse (Prelude.Maybe Prelude.Text)
startImportFileTaskResponse_id :: Lens' StartImportFileTaskResponse (Maybe Text)
startImportFileTaskResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartImportFileTaskResponse' {Maybe Text
id :: Maybe Text
$sel:id:StartImportFileTaskResponse' :: StartImportFileTaskResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: StartImportFileTaskResponse
s@StartImportFileTaskResponse' {} Maybe Text
a -> StartImportFileTaskResponse
s {$sel:id:StartImportFileTaskResponse' :: Maybe Text
id = Maybe Text
a} :: StartImportFileTaskResponse)

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

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