{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.ImportInstanceLaunchSpecification
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.EC2.Types.ImportInstanceLaunchSpecification where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EC2.Internal
import Amazonka.EC2.Types.ArchitectureValues
import Amazonka.EC2.Types.InstanceType
import Amazonka.EC2.Types.Placement
import Amazonka.EC2.Types.ShutdownBehavior
import Amazonka.EC2.Types.UserData
import qualified Amazonka.Prelude as Prelude

-- | Describes the launch specification for VM import.
--
-- /See:/ 'newImportInstanceLaunchSpecification' smart constructor.
data ImportInstanceLaunchSpecification = ImportInstanceLaunchSpecification'
  { -- | Reserved.
    ImportInstanceLaunchSpecification -> Maybe Text
additionalInfo :: Prelude.Maybe Prelude.Text,
    -- | The architecture of the instance.
    ImportInstanceLaunchSpecification -> Maybe ArchitectureValues
architecture :: Prelude.Maybe ArchitectureValues,
    -- | The security group IDs.
    ImportInstanceLaunchSpecification -> Maybe [Text]
groupIds :: Prelude.Maybe [Prelude.Text],
    -- | The security group names.
    ImportInstanceLaunchSpecification -> Maybe [Text]
groupNames :: Prelude.Maybe [Prelude.Text],
    -- | Indicates whether an instance stops or terminates when you initiate
    -- shutdown from the instance (using the operating system command for
    -- system shutdown).
    ImportInstanceLaunchSpecification -> Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior :: Prelude.Maybe ShutdownBehavior,
    -- | The instance type. For more information about the instance types that
    -- you can import, see
    -- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmie_prereqs.html#vmimport-instance-types Instance Types>
    -- in the VM Import\/Export User Guide.
    ImportInstanceLaunchSpecification -> Maybe InstanceType
instanceType :: Prelude.Maybe InstanceType,
    -- | Indicates whether monitoring is enabled.
    ImportInstanceLaunchSpecification -> Maybe Bool
monitoring :: Prelude.Maybe Prelude.Bool,
    -- | The placement information for the instance.
    ImportInstanceLaunchSpecification -> Maybe Placement
placement :: Prelude.Maybe Placement,
    -- | [EC2-VPC] An available IP address from the IP address range of the
    -- subnet.
    ImportInstanceLaunchSpecification -> Maybe Text
privateIpAddress :: Prelude.Maybe Prelude.Text,
    -- | [EC2-VPC] The ID of the subnet in which to launch the instance.
    ImportInstanceLaunchSpecification -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | The Base64-encoded user data to make available to the instance.
    ImportInstanceLaunchSpecification -> Maybe (Sensitive UserData)
userData :: Prelude.Maybe (Data.Sensitive UserData)
  }
  deriving (ImportInstanceLaunchSpecification
-> ImportInstanceLaunchSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportInstanceLaunchSpecification
-> ImportInstanceLaunchSpecification -> Bool
$c/= :: ImportInstanceLaunchSpecification
-> ImportInstanceLaunchSpecification -> Bool
== :: ImportInstanceLaunchSpecification
-> ImportInstanceLaunchSpecification -> Bool
$c== :: ImportInstanceLaunchSpecification
-> ImportInstanceLaunchSpecification -> Bool
Prelude.Eq, Int -> ImportInstanceLaunchSpecification -> ShowS
[ImportInstanceLaunchSpecification] -> ShowS
ImportInstanceLaunchSpecification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportInstanceLaunchSpecification] -> ShowS
$cshowList :: [ImportInstanceLaunchSpecification] -> ShowS
show :: ImportInstanceLaunchSpecification -> String
$cshow :: ImportInstanceLaunchSpecification -> String
showsPrec :: Int -> ImportInstanceLaunchSpecification -> ShowS
$cshowsPrec :: Int -> ImportInstanceLaunchSpecification -> ShowS
Prelude.Show, forall x.
Rep ImportInstanceLaunchSpecification x
-> ImportInstanceLaunchSpecification
forall x.
ImportInstanceLaunchSpecification
-> Rep ImportInstanceLaunchSpecification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ImportInstanceLaunchSpecification x
-> ImportInstanceLaunchSpecification
$cfrom :: forall x.
ImportInstanceLaunchSpecification
-> Rep ImportInstanceLaunchSpecification x
Prelude.Generic)

