{-# 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.MGN.CreateLaunchConfigurationTemplate
-- 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 a new Launch Configuration Template.
module Amazonka.MGN.CreateLaunchConfigurationTemplate
  ( -- * Creating a Request
    CreateLaunchConfigurationTemplate (..),
    newCreateLaunchConfigurationTemplate,

    -- * Request Lenses
    createLaunchConfigurationTemplate_associatePublicIpAddress,
    createLaunchConfigurationTemplate_bootMode,
    createLaunchConfigurationTemplate_copyPrivateIp,
    createLaunchConfigurationTemplate_copyTags,
    createLaunchConfigurationTemplate_enableMapAutoTagging,
    createLaunchConfigurationTemplate_largeVolumeConf,
    createLaunchConfigurationTemplate_launchDisposition,
    createLaunchConfigurationTemplate_licensing,
    createLaunchConfigurationTemplate_mapAutoTaggingMpeID,
    createLaunchConfigurationTemplate_postLaunchActions,
    createLaunchConfigurationTemplate_smallVolumeConf,
    createLaunchConfigurationTemplate_smallVolumeMaxSize,
    createLaunchConfigurationTemplate_tags,
    createLaunchConfigurationTemplate_targetInstanceTypeRightSizingMethod,

    -- * Destructuring the Response
    LaunchConfigurationTemplate (..),
    newLaunchConfigurationTemplate,

    -- * Response Lenses
    launchConfigurationTemplate_arn,
    launchConfigurationTemplate_associatePublicIpAddress,
    launchConfigurationTemplate_bootMode,
    launchConfigurationTemplate_copyPrivateIp,
    launchConfigurationTemplate_copyTags,
    launchConfigurationTemplate_ec2LaunchTemplateID,
    launchConfigurationTemplate_enableMapAutoTagging,
    launchConfigurationTemplate_largeVolumeConf,
    launchConfigurationTemplate_launchDisposition,
    launchConfigurationTemplate_licensing,
    launchConfigurationTemplate_mapAutoTaggingMpeID,
    launchConfigurationTemplate_postLaunchActions,
    launchConfigurationTemplate_smallVolumeConf,
    launchConfigurationTemplate_smallVolumeMaxSize,
    launchConfigurationTemplate_tags,
    launchConfigurationTemplate_targetInstanceTypeRightSizingMethod,
    launchConfigurationTemplate_launchConfigurationTemplateID,
  )
where

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

-- | /See:/ 'newCreateLaunchConfigurationTemplate' smart constructor.
data CreateLaunchConfigurationTemplate = CreateLaunchConfigurationTemplate'
  { -- | Associate public Ip address.
    CreateLaunchConfigurationTemplate -> Maybe Bool
associatePublicIpAddress :: Prelude.Maybe Prelude.Bool,
    -- | Launch configuration template boot mode.
    CreateLaunchConfigurationTemplate -> Maybe BootMode
bootMode :: Prelude.Maybe BootMode,
    -- | Copy private Ip.
    CreateLaunchConfigurationTemplate -> Maybe Bool
copyPrivateIp :: Prelude.Maybe Prelude.Bool,
    -- | Copy tags.
    CreateLaunchConfigurationTemplate -> Maybe Bool
copyTags :: Prelude.Maybe Prelude.Bool,
    -- | Enable map auto tagging.
    CreateLaunchConfigurationTemplate -> Maybe Bool
enableMapAutoTagging :: Prelude.Maybe Prelude.Bool,
    -- | Large volume config.
    CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
largeVolumeConf :: Prelude.Maybe LaunchTemplateDiskConf,
    -- | Launch disposition.
    CreateLaunchConfigurationTemplate -> Maybe LaunchDisposition
launchDisposition :: Prelude.Maybe LaunchDisposition,
    CreateLaunchConfigurationTemplate -> Maybe Licensing
licensing :: Prelude.Maybe Licensing,
    -- | Launch configuration template map auto tagging MPE ID.
    CreateLaunchConfigurationTemplate -> Maybe Text
mapAutoTaggingMpeID :: Prelude.Maybe Prelude.Text,
    -- | Launch configuration template post launch actions.
    CreateLaunchConfigurationTemplate -> Maybe PostLaunchActions
postLaunchActions :: Prelude.Maybe PostLaunchActions,
    -- | Small volume config.
    CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
smallVolumeConf :: Prelude.Maybe LaunchTemplateDiskConf,
    -- | Small volume maximum size.
    CreateLaunchConfigurationTemplate -> Maybe Natural
smallVolumeMaxSize :: Prelude.Maybe Prelude.Natural,
    -- | Request to associate tags during creation of a Launch Configuration
    -- Template.
    CreateLaunchConfigurationTemplate
-> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | Target instance type right-sizing method.
    CreateLaunchConfigurationTemplate
-> Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod :: Prelude.Maybe TargetInstanceTypeRightSizingMethod
  }
  deriving (CreateLaunchConfigurationTemplate
-> CreateLaunchConfigurationTemplate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateLaunchConfigurationTemplate
-> CreateLaunchConfigurationTemplate -> Bool
$c/= :: CreateLaunchConfigurationTemplate
-> CreateLaunchConfigurationTemplate -> Bool
== :: CreateLaunchConfigurationTemplate
-> CreateLaunchConfigurationTemplate -> Bool
$c== :: CreateLaunchConfigurationTemplate
-> CreateLaunchConfigurationTemplate -> Bool
Prelude.Eq, Int -> CreateLaunchConfigurationTemplate -> ShowS
[CreateLaunchConfigurationTemplate] -> ShowS
CreateLaunchConfigurationTemplate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateLaunchConfigurationTemplate] -> ShowS
$cshowList :: [CreateLaunchConfigurationTemplate] -> ShowS
show :: CreateLaunchConfigurationTemplate -> String
$cshow :: CreateLaunchConfigurationTemplate -> String
showsPrec :: Int -> CreateLaunchConfigurationTemplate -> ShowS
$cshowsPrec :: Int -> CreateLaunchConfigurationTemplate -> ShowS
Prelude.Show, forall x.
Rep CreateLaunchConfigurationTemplate x
-> CreateLaunchConfigurationTemplate
forall x.
CreateLaunchConfigurationTemplate
-> Rep CreateLaunchConfigurationTemplate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateLaunchConfigurationTemplate x
-> CreateLaunchConfigurationTemplate
$cfrom :: forall x.
CreateLaunchConfigurationTemplate
-> Rep CreateLaunchConfigurationTemplate x
Prelude.Generic)

