{-# 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.EC2.ImportInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an import instance task using metadata from the specified disk
-- image.
--
-- This API action supports only single-volume VMs. To import multi-volume
-- VMs, use ImportImage instead.
--
-- This API action is not supported by the Command Line Interface (CLI).
-- For information about using the Amazon EC2 CLI, which is deprecated, see
-- <https://awsdocs.s3.amazonaws.com/EC2/ec2-clt.pdf#UsingVirtualMachinesinAmazonEC2 Importing a VM to Amazon EC2>
-- in the /Amazon EC2 CLI Reference/ PDF file.
--
-- For information about the import manifest referenced by this API action,
-- see
-- <https://docs.aws.amazon.com/AWSEC2/latest/APIReference/manifest.html VM Import Manifest>.
module Amazonka.EC2.ImportInstance
  ( -- * Creating a Request
    ImportInstance (..),
    newImportInstance,

    -- * Request Lenses
    importInstance_description,
    importInstance_diskImages,
    importInstance_dryRun,
    importInstance_launchSpecification,
    importInstance_platform,

    -- * Destructuring the Response
    ImportInstanceResponse (..),
    newImportInstanceResponse,

    -- * Response Lenses
    importInstanceResponse_conversionTask,
    importInstanceResponse_httpStatus,
  )
where

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

-- | /See:/ 'newImportInstance' smart constructor.
data ImportInstance = ImportInstance'
  { -- | A description for the instance being imported.
    ImportInstance -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The disk image.
    ImportInstance -> Maybe [DiskImage]
diskImages :: Prelude.Maybe [DiskImage],
    -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    ImportInstance -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The launch specification.
    ImportInstance -> Maybe ImportInstanceLaunchSpecification
launchSpecification :: Prelude.Maybe ImportInstanceLaunchSpecification,
    -- | The instance operating system.
    ImportInstance -> PlatformValues
platform :: PlatformValues
  }
  deriving (ImportInstance -> ImportInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportInstance -> ImportInstance -> Bool
$c/= :: ImportInstance -> ImportInstance -> Bool
== :: ImportInstance -> ImportInstance -> Bool
$c== :: ImportInstance -> ImportInstance -> Bool
Prelude.Eq, Int -> ImportInstance -> ShowS
[ImportInstance] -> ShowS
ImportInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportInstance] -> ShowS
$cshowList :: [ImportInstance] -> ShowS
show :: ImportInstance -> String
$cshow :: ImportInstance -> String
showsPrec :: Int -> ImportInstance -> ShowS
$cshowsPrec :: Int -> ImportInstance -> ShowS
Prelude.Show, forall x. Rep ImportInstance x -> ImportInstance
forall x. ImportInstance -> Rep ImportInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportInstance x -> ImportInstance
$cfrom :: forall x. ImportInstance -> Rep ImportInstance x
Prelude.Generic)

-- |
-- Create a value of 'ImportInstance' 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:
--
-- 'description', 'importInstance_description' - A description for the instance being imported.
--
-- 'diskImages', 'importInstance_diskImages' - The disk image.
--
-- 'dryRun', 'importInstance_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'launchSpecification', 'importInstance_launchSpecification' - The launch specification.
--
-- 'platform', 'importInstance_platform' - The instance operating system.
newImportInstance ::
  -- | 'platform'
  PlatformValues ->
  ImportInstance
newImportInstance :: PlatformValues -> ImportInstance
newImportInstance PlatformValues
pPlatform_ =
  ImportInstance'
    { $sel:description:ImportInstance' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:diskImages:ImportInstance' :: Maybe [DiskImage]
diskImages = forall a. Maybe a
Prelude.Nothing,
      $sel:dryRun:ImportInstance' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:launchSpecification:ImportInstance' :: Maybe ImportInstanceLaunchSpecification
launchSpecification = forall a. Maybe a
Prelude.Nothing,
      $sel:platform:ImportInstance' :: PlatformValues
platform = PlatformValues
pPlatform_
    }

-- | A description for the instance being imported.
importInstance_description :: Lens.Lens' ImportInstance (Prelude.Maybe Prelude.Text)
importInstance_description :: Lens' ImportInstance (Maybe Text)
importInstance_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstance' {Maybe Text
description :: Maybe Text
$sel:description:ImportInstance' :: ImportInstance -> Maybe Text
description} -> Maybe Text
description) (\s :: ImportInstance
s@ImportInstance' {} Maybe Text
a -> ImportInstance
s {$sel:description:ImportInstance' :: Maybe Text
description = Maybe Text
a} :: ImportInstance)