-- |
-- Create a value of 'ImportInstanceLaunchSpecification' 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:
--
-- 'additionalInfo', 'importInstanceLaunchSpecification_additionalInfo' - Reserved.
--
-- 'architecture', 'importInstanceLaunchSpecification_architecture' - The architecture of the instance.
--
-- 'groupIds', 'importInstanceLaunchSpecification_groupIds' - The security group IDs.
--
-- 'groupNames', 'importInstanceLaunchSpecification_groupNames' - The security group names.
--
-- 'instanceInitiatedShutdownBehavior', 'importInstanceLaunchSpecification_instanceInitiatedShutdownBehavior' - Indicates whether an instance stops or terminates when you initiate
-- shutdown from the instance (using the operating system command for
-- system shutdown).
--
-- 'instanceType', 'importInstanceLaunchSpecification_instanceType' - The instance type. For more information about the instance types that
-- you can import, see
-- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmie_prereqs.html#vmimport-instance-types Instance Types>
-- in the VM Import\/Export User Guide.
--
-- 'monitoring', 'importInstanceLaunchSpecification_monitoring' - Indicates whether monitoring is enabled.
--
-- 'placement', 'importInstanceLaunchSpecification_placement' - The placement information for the instance.
--
-- 'privateIpAddress', 'importInstanceLaunchSpecification_privateIpAddress' - [EC2-VPC] An available IP address from the IP address range of the
-- subnet.
--
-- 'subnetId', 'importInstanceLaunchSpecification_subnetId' - [EC2-VPC] The ID of the subnet in which to launch the instance.
--
-- 'userData', 'importInstanceLaunchSpecification_userData' - The Base64-encoded user data to make available to the instance.
newImportInstanceLaunchSpecification ::
  ImportInstanceLaunchSpecification
newImportInstanceLaunchSpecification :: ImportInstanceLaunchSpecification
newImportInstanceLaunchSpecification =
  ImportInstanceLaunchSpecification'
    { $sel:additionalInfo:ImportInstanceLaunchSpecification' :: Maybe Text
additionalInfo =
        forall a. Maybe a
Prelude.Nothing,
      $sel:architecture:ImportInstanceLaunchSpecification' :: Maybe ArchitectureValues
architecture = forall a. Maybe a
Prelude.Nothing,
      $sel:groupIds:ImportInstanceLaunchSpecification' :: Maybe [Text]
groupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:groupNames:ImportInstanceLaunchSpecification' :: Maybe [Text]
groupNames = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceInitiatedShutdownBehavior:ImportInstanceLaunchSpecification' :: Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior =
        forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:ImportInstanceLaunchSpecification' :: Maybe InstanceType
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:monitoring:ImportInstanceLaunchSpecification' :: Maybe Bool
monitoring = forall a. Maybe a
Prelude.Nothing,
      $sel:placement:ImportInstanceLaunchSpecification' :: Maybe Placement
placement = forall a. Maybe a
Prelude.Nothing,
      $sel:privateIpAddress:ImportInstanceLaunchSpecification' :: Maybe Text
privateIpAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:ImportInstanceLaunchSpecification' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:userData:ImportInstanceLaunchSpecification' :: Maybe (Sensitive UserData)
userData = forall a. Maybe a
Prelude.Nothing
    }

-- | Reserved.
importInstanceLaunchSpecification_additionalInfo :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe Prelude.Text)
importInstanceLaunchSpecification_additionalInfo :: Lens' ImportInstanceLaunchSpecification (Maybe Text)
importInstanceLaunchSpecification_additionalInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe Text
additionalInfo :: Maybe Text
$sel:additionalInfo:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
additionalInfo} -> Maybe Text
additionalInfo) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe Text
a -> ImportInstanceLaunchSpecification
s {$sel:additionalInfo:ImportInstanceLaunchSpecification' :: Maybe Text
additionalInfo = Maybe Text
a} :: ImportInstanceLaunchSpecification)

