{-# 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.OnDemandOptionsRequest
-- 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.OnDemandOptionsRequest 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.CapacityReservationOptionsRequest
import Amazonka.EC2.Types.FleetOnDemandAllocationStrategy
import qualified Amazonka.Prelude as Prelude

-- | Describes the configuration of On-Demand Instances in an EC2 Fleet.
--
-- /See:/ 'newOnDemandOptionsRequest' smart constructor.
data OnDemandOptionsRequest = OnDemandOptionsRequest'
  { -- | The strategy that determines the order of the launch template overrides
    -- to use in fulfilling On-Demand capacity.
    --
    -- @lowest-price@ - EC2 Fleet uses price to determine the order, launching
    -- the lowest price first.
    --
    -- @prioritized@ - EC2 Fleet uses the priority that you assigned to each
    -- launch template override, launching the highest priority first.
    --
    -- Default: @lowest-price@
    OnDemandOptionsRequest -> Maybe FleetOnDemandAllocationStrategy
allocationStrategy :: Prelude.Maybe FleetOnDemandAllocationStrategy,
    -- | The strategy for using unused Capacity Reservations for fulfilling
    -- On-Demand capacity.
    --
    -- Supported only for fleets of type @instant@.
    OnDemandOptionsRequest -> Maybe CapacityReservationOptionsRequest
capacityReservationOptions :: Prelude.Maybe CapacityReservationOptionsRequest,
    -- | The maximum amount per hour for On-Demand Instances that you\'re willing
    -- to pay.
    OnDemandOptionsRequest -> Maybe Text
maxTotalPrice :: Prelude.Maybe Prelude.Text,
    -- | The minimum target capacity for On-Demand Instances in the fleet. If the
    -- minimum target capacity is not reached, the fleet launches no instances.
    --
    -- Supported only for fleets of type @instant@.
    --
    -- At least one of the following must be specified:
    -- @SingleAvailabilityZone@ | @SingleInstanceType@
    OnDemandOptionsRequest -> Maybe Int
minTargetCapacity :: Prelude.Maybe Prelude.Int,
    -- | Indicates that the fleet launches all On-Demand Instances into a single
    -- Availability Zone.
    --
    -- Supported only for fleets of type @instant@.
    OnDemandOptionsRequest -> Maybe Bool
singleAvailabilityZone :: Prelude.Maybe Prelude.Bool,
    -- | Indicates that the fleet uses a single instance type to launch all
    -- On-Demand Instances in the fleet.
    --
    -- Supported only for fleets of type @instant@.
    OnDemandOptionsRequest -> Maybe Bool
singleInstanceType :: Prelude.Maybe Prelude.Bool
  }
  deriving (OnDemandOptionsRequest -> OnDemandOptionsRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OnDemandOptionsRequest -> OnDemandOptionsRequest -> Bool
$c/= :: OnDemandOptionsRequest -> OnDemandOptionsRequest -> Bool
== :: OnDemandOptionsRequest -> OnDemandOptionsRequest -> Bool
$c== :: OnDemandOptionsRequest -> OnDemandOptionsRequest -> Bool
Prelude.Eq, ReadPrec [OnDemandOptionsRequest]
ReadPrec OnDemandOptionsRequest
Int -> ReadS OnDemandOptionsRequest
ReadS [OnDemandOptionsRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OnDemandOptionsRequest]
$creadListPrec :: ReadPrec [OnDemandOptionsRequest]
readPrec :: ReadPrec OnDemandOptionsRequest
$creadPrec :: ReadPrec OnDemandOptionsRequest
readList :: ReadS [OnDemandOptionsRequest]
$creadList :: ReadS [OnDemandOptionsRequest]
readsPrec :: Int -> ReadS OnDemandOptionsRequest
$creadsPrec :: Int -> ReadS OnDemandOptionsRequest
Prelude.Read, Int -> OnDemandOptionsRequest -> ShowS
[OnDemandOptionsRequest] -> ShowS
OnDemandOptionsRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OnDemandOptionsRequest] -> ShowS
$cshowList :: [OnDemandOptionsRequest] -> ShowS
show :: OnDemandOptionsRequest -> String
$cshow :: OnDemandOptionsRequest -> String
showsPrec :: Int -> OnDemandOptionsRequest -> ShowS
$cshowsPrec :: Int -> OnDemandOptionsRequest -> ShowS
Prelude.Show, forall x. Rep OnDemandOptionsRequest x -> OnDemandOptionsRequest
forall x. OnDemandOptionsRequest -> Rep OnDemandOptionsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OnDemandOptionsRequest x -> OnDemandOptionsRequest
$cfrom :: forall x. OnDemandOptionsRequest -> Rep OnDemandOptionsRequest x
Prelude.Generic)