-- |
-- Create a value of 'CreateLaunchConfigurationTemplate' 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:
--
-- 'associatePublicIpAddress', 'createLaunchConfigurationTemplate_associatePublicIpAddress' - Associate public Ip address.
--
-- 'bootMode', 'createLaunchConfigurationTemplate_bootMode' - Launch configuration template boot mode.
--
-- 'copyPrivateIp', 'createLaunchConfigurationTemplate_copyPrivateIp' - Copy private Ip.
--
-- 'copyTags', 'createLaunchConfigurationTemplate_copyTags' - Copy tags.
--
-- 'enableMapAutoTagging', 'createLaunchConfigurationTemplate_enableMapAutoTagging' - Enable map auto tagging.
--
-- 'largeVolumeConf', 'createLaunchConfigurationTemplate_largeVolumeConf' - Large volume config.
--
-- 'launchDisposition', 'createLaunchConfigurationTemplate_launchDisposition' - Launch disposition.
--
-- 'licensing', 'createLaunchConfigurationTemplate_licensing' - Undocumented member.
--
-- 'mapAutoTaggingMpeID', 'createLaunchConfigurationTemplate_mapAutoTaggingMpeID' - Launch configuration template map auto tagging MPE ID.
--
-- 'postLaunchActions', 'createLaunchConfigurationTemplate_postLaunchActions' - Launch configuration template post launch actions.
--
-- 'smallVolumeConf', 'createLaunchConfigurationTemplate_smallVolumeConf' - Small volume config.
--
-- 'smallVolumeMaxSize', 'createLaunchConfigurationTemplate_smallVolumeMaxSize' - Small volume maximum size.
--
-- 'tags', 'createLaunchConfigurationTemplate_tags' - Request to associate tags during creation of a Launch Configuration
-- Template.
--
-- 'targetInstanceTypeRightSizingMethod', 'createLaunchConfigurationTemplate_targetInstanceTypeRightSizingMethod' - Target instance type right-sizing method.
newCreateLaunchConfigurationTemplate ::
  CreateLaunchConfigurationTemplate