-- | The architecture of the instance.
importInstanceLaunchSpecification_architecture :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe ArchitectureValues)
importInstanceLaunchSpecification_architecture :: Lens' ImportInstanceLaunchSpecification (Maybe ArchitectureValues)
importInstanceLaunchSpecification_architecture = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe ArchitectureValues
architecture :: Maybe ArchitectureValues
$sel:architecture:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ArchitectureValues
architecture} -> Maybe ArchitectureValues
architecture) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe ArchitectureValues
a -> ImportInstanceLaunchSpecification
s {$sel:architecture:ImportInstanceLaunchSpecification' :: Maybe ArchitectureValues
architecture = Maybe ArchitectureValues
a} :: ImportInstanceLaunchSpecification)

-- | The security group IDs.
importInstanceLaunchSpecification_groupIds :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe [Prelude.Text])
importInstanceLaunchSpecification_groupIds :: Lens' ImportInstanceLaunchSpecification (Maybe [Text])
importInstanceLaunchSpecification_groupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe [Text]
groupIds :: Maybe [Text]
$sel:groupIds:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
groupIds} -> Maybe [Text]
groupIds) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe [Text]
a -> ImportInstanceLaunchSpecification
s {$sel:groupIds:ImportInstanceLaunchSpecification' :: Maybe [Text]
groupIds = Maybe [Text]
a} :: ImportInstanceLaunchSpecification) 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 security group names.
importInstanceLaunchSpecification_groupNames :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe [Prelude.Text])
importInstanceLaunchSpecification_groupNames :: Lens' ImportInstanceLaunchSpecification (Maybe [Text])
importInstanceLaunchSpecification_groupNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe [Text]
groupNames :: Maybe [Text]
$sel:groupNames:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
groupNames} -> Maybe [Text]
groupNames) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe [Text]
a -> ImportInstanceLaunchSpecification
s {$sel:groupNames:ImportInstanceLaunchSpecification' :: Maybe [Text]
groupNames = Maybe [Text]
a} :: ImportInstanceLaunchSpecification) 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

-- | Indicates whether an instance stops or terminates when you initiate
-- shutdown from the instance (using the operating system command for
-- system shutdown).
importInstanceLaunchSpecification_instanceInitiatedShutdownBehavior :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe ShutdownBehavior)
importInstanceLaunchSpecification_instanceInitiatedShutdownBehavior :: Lens' ImportInstanceLaunchSpecification (Maybe ShutdownBehavior)
importInstanceLaunchSpecification_instanceInitiatedShutdownBehavior = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior :: Maybe ShutdownBehavior
$sel:instanceInitiatedShutdownBehavior:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior} -> Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe ShutdownBehavior
a -> ImportInstanceLaunchSpecification
s {$sel:instanceInitiatedShutdownBehavior:ImportInstanceLaunchSpecification' :: Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior = Maybe ShutdownBehavior
a} :: ImportInstanceLaunchSpecification)

-- | The instance type. For more information about the instance types that
-- you can import, see
-- <https://docs.aws.amazon.com/vm-import/latest/userguide/vmie_prereqs.html#vmimport-instance-types Instance Types>
-- in the VM Import\/Export User Guide.
importInstanceLaunchSpecification_instanceType :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe InstanceType)
importInstanceLaunchSpecification_instanceType :: Lens' ImportInstanceLaunchSpecification (Maybe InstanceType)
importInstanceLaunchSpecification_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe InstanceType
instanceType :: Maybe InstanceType
$sel:instanceType:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe InstanceType
instanceType} -> Maybe InstanceType
instanceType) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe InstanceType
a -> ImportInstanceLaunchSpecification
s {$sel:instanceType:ImportInstanceLaunchSpecification' :: Maybe InstanceType
instanceType = Maybe InstanceType
a} :: ImportInstanceLaunchSpecification)

-- | Indicates whether monitoring is enabled.
importInstanceLaunchSpecification_monitoring :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe Prelude.Bool)
importInstanceLaunchSpecification_monitoring :: Lens' ImportInstanceLaunchSpecification (Maybe Bool)
importInstanceLaunchSpecification_monitoring = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe Bool
monitoring :: Maybe Bool
$sel:monitoring:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Bool
monitoring} -> Maybe Bool
monitoring) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe Bool
a -> ImportInstanceLaunchSpecification
s {$sel:monitoring:ImportInstanceLaunchSpecification' :: Maybe Bool
monitoring = Maybe Bool
a} :: ImportInstanceLaunchSpecification)

