{-# 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.AutoScaling.Types.RefreshPreferences
-- 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.AutoScaling.Types.RefreshPreferences where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Describes the preferences for an instance refresh.
--
-- /See:/ 'newRefreshPreferences' smart constructor.
data RefreshPreferences = RefreshPreferences'
  { -- | The amount of time, in seconds, to wait after a checkpoint before
    -- continuing. This property is optional, but if you specify a value for
    -- it, you must also specify a value for @CheckpointPercentages@. If you
    -- specify a value for @CheckpointPercentages@ and not for
    -- @CheckpointDelay@, the @CheckpointDelay@ defaults to @3600@ (1 hour).
    RefreshPreferences -> Maybe Natural
checkpointDelay :: Prelude.Maybe Prelude.Natural,
    -- | Threshold values for each checkpoint in ascending order. Each number
    -- must be unique. To replace all instances in the Auto Scaling group, the
    -- last number in the array must be @100@.
    --
    -- For usage examples, see
    -- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-adding-checkpoints-instance-refresh.html Adding checkpoints to an instance refresh>
    -- in the /Amazon EC2 Auto Scaling User Guide/.
    RefreshPreferences -> Maybe [Natural]
checkpointPercentages :: Prelude.Maybe [Prelude.Natural],
    -- | /Not needed if the default instance warmup is defined for the group./
    --
    -- The duration of the instance warmup, in seconds.
    --
    -- The default is to use the value for the default instance warmup defined
    -- for the group. If default instance warmup is null, then @InstanceWarmup@
    -- falls back to the value of the health check grace period.
    RefreshPreferences -> Maybe Natural
instanceWarmup :: Prelude.Maybe Prelude.Natural,
    -- | The amount of capacity in the Auto Scaling group that must pass your
    -- group\'s health checks to allow the operation to continue. The value is
    -- expressed as a percentage of the desired capacity of the Auto Scaling
    -- group (rounded up to the nearest integer). The default is @90@.
    --
    -- Setting the minimum healthy percentage to 100 percent limits the rate of
    -- replacement to one instance at a time. In contrast, setting it to 0
    -- percent has the effect of replacing all instances at the same time.
    RefreshPreferences -> Maybe Natural
minHealthyPercentage :: Prelude.Maybe Prelude.Natural,
    -- | A boolean value that indicates whether skip matching is enabled. If
    -- true, then Amazon EC2 Auto Scaling skips replacing instances that match
    -- the desired configuration. If no desired configuration is specified,
    -- then it skips replacing instances that have the same configuration that
    -- is already set on the group. The default is @false@.
    RefreshPreferences -> Maybe Bool
skipMatching :: Prelude.Maybe Prelude.Bool
  }
  deriving (RefreshPreferences -> RefreshPreferences -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RefreshPreferences -> RefreshPreferences -> Bool
$c/= :: RefreshPreferences -> RefreshPreferences -> Bool
== :: RefreshPreferences -> RefreshPreferences -> Bool
$c== :: RefreshPreferences -> RefreshPreferences -> Bool
Prelude.Eq, ReadPrec [RefreshPreferences]
ReadPrec RefreshPreferences
Int -> ReadS RefreshPreferences
ReadS [RefreshPreferences]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RefreshPreferences]
$creadListPrec :: ReadPrec [RefreshPreferences]
readPrec :: ReadPrec RefreshPreferences
$creadPrec :: ReadPrec RefreshPreferences
readList :: ReadS [RefreshPreferences]
$creadList :: ReadS [RefreshPreferences]
readsPrec :: Int -> ReadS RefreshPreferences
$creadsPrec :: Int -> ReadS RefreshPreferences
Prelude.Read, Int -> RefreshPreferences -> ShowS
[RefreshPreferences] -> ShowS
RefreshPreferences -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RefreshPreferences] -> ShowS
$cshowList :: [RefreshPreferences] -> ShowS
show :: RefreshPreferences -> String
$cshow :: RefreshPreferences -> String
showsPrec :: Int -> RefreshPreferences -> ShowS
$cshowsPrec :: Int -> RefreshPreferences -> ShowS
Prelude.Show, forall x. Rep RefreshPreferences x -> RefreshPreferences
forall x. RefreshPreferences -> Rep RefreshPreferences x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RefreshPreferences x -> RefreshPreferences
$cfrom :: forall x. RefreshPreferences -> Rep RefreshPreferences x
Prelude.Generic)