newCreateLaunchConfigurationTemplate :: CreateLaunchConfigurationTemplate
newCreateLaunchConfigurationTemplate =
  CreateLaunchConfigurationTemplate'
    { $sel:associatePublicIpAddress:CreateLaunchConfigurationTemplate' :: Maybe Bool
associatePublicIpAddress =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bootMode:CreateLaunchConfigurationTemplate' :: Maybe BootMode
bootMode = forall a. Maybe a
Prelude.Nothing,
      $sel:copyPrivateIp:CreateLaunchConfigurationTemplate' :: Maybe Bool
copyPrivateIp = forall a. Maybe a
Prelude.Nothing,
      $sel:copyTags:CreateLaunchConfigurationTemplate' :: Maybe Bool
copyTags = forall a. Maybe a
Prelude.Nothing,
      $sel:enableMapAutoTagging:CreateLaunchConfigurationTemplate' :: Maybe Bool
enableMapAutoTagging = forall a. Maybe a
Prelude.Nothing,
      $sel:largeVolumeConf:CreateLaunchConfigurationTemplate' :: Maybe LaunchTemplateDiskConf
largeVolumeConf = forall a. Maybe a
Prelude.Nothing,
      $sel:launchDisposition:CreateLaunchConfigurationTemplate' :: Maybe LaunchDisposition
launchDisposition = forall a. Maybe a
Prelude.Nothing,
      $sel:licensing:CreateLaunchConfigurationTemplate' :: Maybe Licensing
licensing = forall a. Maybe a
Prelude.Nothing,
      $sel:mapAutoTaggingMpeID:CreateLaunchConfigurationTemplate' :: Maybe Text
mapAutoTaggingMpeID = forall a. Maybe a
Prelude.Nothing,
      $sel:postLaunchActions:CreateLaunchConfigurationTemplate' :: Maybe PostLaunchActions
postLaunchActions = forall a. Maybe a
Prelude.Nothing,
      $sel:smallVolumeConf:CreateLaunchConfigurationTemplate' :: Maybe LaunchTemplateDiskConf
smallVolumeConf = forall a. Maybe a
Prelude.Nothing,
      $sel:smallVolumeMaxSize:CreateLaunchConfigurationTemplate' :: Maybe Natural
smallVolumeMaxSize = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateLaunchConfigurationTemplate' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:targetInstanceTypeRightSizingMethod:CreateLaunchConfigurationTemplate' :: Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod =
        forall a. Maybe a
Prelude.Nothing
    }

-- | Associate public Ip address.
createLaunchConfigurationTemplate_associatePublicIpAddress :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Prelude.Bool)
createLaunchConfigurationTemplate_associatePublicIpAddress :: Lens' CreateLaunchConfigurationTemplate (Maybe Bool)
createLaunchConfigurationTemplate_associatePublicIpAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Bool
associatePublicIpAddress :: Maybe Bool
$sel:associatePublicIpAddress:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
associatePublicIpAddress} -> Maybe Bool
associatePublicIpAddress) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Bool
a -> CreateLaunchConfigurationTemplate
s {$sel:associatePublicIpAddress:CreateLaunchConfigurationTemplate' :: Maybe Bool
associatePublicIpAddress = Maybe Bool
a} :: CreateLaunchConfigurationTemplate)

-- | Launch configuration template boot mode.
createLaunchConfigurationTemplate_bootMode :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe BootMode)
createLaunchConfigurationTemplate_bootMode :: Lens' CreateLaunchConfigurationTemplate (Maybe BootMode)
createLaunchConfigurationTemplate_bootMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe BootMode
bootMode :: Maybe BootMode
$sel:bootMode:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe BootMode
bootMode} -> Maybe BootMode
bootMode) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe BootMode
a -> CreateLaunchConfigurationTemplate
s {$sel:bootMode:CreateLaunchConfigurationTemplate' :: Maybe BootMode
bootMode = Maybe BootMode
a} :: CreateLaunchConfigurationTemplate)

-- | Copy private Ip.
createLaunchConfigurationTemplate_copyPrivateIp :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Prelude.Bool)
createLaunchConfigurationTemplate_copyPrivateIp :: Lens' CreateLaunchConfigurationTemplate (Maybe Bool)
createLaunchConfigurationTemplate_copyPrivateIp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Bool
copyPrivateIp :: Maybe Bool
$sel:copyPrivateIp:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
copyPrivateIp} -> Maybe Bool
copyPrivateIp) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Bool
a -> CreateLaunchConfigurationTemplate
s {$sel:copyPrivateIp:CreateLaunchConfigurationTemplate' :: Maybe Bool
copyPrivateIp = Maybe Bool
a} :: CreateLaunchConfigurationTemplate)