-- | The placement information for the instance.
importInstanceLaunchSpecification_placement :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe Placement)
importInstanceLaunchSpecification_placement :: Lens' ImportInstanceLaunchSpecification (Maybe Placement)
importInstanceLaunchSpecification_placement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe Placement
placement :: Maybe Placement
$sel:placement:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Placement
placement} -> Maybe Placement
placement) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe Placement
a -> ImportInstanceLaunchSpecification
s {$sel:placement:ImportInstanceLaunchSpecification' :: Maybe Placement
placement = Maybe Placement
a} :: ImportInstanceLaunchSpecification)

-- | [EC2-VPC] An available IP address from the IP address range of the
-- subnet.
importInstanceLaunchSpecification_privateIpAddress :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe Prelude.Text)
importInstanceLaunchSpecification_privateIpAddress :: Lens' ImportInstanceLaunchSpecification (Maybe Text)
importInstanceLaunchSpecification_privateIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe Text
privateIpAddress :: Maybe Text
$sel:privateIpAddress:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
privateIpAddress} -> Maybe Text
privateIpAddress) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe Text
a -> ImportInstanceLaunchSpecification
s {$sel:privateIpAddress:ImportInstanceLaunchSpecification' :: Maybe Text
privateIpAddress = Maybe Text
a} :: ImportInstanceLaunchSpecification)

-- | [EC2-VPC] The ID of the subnet in which to launch the instance.
importInstanceLaunchSpecification_subnetId :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe Prelude.Text)
importInstanceLaunchSpecification_subnetId :: Lens' ImportInstanceLaunchSpecification (Maybe Text)
importInstanceLaunchSpecification_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe Text
a -> ImportInstanceLaunchSpecification
s {$sel:subnetId:ImportInstanceLaunchSpecification' :: Maybe Text
subnetId = Maybe Text
a} :: ImportInstanceLaunchSpecification)

-- | The Base64-encoded user data to make available to the instance.
importInstanceLaunchSpecification_userData :: Lens.Lens' ImportInstanceLaunchSpecification (Prelude.Maybe UserData)
importInstanceLaunchSpecification_userData :: Lens' ImportInstanceLaunchSpecification (Maybe UserData)
importInstanceLaunchSpecification_userData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportInstanceLaunchSpecification' {Maybe (Sensitive UserData)
userData :: Maybe (Sensitive UserData)
$sel:userData:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe (Sensitive UserData)
userData} -> Maybe (Sensitive UserData)
userData) (\s :: ImportInstanceLaunchSpecification
s@ImportInstanceLaunchSpecification' {} Maybe (Sensitive UserData)
a -> ImportInstanceLaunchSpecification
s {$sel:userData:ImportInstanceLaunchSpecification' :: Maybe (Sensitive UserData)
userData = Maybe (Sensitive UserData)
a} :: ImportInstanceLaunchSpecification) 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 a. Iso' (Sensitive a) a
Data._Sensitive

instance
  Prelude.Hashable
    ImportInstanceLaunchSpecification
  where
  hashWithSalt :: Int -> ImportInstanceLaunchSpecification -> Int
hashWithSalt
    Int
_salt
    ImportInstanceLaunchSpecification' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe (Sensitive UserData)