-- |
-- Create a value of 'OnDemandOptionsRequest' 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:
--
-- 'allocationStrategy', 'onDemandOptionsRequest_allocationStrategy' - The strategy that determines the order of the launch template overrides
-- to use in fulfilling On-Demand capacity.
--
-- @lowest-price@ - EC2 Fleet uses price to determine the order, launching
-- the lowest price first.
--
-- @prioritized@ - EC2 Fleet uses the priority that you assigned to each
-- launch template override, launching the highest priority first.
--
-- Default: @lowest-price@
--
-- 'capacityReservationOptions', 'onDemandOptionsRequest_capacityReservationOptions' - The strategy for using unused Capacity Reservations for fulfilling
-- On-Demand capacity.
--
-- Supported only for fleets of type @instant@.
--
-- 'maxTotalPrice', 'onDemandOptionsRequest_maxTotalPrice' - The maximum amount per hour for On-Demand Instances that you\'re willing
-- to pay.
--
-- 'minTargetCapacity', 'onDemandOptionsRequest_minTargetCapacity' - The minimum target capacity for On-Demand Instances in the fleet. If the
-- minimum target capacity is not reached, the fleet launches no instances.
--
-- Supported only for fleets of type @instant@.
--
-- At least one of the following must be specified:
-- @SingleAvailabilityZone@ | @SingleInstanceType@
--
-- 'singleAvailabilityZone', 'onDemandOptionsRequest_singleAvailabilityZone' - Indicates that the fleet launches all On-Demand Instances into a single
-- Availability Zone.
--
-- Supported only for fleets of type @instant@.
--
-- 'singleInstanceType', 'onDemandOptionsRequest_singleInstanceType' - Indicates that the fleet uses a single instance type to launch all
-- On-Demand Instances in the fleet.
--
-- Supported only for fleets of type @instant@.
newOnDemandOptionsRequest ::
  OnDemandOptionsRequest
newOnDemandOptionsRequest :: OnDemandOptionsRequest
newOnDemandOptionsRequest =
  OnDemandOptionsRequest'
    { $sel:allocationStrategy:OnDemandOptionsRequest' :: Maybe FleetOnDemandAllocationStrategy
allocationStrategy =
        forall a. Maybe a
Prelude.Nothing,
      $sel:capacityReservationOptions:OnDemandOptionsRequest' :: Maybe CapacityReservationOptionsRequest
capacityReservationOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:maxTotalPrice:OnDemandOptionsRequest' :: Maybe Text
maxTotalPrice = forall a. Maybe a
Prelude.Nothing,
      $sel:minTargetCapacity:OnDemandOptionsRequest' :: Maybe Int
minTargetCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:singleAvailabilityZone:OnDemandOptionsRequest' :: Maybe Bool
singleAvailabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:singleInstanceType:OnDemandOptionsRequest' :: Maybe Bool
singleInstanceType = forall a. Maybe a
Prelude.Nothing
    }

-- | The strategy that determines the order of the launch template overrides
-- to use in fulfilling On-Demand capacity.
--
-- @lowest-price@ - EC2 Fleet uses price to determine the order, launching
-- the lowest price first.
--
-- @prioritized@ - EC2 Fleet uses the priority that you assigned to each
-- launch template override, launching the highest priority first.
--
-- Default: @lowest-price@
onDemandOptionsRequest_allocationStrategy :: Lens.Lens' OnDemandOptionsRequest (Prelude.Maybe FleetOnDemandAllocationStrategy)
onDemandOptionsRequest_allocationStrategy :: Lens'
  OnDemandOptionsRequest (Maybe FleetOnDemandAllocationStrategy)
onDemandOptionsRequest_allocationStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OnDemandOptionsRequest' {Maybe FleetOnDemandAllocationStrategy
allocationStrategy :: Maybe FleetOnDemandAllocationStrategy
$sel:allocationStrategy:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe FleetOnDemandAllocationStrategy
allocationStrategy} -> Maybe FleetOnDemandAllocationStrategy
allocationStrategy) (\s :: OnDemandOptionsRequest
s@OnDemandOptionsRequest' {} Maybe FleetOnDemandAllocationStrategy
a -> OnDemandOptionsRequest
s {$sel:allocationStrategy:OnDemandOptionsRequest' :: Maybe FleetOnDemandAllocationStrategy
allocationStrategy = Maybe FleetOnDemandAllocationStrategy
a} :: OnDemandOptionsRequest)