-- | Copy tags.
createLaunchConfigurationTemplate_copyTags :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Prelude.Bool)
createLaunchConfigurationTemplate_copyTags :: Lens' CreateLaunchConfigurationTemplate (Maybe Bool)
createLaunchConfigurationTemplate_copyTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Bool
copyTags :: Maybe Bool
$sel:copyTags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
copyTags} -> Maybe Bool
copyTags) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Bool
a -> CreateLaunchConfigurationTemplate
s {$sel:copyTags:CreateLaunchConfigurationTemplate' :: Maybe Bool
copyTags = Maybe Bool
a} :: CreateLaunchConfigurationTemplate)

-- | Enable map auto tagging.
createLaunchConfigurationTemplate_enableMapAutoTagging :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Prelude.Bool)
createLaunchConfigurationTemplate_enableMapAutoTagging :: Lens' CreateLaunchConfigurationTemplate (Maybe Bool)
createLaunchConfigurationTemplate_enableMapAutoTagging = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Bool
enableMapAutoTagging :: Maybe Bool
$sel:enableMapAutoTagging:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
enableMapAutoTagging} -> Maybe Bool
enableMapAutoTagging) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Bool
a -> CreateLaunchConfigurationTemplate
s {$sel:enableMapAutoTagging:CreateLaunchConfigurationTemplate' :: Maybe Bool
enableMapAutoTagging = Maybe Bool
a} :: CreateLaunchConfigurationTemplate)

-- | Large volume config.
createLaunchConfigurationTemplate_largeVolumeConf :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe LaunchTemplateDiskConf)
createLaunchConfigurationTemplate_largeVolumeConf :: Lens'
  CreateLaunchConfigurationTemplate (Maybe LaunchTemplateDiskConf)
createLaunchConfigurationTemplate_largeVolumeConf = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe LaunchTemplateDiskConf
largeVolumeConf :: Maybe LaunchTemplateDiskConf
$sel:largeVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
largeVolumeConf} -> Maybe LaunchTemplateDiskConf
largeVolumeConf) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe LaunchTemplateDiskConf
a -> CreateLaunchConfigurationTemplate
s {$sel:largeVolumeConf:CreateLaunchConfigurationTemplate' :: Maybe LaunchTemplateDiskConf
largeVolumeConf = Maybe LaunchTemplateDiskConf
a} :: CreateLaunchConfigurationTemplate)

-- | Launch disposition.
createLaunchConfigurationTemplate_launchDisposition :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe LaunchDisposition)
createLaunchConfigurationTemplate_launchDisposition :: Lens' CreateLaunchConfigurationTemplate (Maybe LaunchDisposition)
createLaunchConfigurationTemplate_launchDisposition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe LaunchDisposition
launchDisposition :: Maybe LaunchDisposition
$sel:launchDisposition:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchDisposition
launchDisposition} -> Maybe LaunchDisposition
launchDisposition) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe LaunchDisposition
a -> CreateLaunchConfigurationTemplate
s {$sel:launchDisposition:CreateLaunchConfigurationTemplate' :: Maybe LaunchDisposition
launchDisposition = Maybe LaunchDisposition
a} :: CreateLaunchConfigurationTemplate)

-- | Undocumented member.
createLaunchConfigurationTemplate_licensing :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Licensing)
createLaunchConfigurationTemplate_licensing :: Lens' CreateLaunchConfigurationTemplate (Maybe Licensing)
createLaunchConfigurationTemplate_licensing = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Licensing
licensing :: Maybe Licensing
$sel:licensing:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Licensing
licensing} -> Maybe Licensing
licensing) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Licensing
a -> CreateLaunchConfigurationTemplate
s {$sel:licensing:CreateLaunchConfigurationTemplate' :: Maybe Licensing
licensing = Maybe Licensing
a} :: CreateLaunchConfigurationTemplate)