-- |
-- Create a value of 'RefreshPreferences' 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:
--
-- 'checkpointDelay', 'refreshPreferences_checkpointDelay' - The amount of time, in seconds, to wait after a checkpoint before
-- continuing. This property is optional, but if you specify a value for
-- it, you must also specify a value for @CheckpointPercentages@. If you
-- specify a value for @CheckpointPercentages@ and not for
-- @CheckpointDelay@, the @CheckpointDelay@ defaults to @3600@ (1 hour).
--
-- 'checkpointPercentages', 'refreshPreferences_checkpointPercentages' - Threshold values for each checkpoint in ascending order. Each number
-- must be unique. To replace all instances in the Auto Scaling group, the
-- last number in the array must be @100@.
--
-- For usage examples, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-adding-checkpoints-instance-refresh.html Adding checkpoints to an instance refresh>
-- in the /Amazon EC2 Auto Scaling User Guide/.
--
-- 'instanceWarmup', 'refreshPreferences_instanceWarmup' - /Not needed if the default instance warmup is defined for the group./
--
-- The duration of the instance warmup, in seconds.
--
-- The default is to use the value for the default instance warmup defined
-- for the group. If default instance warmup is null, then @InstanceWarmup@
-- falls back to the value of the health check grace period.
--
-- 'minHealthyPercentage', 'refreshPreferences_minHealthyPercentage' - The amount of capacity in the Auto Scaling group that must pass your
-- group\'s health checks to allow the operation to continue. The value is
-- expressed as a percentage of the desired capacity of the Auto Scaling
-- group (rounded up to the nearest integer). The default is @90@.
--
-- Setting the minimum healthy percentage to 100 percent limits the rate of
-- replacement to one instance at a time. In contrast, setting it to 0
-- percent has the effect of replacing all instances at the same time.
--
-- 'skipMatching', 'refreshPreferences_skipMatching' - A boolean value that indicates whether skip matching is enabled. If
-- true, then Amazon EC2 Auto Scaling skips replacing instances that match
-- the desired configuration. If no desired configuration is specified,
-- then it skips replacing instances that have the same configuration that
-- is already set on the group. The default is @false@.
newRefreshPreferences ::
  RefreshPreferences
newRefreshPreferences :: RefreshPreferences
newRefreshPreferences =
  RefreshPreferences'
    { $sel:checkpointDelay:RefreshPreferences' :: Maybe Natural
checkpointDelay =
        forall a. Maybe a
Prelude.Nothing,
      $sel:checkpointPercentages:RefreshPreferences' :: Maybe [Natural]
checkpointPercentages = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceWarmup:RefreshPreferences' :: Maybe Natural
instanceWarmup = forall a. Maybe a
Prelude.Nothing,
      $sel:minHealthyPercentage:RefreshPreferences' :: Maybe Natural
minHealthyPercentage = forall a. Maybe a
Prelude.Nothing,
      $sel:skipMatching:RefreshPreferences' :: Maybe Bool
skipMatching = forall a. Maybe a
Prelude.Nothing
    }

-- | The amount of time, in seconds, to wait after a checkpoint before
-- continuing. This property is optional, but if you specify a value for
-- it, you must also specify a value for @CheckpointPercentages@. If you
-- specify a value for @CheckpointPercentages@ and not for
-- @CheckpointDelay@, the @CheckpointDelay@ defaults to @3600@ (1 hour).
refreshPreferences_checkpointDelay :: Lens.Lens' RefreshPreferences (Prelude.Maybe Prelude.Natural)
refreshPreferences_checkpointDelay :: Lens' RefreshPreferences (Maybe Natural)
refreshPreferences_checkpointDelay = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshPreferences' {Maybe Natural
checkpointDelay :: Maybe Natural
$sel:checkpointDelay:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
checkpointDelay} -> Maybe Natural
checkpointDelay) (\s :: RefreshPreferences
s@RefreshPreferences' {} Maybe Natural
a -> RefreshPreferences
s {$sel:checkpointDelay:RefreshPreferences' :: Maybe Natural
checkpointDelay = Maybe Natural
a} :: RefreshPreferences)