Maybe ArchitectureValues
Maybe InstanceType
Maybe ShutdownBehavior
Maybe Placement
userData :: Maybe (Sensitive UserData)
subnetId :: Maybe Text
privateIpAddress :: Maybe Text
placement :: Maybe Placement
monitoring :: Maybe Bool
instanceType :: Maybe InstanceType
instanceInitiatedShutdownBehavior :: Maybe ShutdownBehavior
groupNames :: Maybe [Text]
groupIds :: Maybe [Text]
architecture :: Maybe ArchitectureValues
additionalInfo :: Maybe Text
$sel:userData:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe (Sensitive UserData)
$sel:subnetId:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
$sel:privateIpAddress:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
$sel:placement:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Placement
$sel:monitoring:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Bool
$sel:instanceType:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe InstanceType
$sel:instanceInitiatedShutdownBehavior:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ShutdownBehavior
$sel:groupNames:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
$sel:groupIds:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
$sel:architecture:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ArchitectureValues
$sel:additionalInfo:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
additionalInfo
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ArchitectureValues
architecture
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groupIds
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groupNames
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InstanceType
instanceType
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
monitoring
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Placement
placement
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
privateIpAddress
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive UserData)
userData

instance
  Prelude.NFData
    ImportInstanceLaunchSpecification
  where
  rnf :: ImportInstanceLaunchSpecification -> ()
rnf ImportInstanceLaunchSpecification' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe (Sensitive UserData)
Maybe ArchitectureValues
Maybe InstanceType
Maybe ShutdownBehavior
Maybe Placement
userData :: Maybe (Sensitive UserData)
subnetId :: Maybe Text
privateIpAddress :: Maybe Text
placement :: Maybe Placement
monitoring :: Maybe Bool
instanceType :: Maybe InstanceType
instanceInitiatedShutdownBehavior :: Maybe ShutdownBehavior
groupNames :: Maybe [Text]
groupIds :: Maybe [Text]
architecture :: Maybe ArchitectureValues
additionalInfo :: Maybe Text
$sel:userData:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe (Sensitive UserData)
$sel:subnetId:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
$sel:privateIpAddress:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
$sel:placement:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Placement
$sel:monitoring:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Bool
$sel:instanceType:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe InstanceType
$sel:instanceInitiatedShutdownBehavior:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ShutdownBehavior
$sel:groupNames:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
$sel:groupIds:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
$sel:architecture:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ArchitectureValues
$sel:additionalInfo:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
additionalInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ArchitectureValues
architecture
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
groupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
groupNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InstanceType
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
monitoring
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Placement
placement
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
privateIpAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive UserData)
userData

instance
  Data.ToQuery
    ImportInstanceLaunchSpecification
  where
  toQuery :: ImportInstanceLaunchSpecification -> QueryString
toQuery ImportInstanceLaunchSpecification' {Maybe Bool
Maybe [Text]
Maybe Text
Maybe (Sensitive UserData)
Maybe ArchitectureValues
Maybe InstanceType
Maybe ShutdownBehavior
Maybe Placement
userData :: Maybe (Sensitive UserData)
subnetId :: Maybe Text
privateIpAddress :: Maybe Text
placement :: Maybe Placement
monitoring :: Maybe Bool
instanceType :: Maybe InstanceType
instanceInitiatedShutdownBehavior :: Maybe ShutdownBehavior
groupNames :: Maybe [Text]
groupIds :: Maybe [Text]
architecture :: Maybe ArchitectureValues
additionalInfo :: Maybe Text
$sel:userData:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe (Sensitive UserData)
$sel:subnetId:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
$sel:privateIpAddress:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
$sel:placement:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Placement
$sel:monitoring:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Bool
$sel:instanceType:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe InstanceType
$sel:instanceInitiatedShutdownBehavior:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ShutdownBehavior
$sel:groupNames:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
$sel:groupIds:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe [Text]
$sel:architecture:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe ArchitectureValues
$sel:additionalInfo:ImportInstanceLaunchSpecification' :: ImportInstanceLaunchSpecification -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"AdditionalInfo" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
additionalInfo,
        ByteString
"Architecture" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ArchitectureValues
architecture,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"GroupId" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
groupIds),
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"GroupName"
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
groupNames
          ),
        ByteString
"InstanceInitiatedShutdownBehavior"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ShutdownBehavior
instanceInitiatedShutdownBehavior,
        ByteString
"InstanceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe InstanceType
instanceType,
        ByteString
"Monitoring" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
monitoring,
        ByteString
"Placement" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Placement
placement,
        ByteString
"PrivateIpAddress" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
privateIpAddress,
        ByteString
"SubnetId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
subnetId,
        ByteString
"UserData" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe (Sensitive UserData)
userData
      ]