-- | Launch configuration template map auto tagging MPE ID.
createLaunchConfigurationTemplate_mapAutoTaggingMpeID :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Prelude.Text)
createLaunchConfigurationTemplate_mapAutoTaggingMpeID :: Lens' CreateLaunchConfigurationTemplate (Maybe Text)
createLaunchConfigurationTemplate_mapAutoTaggingMpeID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Text
mapAutoTaggingMpeID :: Maybe Text
$sel:mapAutoTaggingMpeID:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Text
mapAutoTaggingMpeID} -> Maybe Text
mapAutoTaggingMpeID) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Text
a -> CreateLaunchConfigurationTemplate
s {$sel:mapAutoTaggingMpeID:CreateLaunchConfigurationTemplate' :: Maybe Text
mapAutoTaggingMpeID = Maybe Text
a} :: CreateLaunchConfigurationTemplate)

-- | Launch configuration template post launch actions.
createLaunchConfigurationTemplate_postLaunchActions :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe PostLaunchActions)
createLaunchConfigurationTemplate_postLaunchActions :: Lens' CreateLaunchConfigurationTemplate (Maybe PostLaunchActions)
createLaunchConfigurationTemplate_postLaunchActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe PostLaunchActions
postLaunchActions :: Maybe PostLaunchActions
$sel:postLaunchActions:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe PostLaunchActions
postLaunchActions} -> Maybe PostLaunchActions
postLaunchActions) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe PostLaunchActions
a -> CreateLaunchConfigurationTemplate
s {$sel:postLaunchActions:CreateLaunchConfigurationTemplate' :: Maybe PostLaunchActions
postLaunchActions = Maybe PostLaunchActions
a} :: CreateLaunchConfigurationTemplate)

-- | Small volume config.
createLaunchConfigurationTemplate_smallVolumeConf :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe LaunchTemplateDiskConf)
createLaunchConfigurationTemplate_smallVolumeConf :: Lens'
  CreateLaunchConfigurationTemplate (Maybe LaunchTemplateDiskConf)
createLaunchConfigurationTemplate_smallVolumeConf = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe LaunchTemplateDiskConf
smallVolumeConf :: Maybe LaunchTemplateDiskConf
$sel:smallVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
smallVolumeConf} -> Maybe LaunchTemplateDiskConf
smallVolumeConf) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe LaunchTemplateDiskConf
a -> CreateLaunchConfigurationTemplate
s {$sel:smallVolumeConf:CreateLaunchConfigurationTemplate' :: Maybe LaunchTemplateDiskConf
smallVolumeConf = Maybe LaunchTemplateDiskConf
a} :: CreateLaunchConfigurationTemplate)

-- | Small volume maximum size.
createLaunchConfigurationTemplate_smallVolumeMaxSize :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe Prelude.Natural)
createLaunchConfigurationTemplate_smallVolumeMaxSize :: Lens' CreateLaunchConfigurationTemplate (Maybe Natural)
createLaunchConfigurationTemplate_smallVolumeMaxSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe Natural
smallVolumeMaxSize :: Maybe Natural
$sel:smallVolumeMaxSize:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Natural
smallVolumeMaxSize} -> Maybe Natural
smallVolumeMaxSize) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe Natural
a -> CreateLaunchConfigurationTemplate
s {$sel:smallVolumeMaxSize:CreateLaunchConfigurationTemplate' :: Maybe Natural
smallVolumeMaxSize = Maybe Natural
a} :: CreateLaunchConfigurationTemplate)

-- | Request to associate tags during creation of a Launch Configuration
-- Template.
createLaunchConfigurationTemplate_tags :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createLaunchConfigurationTemplate_tags :: Lens' CreateLaunchConfigurationTemplate (Maybe (HashMap Text Text))
createLaunchConfigurationTemplate_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe (Sensitive (HashMap Text Text))
a -> CreateLaunchConfigurationTemplate
s {$sel:tags:CreateLaunchConfigurationTemplate' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: CreateLaunchConfigurationTemplate) 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | Target instance type right-sizing method.
createLaunchConfigurationTemplate_targetInstanceTypeRightSizingMethod :: Lens.Lens' CreateLaunchConfigurationTemplate (Prelude.Maybe TargetInstanceTypeRightSizingMethod)
createLaunchConfigurationTemplate_targetInstanceTypeRightSizingMethod :: Lens'
  CreateLaunchConfigurationTemplate
  (Maybe TargetInstanceTypeRightSizingMethod)
createLaunchConfigurationTemplate_targetInstanceTypeRightSizingMethod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateLaunchConfigurationTemplate' {Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod :: Maybe TargetInstanceTypeRightSizingMethod
$sel:targetInstanceTypeRightSizingMethod:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod} -> Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod) (\s :: CreateLaunchConfigurationTemplate
s@CreateLaunchConfigurationTemplate' {} Maybe TargetInstanceTypeRightSizingMethod
a -> CreateLaunchConfigurationTemplate
s {$sel:targetInstanceTypeRightSizingMethod:CreateLaunchConfigurationTemplate' :: Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod = Maybe TargetInstanceTypeRightSizingMethod
a} :: CreateLaunchConfigurationTemplate)