-- | Threshold values for each checkpoint in ascending order. Each number
-- must be unique. To replace all instances in the Auto Scaling group, the
-- last number in the array must be @100@.
--
-- For usage examples, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-adding-checkpoints-instance-refresh.html Adding checkpoints to an instance refresh>
-- in the /Amazon EC2 Auto Scaling User Guide/.
refreshPreferences_checkpointPercentages :: Lens.Lens' RefreshPreferences (Prelude.Maybe [Prelude.Natural])
refreshPreferences_checkpointPercentages :: Lens' RefreshPreferences (Maybe [Natural])
refreshPreferences_checkpointPercentages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshPreferences' {Maybe [Natural]
checkpointPercentages :: Maybe [Natural]
$sel:checkpointPercentages:RefreshPreferences' :: RefreshPreferences -> Maybe [Natural]
checkpointPercentages} -> Maybe [Natural]
checkpointPercentages) (\s :: RefreshPreferences
s@RefreshPreferences' {} Maybe [Natural]
a -> RefreshPreferences
s {$sel:checkpointPercentages:RefreshPreferences' :: Maybe [Natural]
checkpointPercentages = Maybe [Natural]
a} :: RefreshPreferences) 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

-- | /Not needed if the default instance warmup is defined for the group./
--
-- The duration of the instance warmup, in seconds.
--
-- The default is to use the value for the default instance warmup defined
-- for the group. If default instance warmup is null, then @InstanceWarmup@
-- falls back to the value of the health check grace period.
refreshPreferences_instanceWarmup :: Lens.Lens' RefreshPreferences (Prelude.Maybe Prelude.Natural)
refreshPreferences_instanceWarmup :: Lens' RefreshPreferences (Maybe Natural)
refreshPreferences_instanceWarmup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshPreferences' {Maybe Natural
instanceWarmup :: Maybe Natural
$sel:instanceWarmup:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
instanceWarmup} -> Maybe Natural
instanceWarmup) (\s :: RefreshPreferences
s@RefreshPreferences' {} Maybe Natural
a -> RefreshPreferences
s {$sel:instanceWarmup:RefreshPreferences' :: Maybe Natural
instanceWarmup = Maybe Natural
a} :: RefreshPreferences)

-- | The amount of capacity in the Auto Scaling group that must pass your
-- group\'s health checks to allow the operation to continue. The value is
-- expressed as a percentage of the desired capacity of the Auto Scaling
-- group (rounded up to the nearest integer). The default is @90@.
--
-- Setting the minimum healthy percentage to 100 percent limits the rate of
-- replacement to one instance at a time. In contrast, setting it to 0
-- percent has the effect of replacing all instances at the same time.
refreshPreferences_minHealthyPercentage :: Lens.Lens' RefreshPreferences (Prelude.Maybe Prelude.Natural)
refreshPreferences_minHealthyPercentage :: Lens' RefreshPreferences (Maybe Natural)
refreshPreferences_minHealthyPercentage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshPreferences' {Maybe Natural
minHealthyPercentage :: Maybe Natural
$sel:minHealthyPercentage:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
minHealthyPercentage} -> Maybe Natural
minHealthyPercentage) (\s :: RefreshPreferences
s@RefreshPreferences' {} Maybe Natural
a -> RefreshPreferences
s {$sel:minHealthyPercentage:RefreshPreferences' :: Maybe Natural
minHealthyPercentage = Maybe Natural
a} :: RefreshPreferences)