-- | The disk image.
importInstance_diskImages :: Lens.Lens' ImportInstance (Prelude.Maybe [DiskImage])
importInstance_diskImages :: Lens' ImportInstance (Maybe [DiskImage])
importInstance_diskImages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstance' {Maybe [DiskImage]
diskImages :: Maybe [DiskImage]
$sel:diskImages:ImportInstance' :: ImportInstance -> Maybe [DiskImage]
diskImages} -> Maybe [DiskImage]
diskImages) (\s :: ImportInstance
s@ImportInstance' {} Maybe [DiskImage]
a -> ImportInstance
s {$sel:diskImages:ImportInstance' :: Maybe [DiskImage]
diskImages = Maybe [DiskImage]
a} :: ImportInstance) 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

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
importInstance_dryRun :: Lens.Lens' ImportInstance (Prelude.Maybe Prelude.Bool)
importInstance_dryRun :: Lens' ImportInstance (Maybe Bool)
importInstance_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstance' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:ImportInstance' :: ImportInstance -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: ImportInstance
s@ImportInstance' {} Maybe Bool
a -> ImportInstance
s {$sel:dryRun:ImportInstance' :: Maybe Bool
dryRun = Maybe Bool
a} :: ImportInstance)

-- | The launch specification.
importInstance_launchSpecification :: Lens.Lens' ImportInstance (Prelude.Maybe ImportInstanceLaunchSpecification)
importInstance_launchSpecification :: Lens' ImportInstance (Maybe ImportInstanceLaunchSpecification)
importInstance_launchSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstance' {Maybe ImportInstanceLaunchSpecification
launchSpecification :: Maybe ImportInstanceLaunchSpecification
$sel:launchSpecification:ImportInstance' :: ImportInstance -> Maybe ImportInstanceLaunchSpecification
launchSpecification} -> Maybe ImportInstanceLaunchSpecification
launchSpecification) (\s :: ImportInstance
s@ImportInstance' {} Maybe ImportInstanceLaunchSpecification
a -> ImportInstance
s {$sel:launchSpecification:ImportInstance' :: Maybe ImportInstanceLaunchSpecification
launchSpecification = Maybe ImportInstanceLaunchSpecification
a} :: ImportInstance)

-- | The instance operating system.
importInstance_platform :: Lens.Lens' ImportInstance PlatformValues
importInstance_platform :: Lens' ImportInstance PlatformValues
importInstance_platform = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstance' {PlatformValues
platform :: PlatformValues
$sel:platform:ImportInstance' :: ImportInstance -> PlatformValues
platform} -> PlatformValues
platform) (\s :: ImportInstance
s@ImportInstance' {} PlatformValues
a -> ImportInstance
s {$sel:platform:ImportInstance' :: PlatformValues
platform = PlatformValues
a} :: ImportInstance)

instance Core.AWSRequest ImportInstance where
  type
    AWSResponse ImportInstance =
      ImportInstanceResponse
  request :: (Service -> Service) -> ImportInstance -> Request ImportInstance
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ImportInstance
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ImportInstance)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe ConversionTask -> Int -> ImportInstanceResponse
ImportInstanceResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"conversionTask")
            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 ImportInstance where
  hashWithSalt :: Int -> ImportInstance -> Int
hashWithSalt Int
_salt ImportInstance' {Maybe Bool
Maybe [DiskImage]
Maybe Text
Maybe ImportInstanceLaunchSpecification
PlatformValues
platform :: PlatformValues
launchSpecification :: Maybe ImportInstanceLaunchSpecification
dryRun :: Maybe Bool
diskImages :: Maybe [DiskImage]
description :: Maybe Text
$sel:platform:ImportInstance' :: ImportInstance -> PlatformValues
$sel:launchSpecification:ImportInstance' :: ImportInstance -> Maybe ImportInstanceLaunchSpecification
$sel:dryRun:ImportInstance' :: ImportInstance -> Maybe Bool
$sel:diskImages:ImportInstance' :: ImportInstance -> Maybe [DiskImage]
$sel:description:ImportInstance' :: ImportInstance -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DiskImage]
diskImages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImportInstanceLaunchSpecification
launchSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PlatformValues
platform

instance Prelude.NFData ImportInstance where
  rnf :: ImportInstance -> ()
rnf ImportInstance' {Maybe Bool
Maybe [DiskImage]
Maybe Text
Maybe ImportInstanceLaunchSpecification
PlatformValues
platform :: PlatformValues
launchSpecification :: Maybe ImportInstanceLaunchSpecification
dryRun :: Maybe Bool
diskImages :: Maybe [DiskImage]
description :: Maybe Text
$sel:platform:ImportInstance' :: ImportInstance -> PlatformValues
$sel:launchSpecification:ImportInstance' :: ImportInstance -> Maybe ImportInstanceLaunchSpecification
$sel:dryRun:ImportInstance' :: ImportInstance -> Maybe Bool
$sel:diskImages:ImportInstance' :: ImportInstance -> Maybe [DiskImage]
$sel:description:ImportInstance' :: ImportInstance -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DiskImage]
diskImages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImportInstanceLaunchSpecification
launchSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PlatformValues
platform