-- | The strategy for using unused Capacity Reservations for fulfilling
-- On-Demand capacity.
--
-- Supported only for fleets of type @instant@.
onDemandOptionsRequest_capacityReservationOptions :: Lens.Lens' OnDemandOptionsRequest (Prelude.Maybe CapacityReservationOptionsRequest)
onDemandOptionsRequest_capacityReservationOptions :: Lens'
  OnDemandOptionsRequest (Maybe CapacityReservationOptionsRequest)
onDemandOptionsRequest_capacityReservationOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OnDemandOptionsRequest' {Maybe CapacityReservationOptionsRequest
capacityReservationOptions :: Maybe CapacityReservationOptionsRequest
$sel:capacityReservationOptions:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe CapacityReservationOptionsRequest
capacityReservationOptions} -> Maybe CapacityReservationOptionsRequest
capacityReservationOptions) (\s :: OnDemandOptionsRequest
s@OnDemandOptionsRequest' {} Maybe CapacityReservationOptionsRequest
a -> OnDemandOptionsRequest
s {$sel:capacityReservationOptions:OnDemandOptionsRequest' :: Maybe CapacityReservationOptionsRequest
capacityReservationOptions = Maybe CapacityReservationOptionsRequest
a} :: OnDemandOptionsRequest)

-- | The maximum amount per hour for On-Demand Instances that you\'re willing
-- to pay.
onDemandOptionsRequest_maxTotalPrice :: Lens.Lens' OnDemandOptionsRequest (Prelude.Maybe Prelude.Text)
onDemandOptionsRequest_maxTotalPrice :: Lens' OnDemandOptionsRequest (Maybe Text)
onDemandOptionsRequest_maxTotalPrice = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OnDemandOptionsRequest' {Maybe Text
maxTotalPrice :: Maybe Text
$sel:maxTotalPrice:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Text
maxTotalPrice} -> Maybe Text
maxTotalPrice) (\s :: OnDemandOptionsRequest
s@OnDemandOptionsRequest' {} Maybe Text
a -> OnDemandOptionsRequest
s {$sel:maxTotalPrice:OnDemandOptionsRequest' :: Maybe Text
maxTotalPrice = Maybe Text
a} :: OnDemandOptionsRequest)

-- | The minimum target capacity for On-Demand Instances in the fleet. If the
-- minimum target capacity is not reached, the fleet launches no instances.
--
-- Supported only for fleets of type @instant@.
--
-- At least one of the following must be specified:
-- @SingleAvailabilityZone@ | @SingleInstanceType@
onDemandOptionsRequest_minTargetCapacity :: Lens.Lens' OnDemandOptionsRequest (Prelude.Maybe Prelude.Int)
onDemandOptionsRequest_minTargetCapacity :: Lens' OnDemandOptionsRequest (Maybe Int)
onDemandOptionsRequest_minTargetCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OnDemandOptionsRequest' {Maybe Int
minTargetCapacity :: Maybe Int
$sel:minTargetCapacity:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Int
minTargetCapacity} -> Maybe Int
minTargetCapacity) (\s :: OnDemandOptionsRequest
s@OnDemandOptionsRequest' {} Maybe Int
a -> OnDemandOptionsRequest
s {$sel:minTargetCapacity:OnDemandOptionsRequest' :: Maybe Int
minTargetCapacity = Maybe Int
a} :: OnDemandOptionsRequest)

-- | Indicates that the fleet launches all On-Demand Instances into a single
-- Availability Zone.
--
-- Supported only for fleets of type @instant@.
onDemandOptionsRequest_singleAvailabilityZone :: Lens.Lens' OnDemandOptionsRequest (Prelude.Maybe Prelude.Bool)
onDemandOptionsRequest_singleAvailabilityZone :: Lens' OnDemandOptionsRequest (Maybe Bool)
onDemandOptionsRequest_singleAvailabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OnDemandOptionsRequest' {Maybe Bool
singleAvailabilityZone :: Maybe Bool
$sel:singleAvailabilityZone:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
singleAvailabilityZone} -> Maybe Bool
singleAvailabilityZone) (\s :: OnDemandOptionsRequest
s@OnDemandOptionsRequest' {} Maybe Bool
a -> OnDemandOptionsRequest
s {$sel:singleAvailabilityZone:OnDemandOptionsRequest' :: Maybe Bool
singleAvailabilityZone = Maybe Bool
a} :: OnDemandOptionsRequest)