-- | A boolean value that indicates whether skip matching is enabled. If
-- true, then Amazon EC2 Auto Scaling skips replacing instances that match
-- the desired configuration. If no desired configuration is specified,
-- then it skips replacing instances that have the same configuration that
-- is already set on the group. The default is @false@.
refreshPreferences_skipMatching :: Lens.Lens' RefreshPreferences (Prelude.Maybe Prelude.Bool)
refreshPreferences_skipMatching :: Lens' RefreshPreferences (Maybe Bool)
refreshPreferences_skipMatching = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RefreshPreferences' {Maybe Bool
skipMatching :: Maybe Bool
$sel:skipMatching:RefreshPreferences' :: RefreshPreferences -> Maybe Bool
skipMatching} -> Maybe Bool
skipMatching) (\s :: RefreshPreferences
s@RefreshPreferences' {} Maybe Bool
a -> RefreshPreferences
s {$sel:skipMatching:RefreshPreferences' :: Maybe Bool
skipMatching = Maybe Bool
a} :: RefreshPreferences)

instance Data.FromXML RefreshPreferences where
  parseXML :: [Node] -> Either String RefreshPreferences
parseXML [Node]
x =
    Maybe Natural
-> Maybe [Natural]
-> Maybe Natural
-> Maybe Natural
-> Maybe Bool
-> RefreshPreferences
RefreshPreferences'
      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
"CheckpointDelay")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CheckpointPercentages"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InstanceWarmup")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MinHealthyPercentage")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SkipMatching")

instance Prelude.Hashable RefreshPreferences where
  hashWithSalt :: Int -> RefreshPreferences -> Int
hashWithSalt Int
_salt RefreshPreferences' {Maybe Bool
Maybe Natural
Maybe [Natural]
skipMatching :: Maybe Bool
minHealthyPercentage :: Maybe Natural
instanceWarmup :: Maybe Natural
checkpointPercentages :: Maybe [Natural]
checkpointDelay :: Maybe Natural
$sel:skipMatching:RefreshPreferences' :: RefreshPreferences -> Maybe Bool
$sel:minHealthyPercentage:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
$sel:instanceWarmup:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
$sel:checkpointPercentages:RefreshPreferences' :: RefreshPreferences -> Maybe [Natural]
$sel:checkpointDelay:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
checkpointDelay
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Natural]
checkpointPercentages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
instanceWarmup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
minHealthyPercentage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
skipMatching

instance Prelude.NFData RefreshPreferences where
  rnf :: RefreshPreferences -> ()
rnf RefreshPreferences' {Maybe Bool
Maybe Natural
Maybe [Natural]
skipMatching :: Maybe Bool
minHealthyPercentage :: Maybe Natural
instanceWarmup :: Maybe Natural
checkpointPercentages :: Maybe [Natural]
checkpointDelay :: Maybe Natural
$sel:skipMatching:RefreshPreferences' :: RefreshPreferences -> Maybe Bool
$sel:minHealthyPercentage:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
$sel:instanceWarmup:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
$sel:checkpointPercentages:RefreshPreferences' :: RefreshPreferences -> Maybe [Natural]
$sel:checkpointDelay:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
checkpointDelay
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Natural]
checkpointPercentages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
instanceWarmup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
minHealthyPercentage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
skipMatching

instance Data.ToQuery RefreshPreferences where
  toQuery :: RefreshPreferences -> QueryString
toQuery RefreshPreferences' {Maybe Bool
Maybe Natural
Maybe [Natural]
skipMatching :: Maybe Bool
minHealthyPercentage :: Maybe Natural
instanceWarmup :: Maybe Natural
checkpointPercentages :: Maybe [Natural]
checkpointDelay :: Maybe Natural
$sel:skipMatching:RefreshPreferences' :: RefreshPreferences -> Maybe Bool
$sel:minHealthyPercentage:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
$sel:instanceWarmup:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
$sel:checkpointPercentages:RefreshPreferences' :: RefreshPreferences -> Maybe [Natural]
$sel:checkpointDelay:RefreshPreferences' :: RefreshPreferences -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"CheckpointDelay" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
checkpointDelay,
        ByteString
"CheckpointPercentages"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Natural]
checkpointPercentages
            ),
        ByteString
"InstanceWarmup" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
instanceWarmup,
        ByteString
"MinHealthyPercentage" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
minHealthyPercentage,
        ByteString
"SkipMatching" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
skipMatching
      ]