instance
  Core.AWSRequest
    CreateLaunchConfigurationTemplate
  where
  type
    AWSResponse CreateLaunchConfigurationTemplate =
      LaunchConfigurationTemplate
  request :: (Service -> Service)
-> CreateLaunchConfigurationTemplate
-> Request CreateLaunchConfigurationTemplate
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 CreateLaunchConfigurationTemplate
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse CreateLaunchConfigurationTemplate)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance
  Prelude.Hashable
    CreateLaunchConfigurationTemplate
  where
  hashWithSalt :: Int -> CreateLaunchConfigurationTemplate -> Int
hashWithSalt
    Int
_salt
    CreateLaunchConfigurationTemplate' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe BootMode
Maybe LaunchDisposition
Maybe Licensing
Maybe PostLaunchActions
Maybe TargetInstanceTypeRightSizingMethod
Maybe LaunchTemplateDiskConf
targetInstanceTypeRightSizingMethod :: Maybe TargetInstanceTypeRightSizingMethod
tags :: Maybe (Sensitive (HashMap Text Text))
smallVolumeMaxSize :: Maybe Natural
smallVolumeConf :: Maybe LaunchTemplateDiskConf
postLaunchActions :: Maybe PostLaunchActions
mapAutoTaggingMpeID :: Maybe Text
licensing :: Maybe Licensing
launchDisposition :: Maybe LaunchDisposition
largeVolumeConf :: Maybe LaunchTemplateDiskConf
enableMapAutoTagging :: Maybe Bool
copyTags :: Maybe Bool
copyPrivateIp :: Maybe Bool
bootMode :: Maybe BootMode
associatePublicIpAddress :: Maybe Bool
$sel:targetInstanceTypeRightSizingMethod:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe TargetInstanceTypeRightSizingMethod
$sel:tags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe (Sensitive (HashMap Text Text))
$sel:smallVolumeMaxSize:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Natural
$sel:smallVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
$sel:postLaunchActions:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe PostLaunchActions
$sel:mapAutoTaggingMpeID:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Text
$sel:licensing:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Licensing
$sel:launchDisposition:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchDisposition
$sel:largeVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
$sel:enableMapAutoTagging:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:copyTags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:copyPrivateIp:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:bootMode:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe BootMode
$sel:associatePublicIpAddress:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
associatePublicIpAddress
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BootMode
bootMode
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyPrivateIp
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTags
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableMapAutoTagging
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateDiskConf
largeVolumeConf
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchDisposition
launchDisposition
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Licensing
licensing
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
mapAutoTaggingMpeID
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PostLaunchActions
postLaunchActions
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LaunchTemplateDiskConf
smallVolumeConf
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
smallVolumeMaxSize
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text Text))
tags
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod

instance
  Prelude.NFData
    CreateLaunchConfigurationTemplate
  where
  rnf :: CreateLaunchConfigurationTemplate -> ()
rnf CreateLaunchConfigurationTemplate' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe BootMode
Maybe LaunchDisposition
Maybe Licensing
Maybe PostLaunchActions
Maybe TargetInstanceTypeRightSizingMethod
Maybe LaunchTemplateDiskConf
targetInstanceTypeRightSizingMethod :: Maybe TargetInstanceTypeRightSizingMethod
tags :: Maybe (Sensitive (HashMap Text Text))
smallVolumeMaxSize :: Maybe Natural
smallVolumeConf :: Maybe LaunchTemplateDiskConf
postLaunchActions :: Maybe PostLaunchActions
mapAutoTaggingMpeID :: Maybe Text
licensing :: Maybe Licensing
launchDisposition :: Maybe LaunchDisposition
largeVolumeConf :: Maybe LaunchTemplateDiskConf
enableMapAutoTagging :: Maybe Bool
copyTags :: Maybe Bool
copyPrivateIp :: Maybe Bool
bootMode :: Maybe BootMode
associatePublicIpAddress :: Maybe Bool
$sel:targetInstanceTypeRightSizingMethod:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe TargetInstanceTypeRightSizingMethod
$sel:tags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe (Sensitive (HashMap Text Text))
$sel:smallVolumeMaxSize:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Natural
$sel:smallVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
$sel:postLaunchActions:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe PostLaunchActions
$sel:mapAutoTaggingMpeID:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Text
$sel:licensing:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Licensing
$sel:launchDisposition:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchDisposition
$sel:largeVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
$sel:enableMapAutoTagging:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:copyTags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:copyPrivateIp:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:bootMode:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe BootMode
$sel:associatePublicIpAddress:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
associatePublicIpAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BootMode
bootMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyPrivateIp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableMapAutoTagging
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateDiskConf
largeVolumeConf
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchDisposition
launchDisposition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Licensing
licensing
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
mapAutoTaggingMpeID
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PostLaunchActions
postLaunchActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LaunchTemplateDiskConf
smallVolumeConf
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
smallVolumeMaxSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod

instance
  Data.ToHeaders
    CreateLaunchConfigurationTemplate
  where
  toHeaders :: CreateLaunchConfigurationTemplate -> 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
    CreateLaunchConfigurationTemplate
  where
  toJSON :: CreateLaunchConfigurationTemplate -> Value
toJSON CreateLaunchConfigurationTemplate' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe BootMode
Maybe LaunchDisposition
Maybe Licensing
Maybe PostLaunchActions
Maybe TargetInstanceTypeRightSizingMethod
Maybe LaunchTemplateDiskConf
targetInstanceTypeRightSizingMethod :: Maybe TargetInstanceTypeRightSizingMethod
tags :: Maybe (Sensitive (HashMap Text Text))
smallVolumeMaxSize :: Maybe Natural
smallVolumeConf :: Maybe LaunchTemplateDiskConf
postLaunchActions :: Maybe PostLaunchActions
mapAutoTaggingMpeID :: Maybe Text
licensing :: Maybe Licensing
launchDisposition :: Maybe LaunchDisposition
largeVolumeConf :: Maybe LaunchTemplateDiskConf
enableMapAutoTagging :: Maybe Bool
copyTags :: Maybe Bool
copyPrivateIp :: Maybe Bool
bootMode :: Maybe BootMode
associatePublicIpAddress :: Maybe Bool
$sel:targetInstanceTypeRightSizingMethod:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe TargetInstanceTypeRightSizingMethod
$sel:tags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate
-> Maybe (Sensitive (HashMap Text Text))
$sel:smallVolumeMaxSize:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Natural
$sel:smallVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
$sel:postLaunchActions:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe PostLaunchActions
$sel:mapAutoTaggingMpeID:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Text
$sel:licensing:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Licensing
$sel:launchDisposition:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchDisposition
$sel:largeVolumeConf:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe LaunchTemplateDiskConf
$sel:enableMapAutoTagging:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:copyTags:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:copyPrivateIp:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
$sel:bootMode:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe BootMode
$sel:associatePublicIpAddress:CreateLaunchConfigurationTemplate' :: CreateLaunchConfigurationTemplate -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"associatePublicIpAddress" 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 Bool
associatePublicIpAddress,
            (Key
"bootMode" 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 BootMode
bootMode,
            (Key
"copyPrivateIp" 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 Bool
copyPrivateIp,
            (Key
"copyTags" 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 Bool
copyTags,
            (Key
"enableMapAutoTagging" 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 Bool
enableMapAutoTagging,
            (Key
"largeVolumeConf" 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 LaunchTemplateDiskConf
largeVolumeConf,
            (Key
"launchDisposition" 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 LaunchDisposition
launchDisposition,
            (Key
"licensing" 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 Licensing
licensing,
            (Key
"mapAutoTaggingMpeID" 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
mapAutoTaggingMpeID,
            (Key
"postLaunchActions" 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 PostLaunchActions
postLaunchActions,
            (Key
"smallVolumeConf" 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 LaunchTemplateDiskConf
smallVolumeConf,
            (Key
"smallVolumeMaxSize" 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 Natural
smallVolumeMaxSize,
            (Key
"tags" 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 (Sensitive (HashMap Text Text))
tags,
            (Key
"targetInstanceTypeRightSizingMethod" 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 TargetInstanceTypeRightSizingMethod
targetInstanceTypeRightSizingMethod
          ]
      )

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

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