-- | Indicates that the fleet uses a single instance type to launch all
-- On-Demand Instances in the fleet.
--
-- Supported only for fleets of type @instant@.
onDemandOptionsRequest_singleInstanceType :: Lens.Lens' OnDemandOptionsRequest (Prelude.Maybe Prelude.Bool)
onDemandOptionsRequest_singleInstanceType :: Lens' OnDemandOptionsRequest (Maybe Bool)
onDemandOptionsRequest_singleInstanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\OnDemandOptionsRequest' {Maybe Bool
singleInstanceType :: Maybe Bool
$sel:singleInstanceType:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
singleInstanceType} -> Maybe Bool
singleInstanceType) (\s :: OnDemandOptionsRequest
s@OnDemandOptionsRequest' {} Maybe Bool
a -> OnDemandOptionsRequest
s {$sel:singleInstanceType:OnDemandOptionsRequest' :: Maybe Bool
singleInstanceType = Maybe Bool
a} :: OnDemandOptionsRequest)

instance Prelude.Hashable OnDemandOptionsRequest where
  hashWithSalt :: Int -> OnDemandOptionsRequest -> Int
hashWithSalt Int
_salt OnDemandOptionsRequest' {Maybe Bool
Maybe Int
Maybe Text
Maybe CapacityReservationOptionsRequest
Maybe FleetOnDemandAllocationStrategy
singleInstanceType :: Maybe Bool
singleAvailabilityZone :: Maybe Bool
minTargetCapacity :: Maybe Int
maxTotalPrice :: Maybe Text
capacityReservationOptions :: Maybe CapacityReservationOptionsRequest
allocationStrategy :: Maybe FleetOnDemandAllocationStrategy
$sel:singleInstanceType:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
$sel:singleAvailabilityZone:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
$sel:minTargetCapacity:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Int
$sel:maxTotalPrice:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Text
$sel:capacityReservationOptions:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe CapacityReservationOptionsRequest
$sel:allocationStrategy:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe FleetOnDemandAllocationStrategy
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FleetOnDemandAllocationStrategy
allocationStrategy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CapacityReservationOptionsRequest
capacityReservationOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxTotalPrice
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minTargetCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
singleAvailabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
singleInstanceType

instance Prelude.NFData OnDemandOptionsRequest where
  rnf :: OnDemandOptionsRequest -> ()
rnf OnDemandOptionsRequest' {Maybe Bool
Maybe Int
Maybe Text
Maybe CapacityReservationOptionsRequest
Maybe FleetOnDemandAllocationStrategy
singleInstanceType :: Maybe Bool
singleAvailabilityZone :: Maybe Bool
minTargetCapacity :: Maybe Int
maxTotalPrice :: Maybe Text
capacityReservationOptions :: Maybe CapacityReservationOptionsRequest
allocationStrategy :: Maybe FleetOnDemandAllocationStrategy
$sel:singleInstanceType:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
$sel:singleAvailabilityZone:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
$sel:minTargetCapacity:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Int
$sel:maxTotalPrice:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Text
$sel:capacityReservationOptions:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe CapacityReservationOptionsRequest
$sel:allocationStrategy:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe FleetOnDemandAllocationStrategy
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe FleetOnDemandAllocationStrategy
allocationStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CapacityReservationOptionsRequest
capacityReservationOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxTotalPrice
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minTargetCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
singleAvailabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
singleInstanceType

instance Data.ToQuery OnDemandOptionsRequest where
  toQuery :: OnDemandOptionsRequest -> QueryString
toQuery OnDemandOptionsRequest' {Maybe Bool
Maybe Int
Maybe Text
Maybe CapacityReservationOptionsRequest
Maybe FleetOnDemandAllocationStrategy
singleInstanceType :: Maybe Bool
singleAvailabilityZone :: Maybe Bool
minTargetCapacity :: Maybe Int
maxTotalPrice :: Maybe Text
capacityReservationOptions :: Maybe CapacityReservationOptionsRequest
allocationStrategy :: Maybe FleetOnDemandAllocationStrategy
$sel:singleInstanceType:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
$sel:singleAvailabilityZone:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Bool
$sel:minTargetCapacity:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Int
$sel:maxTotalPrice:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe Text
$sel:capacityReservationOptions:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe CapacityReservationOptionsRequest
$sel:allocationStrategy:OnDemandOptionsRequest' :: OnDemandOptionsRequest -> Maybe FleetOnDemandAllocationStrategy
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"AllocationStrategy" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe FleetOnDemandAllocationStrategy
allocationStrategy,
        ByteString
"CapacityReservationOptions"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe CapacityReservationOptionsRequest
capacityReservationOptions,
        ByteString
"MaxTotalPrice" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
maxTotalPrice,
        ByteString
"MinTargetCapacity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
minTargetCapacity,
        ByteString
"SingleAvailabilityZone"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
singleAvailabilityZone,
        ByteString
"SingleInstanceType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
singleInstanceType
      ]