instance Data.ToHeaders ImportInstance where
  toHeaders :: ImportInstance -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ImportInstance where
  toQuery :: ImportInstance -> QueryString
toQuery ImportInstance' {Maybe Bool
Maybe [DiskImage]
Maybe Text
Maybe ImportInstanceLaunchSpecification
PlatformValues
platform :: PlatformValues
launchSpecification :: Maybe ImportInstanceLaunchSpecification
dryRun :: Maybe Bool
diskImages :: Maybe [DiskImage]
description :: Maybe Text
$sel:platform:ImportInstance' :: ImportInstance -> PlatformValues
$sel:launchSpecification:ImportInstance' :: ImportInstance -> Maybe ImportInstanceLaunchSpecification
$sel:dryRun:ImportInstance' :: ImportInstance -> Maybe Bool
$sel:diskImages:ImportInstance' :: ImportInstance -> Maybe [DiskImage]
$sel:description:ImportInstance' :: ImportInstance -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ImportInstance" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"Description" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
description,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"DiskImage"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [DiskImage]
diskImages
          ),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        ByteString
"LaunchSpecification" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ImportInstanceLaunchSpecification
launchSpecification,
        ByteString
"Platform" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: PlatformValues
platform
      ]

-- | /See:/ 'newImportInstanceResponse' smart constructor.
data ImportInstanceResponse = ImportInstanceResponse'
  { -- | Information about the conversion task.
    ImportInstanceResponse -> Maybe ConversionTask
conversionTask :: Prelude.Maybe ConversionTask,
    -- | The response's http status code.
    ImportInstanceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ImportInstanceResponse -> ImportInstanceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportInstanceResponse -> ImportInstanceResponse -> Bool
$c/= :: ImportInstanceResponse -> ImportInstanceResponse -> Bool
== :: ImportInstanceResponse -> ImportInstanceResponse -> Bool
$c== :: ImportInstanceResponse -> ImportInstanceResponse -> Bool
Prelude.Eq, ReadPrec [ImportInstanceResponse]
ReadPrec ImportInstanceResponse
Int -> ReadS ImportInstanceResponse
ReadS [ImportInstanceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportInstanceResponse]
$creadListPrec :: ReadPrec [ImportInstanceResponse]
readPrec :: ReadPrec ImportInstanceResponse
$creadPrec :: ReadPrec ImportInstanceResponse
readList :: ReadS [ImportInstanceResponse]
$creadList :: ReadS [ImportInstanceResponse]
readsPrec :: Int -> ReadS ImportInstanceResponse
$creadsPrec :: Int -> ReadS ImportInstanceResponse
Prelude.Read, Int -> ImportInstanceResponse -> ShowS
[ImportInstanceResponse] -> ShowS
ImportInstanceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportInstanceResponse] -> ShowS
$cshowList :: [ImportInstanceResponse] -> ShowS
show :: ImportInstanceResponse -> String
$cshow :: ImportInstanceResponse -> String
showsPrec :: Int -> ImportInstanceResponse -> ShowS
$cshowsPrec :: Int -> ImportInstanceResponse -> ShowS
Prelude.Show, forall x. Rep ImportInstanceResponse x -> ImportInstanceResponse
forall x. ImportInstanceResponse -> Rep ImportInstanceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportInstanceResponse x -> ImportInstanceResponse
$cfrom :: forall x. ImportInstanceResponse -> Rep ImportInstanceResponse x
Prelude.Generic)

-- |
-- Create a value of 'ImportInstanceResponse' 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:
--
-- 'conversionTask', 'importInstanceResponse_conversionTask' - Information about the conversion task.
--
-- 'httpStatus', 'importInstanceResponse_httpStatus' - The response's http status code.
newImportInstanceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ImportInstanceResponse
newImportInstanceResponse :: Int -> ImportInstanceResponse
newImportInstanceResponse Int
pHttpStatus_ =
  ImportInstanceResponse'
    { $sel:conversionTask:ImportInstanceResponse' :: Maybe ConversionTask
conversionTask =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ImportInstanceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the conversion task.
importInstanceResponse_conversionTask :: Lens.Lens' ImportInstanceResponse (Prelude.Maybe ConversionTask)
importInstanceResponse_conversionTask :: Lens' ImportInstanceResponse (Maybe ConversionTask)
importInstanceResponse_conversionTask = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceResponse' {Maybe ConversionTask
conversionTask :: Maybe ConversionTask
$sel:conversionTask:ImportInstanceResponse' :: ImportInstanceResponse -> Maybe ConversionTask
conversionTask} -> Maybe ConversionTask
conversionTask) (\s :: ImportInstanceResponse
s@ImportInstanceResponse' {} Maybe ConversionTask
a -> ImportInstanceResponse
s {$sel:conversionTask:ImportInstanceResponse' :: Maybe ConversionTask
conversionTask = Maybe ConversionTask
a} :: ImportInstanceResponse)

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

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