{-# 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.AppRunner.Types.AutoScalingConfiguration
-- 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.AppRunner.Types.AutoScalingConfiguration where

import Amazonka.AppRunner.Types.AutoScalingConfigurationStatus
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 an App Runner automatic scaling configuration resource.
--
-- A higher @MinSize@ increases the spread of your App Runner service over
-- more Availability Zones in the Amazon Web Services Region. The tradeoff
-- is a higher minimal cost.
--
-- A lower @MaxSize@ controls your cost. The tradeoff is lower
-- responsiveness during peak demand.
--
-- Multiple revisions of a configuration might have the same
-- @AutoScalingConfigurationName@ and different
-- @AutoScalingConfigurationRevision@ values.
--
-- /See:/ 'newAutoScalingConfiguration' smart constructor.
data AutoScalingConfiguration = AutoScalingConfiguration'
  { -- | The Amazon Resource Name (ARN) of this auto scaling configuration.
    AutoScalingConfiguration -> Maybe Text
autoScalingConfigurationArn :: Prelude.Maybe Prelude.Text,
    -- | The customer-provided auto scaling configuration name. It can be used in
    -- multiple revisions of a configuration.
    AutoScalingConfiguration -> Maybe Text
autoScalingConfigurationName :: Prelude.Maybe Prelude.Text,
    -- | The revision of this auto scaling configuration. It\'s unique among all
    -- the active configurations (@\"Status\": \"ACTIVE\"@) that share the same
    -- @AutoScalingConfigurationName@.
    AutoScalingConfiguration -> Maybe Int
autoScalingConfigurationRevision :: Prelude.Maybe Prelude.Int,
    -- | The time when the auto scaling configuration was created. It\'s in Unix
    -- time stamp format.
    AutoScalingConfiguration -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The time when the auto scaling configuration was deleted. It\'s in Unix
    -- time stamp format.
    AutoScalingConfiguration -> Maybe POSIX
deletedAt :: Prelude.Maybe Data.POSIX,
    -- | It\'s set to @true@ for the configuration with the highest @Revision@
    -- among all configurations that share the same
    -- @AutoScalingConfigurationName@. It\'s set to @false@ otherwise.
    AutoScalingConfiguration -> Maybe Bool
latest :: Prelude.Maybe Prelude.Bool,
    -- | The maximum number of concurrent requests that an instance processes. If
    -- the number of concurrent requests exceeds this limit, App Runner scales
    -- the service up.
    AutoScalingConfiguration -> Maybe Int
maxConcurrency :: Prelude.Maybe Prelude.Int,
    -- | The maximum number of instances that a service scales up to. At most
    -- @MaxSize@ instances actively serve traffic for your service.
    AutoScalingConfiguration -> Maybe Int
maxSize :: Prelude.Maybe Prelude.Int,
    -- | The minimum number of instances that App Runner provisions for a
    -- service. The service always has at least @MinSize@ provisioned
    -- instances. Some of them actively serve traffic. The rest of them
    -- (provisioned and inactive instances) are a cost-effective compute
    -- capacity reserve and are ready to be quickly activated. You pay for
    -- memory usage of all the provisioned instances. You pay for CPU usage of
    -- only the active subset.
    --
    -- App Runner temporarily doubles the number of provisioned instances
    -- during deployments, to maintain the same capacity for both old and new
    -- code.
    AutoScalingConfiguration -> Maybe Int
minSize :: Prelude.Maybe Prelude.Int,
    -- | The current state of the auto scaling configuration. If the status of a
    -- configuration revision is @INACTIVE@, it was deleted and can\'t be used.
    -- Inactive configuration revisions are permanently removed some time after
    -- they are deleted.
    AutoScalingConfiguration -> Maybe AutoScalingConfigurationStatus
status :: Prelude.Maybe AutoScalingConfigurationStatus
  }
  deriving (AutoScalingConfiguration -> AutoScalingConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoScalingConfiguration -> AutoScalingConfiguration -> Bool
$c/= :: AutoScalingConfiguration -> AutoScalingConfiguration -> Bool
== :: AutoScalingConfiguration -> AutoScalingConfiguration -> Bool
$c== :: AutoScalingConfiguration -> AutoScalingConfiguration -> Bool
Prelude.Eq, ReadPrec [AutoScalingConfiguration]
ReadPrec AutoScalingConfiguration
Int -> ReadS AutoScalingConfiguration
ReadS [AutoScalingConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutoScalingConfiguration]
$creadListPrec :: ReadPrec [AutoScalingConfiguration]
readPrec :: ReadPrec AutoScalingConfiguration
$creadPrec :: ReadPrec AutoScalingConfiguration
readList :: ReadS [AutoScalingConfiguration]
$creadList :: ReadS [AutoScalingConfiguration]
readsPrec :: Int -> ReadS AutoScalingConfiguration
$creadsPrec :: Int -> ReadS AutoScalingConfiguration
Prelude.Read, Int -> AutoScalingConfiguration -> ShowS
[AutoScalingConfiguration] -> ShowS
AutoScalingConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoScalingConfiguration] -> ShowS
$cshowList :: [AutoScalingConfiguration] -> ShowS
show :: AutoScalingConfiguration -> String
$cshow :: AutoScalingConfiguration -> String
showsPrec :: Int -> AutoScalingConfiguration -> ShowS
$cshowsPrec :: Int -> AutoScalingConfiguration -> ShowS
Prelude.Show, forall x.
Rep AutoScalingConfiguration x -> AutoScalingConfiguration
forall x.
AutoScalingConfiguration -> Rep AutoScalingConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AutoScalingConfiguration x -> AutoScalingConfiguration
$cfrom :: forall x.
AutoScalingConfiguration -> Rep AutoScalingConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'AutoScalingConfiguration' 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:
--
-- 'autoScalingConfigurationArn', 'autoScalingConfiguration_autoScalingConfigurationArn' - The Amazon Resource Name (ARN) of this auto scaling configuration.
--
-- 'autoScalingConfigurationName', 'autoScalingConfiguration_autoScalingConfigurationName' - The customer-provided auto scaling configuration name. It can be used in
-- multiple revisions of a configuration.
--
-- 'autoScalingConfigurationRevision', 'autoScalingConfiguration_autoScalingConfigurationRevision' - The revision of this auto scaling configuration. It\'s unique among all
-- the active configurations (@\"Status\": \"ACTIVE\"@) that share the same
-- @AutoScalingConfigurationName@.
--
-- 'createdAt', 'autoScalingConfiguration_createdAt' - The time when the auto scaling configuration was created. It\'s in Unix
-- time stamp format.
--
-- 'deletedAt', 'autoScalingConfiguration_deletedAt' - The time when the auto scaling configuration was deleted. It\'s in Unix
-- time stamp format.
--
-- 'latest', 'autoScalingConfiguration_latest' - It\'s set to @true@ for the configuration with the highest @Revision@
-- among all configurations that share the same
-- @AutoScalingConfigurationName@. It\'s set to @false@ otherwise.
--
-- 'maxConcurrency', 'autoScalingConfiguration_maxConcurrency' - The maximum number of concurrent requests that an instance processes. If
-- the number of concurrent requests exceeds this limit, App Runner scales
-- the service up.
--
-- 'maxSize', 'autoScalingConfiguration_maxSize' - The maximum number of instances that a service scales up to. At most
-- @MaxSize@ instances actively serve traffic for your service.
--
-- 'minSize', 'autoScalingConfiguration_minSize' - The minimum number of instances that App Runner provisions for a
-- service. The service always has at least @MinSize@ provisioned
-- instances. Some of them actively serve traffic. The rest of them
-- (provisioned and inactive instances) are a cost-effective compute
-- capacity reserve and are ready to be quickly activated. You pay for
-- memory usage of all the provisioned instances. You pay for CPU usage of
-- only the active subset.
--
-- App Runner temporarily doubles the number of provisioned instances
-- during deployments, to maintain the same capacity for both old and new
-- code.
--
-- 'status', 'autoScalingConfiguration_status' - The current state of the auto scaling configuration. If the status of a
-- configuration revision is @INACTIVE@, it was deleted and can\'t be used.
-- Inactive configuration revisions are permanently removed some time after
-- they are deleted.
newAutoScalingConfiguration ::
  AutoScalingConfiguration
newAutoScalingConfiguration :: AutoScalingConfiguration
newAutoScalingConfiguration =
  AutoScalingConfiguration'
    { $sel:autoScalingConfigurationArn:AutoScalingConfiguration' :: Maybe Text
autoScalingConfigurationArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingConfigurationName:AutoScalingConfiguration' :: Maybe Text
autoScalingConfigurationName = forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingConfigurationRevision:AutoScalingConfiguration' :: Maybe Int
autoScalingConfigurationRevision =
        forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:AutoScalingConfiguration' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:deletedAt:AutoScalingConfiguration' :: Maybe POSIX
deletedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:latest:AutoScalingConfiguration' :: Maybe Bool
latest = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrency:AutoScalingConfiguration' :: Maybe Int
maxConcurrency = forall a. Maybe a
Prelude.Nothing,
      $sel:maxSize:AutoScalingConfiguration' :: Maybe Int
maxSize = forall a. Maybe a
Prelude.Nothing,
      $sel:minSize:AutoScalingConfiguration' :: Maybe Int
minSize = forall a. Maybe a
Prelude.Nothing,
      $sel:status:AutoScalingConfiguration' :: Maybe AutoScalingConfigurationStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of this auto scaling configuration.
autoScalingConfiguration_autoScalingConfigurationArn :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Text)
autoScalingConfiguration_autoScalingConfigurationArn :: Lens' AutoScalingConfiguration (Maybe Text)
autoScalingConfiguration_autoScalingConfigurationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Text
autoScalingConfigurationArn :: Maybe Text
$sel:autoScalingConfigurationArn:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Text
autoScalingConfigurationArn} -> Maybe Text
autoScalingConfigurationArn) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Text
a -> AutoScalingConfiguration
s {$sel:autoScalingConfigurationArn:AutoScalingConfiguration' :: Maybe Text
autoScalingConfigurationArn = Maybe Text
a} :: AutoScalingConfiguration)

-- | The customer-provided auto scaling configuration name. It can be used in
-- multiple revisions of a configuration.
autoScalingConfiguration_autoScalingConfigurationName :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Text)
autoScalingConfiguration_autoScalingConfigurationName :: Lens' AutoScalingConfiguration (Maybe Text)
autoScalingConfiguration_autoScalingConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Text
autoScalingConfigurationName :: Maybe Text
$sel:autoScalingConfigurationName:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Text
autoScalingConfigurationName} -> Maybe Text
autoScalingConfigurationName) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Text
a -> AutoScalingConfiguration
s {$sel:autoScalingConfigurationName:AutoScalingConfiguration' :: Maybe Text
autoScalingConfigurationName = Maybe Text
a} :: AutoScalingConfiguration)

-- | The revision of this auto scaling configuration. It\'s unique among all
-- the active configurations (@\"Status\": \"ACTIVE\"@) that share the same
-- @AutoScalingConfigurationName@.
autoScalingConfiguration_autoScalingConfigurationRevision :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Int)
autoScalingConfiguration_autoScalingConfigurationRevision :: Lens' AutoScalingConfiguration (Maybe Int)
autoScalingConfiguration_autoScalingConfigurationRevision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Int
autoScalingConfigurationRevision :: Maybe Int
$sel:autoScalingConfigurationRevision:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
autoScalingConfigurationRevision} -> Maybe Int
autoScalingConfigurationRevision) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Int
a -> AutoScalingConfiguration
s {$sel:autoScalingConfigurationRevision:AutoScalingConfiguration' :: Maybe Int
autoScalingConfigurationRevision = Maybe Int
a} :: AutoScalingConfiguration)

-- | The time when the auto scaling configuration was created. It\'s in Unix
-- time stamp format.
autoScalingConfiguration_createdAt :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.UTCTime)
autoScalingConfiguration_createdAt :: Lens' AutoScalingConfiguration (Maybe UTCTime)
autoScalingConfiguration_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe POSIX
a -> AutoScalingConfiguration
s {$sel:createdAt:AutoScalingConfiguration' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: AutoScalingConfiguration) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The time when the auto scaling configuration was deleted. It\'s in Unix
-- time stamp format.
autoScalingConfiguration_deletedAt :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.UTCTime)
autoScalingConfiguration_deletedAt :: Lens' AutoScalingConfiguration (Maybe UTCTime)
autoScalingConfiguration_deletedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe POSIX
deletedAt :: Maybe POSIX
$sel:deletedAt:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe POSIX
deletedAt} -> Maybe POSIX
deletedAt) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe POSIX
a -> AutoScalingConfiguration
s {$sel:deletedAt:AutoScalingConfiguration' :: Maybe POSIX
deletedAt = Maybe POSIX
a} :: AutoScalingConfiguration) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | It\'s set to @true@ for the configuration with the highest @Revision@
-- among all configurations that share the same
-- @AutoScalingConfigurationName@. It\'s set to @false@ otherwise.
autoScalingConfiguration_latest :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Bool)
autoScalingConfiguration_latest :: Lens' AutoScalingConfiguration (Maybe Bool)
autoScalingConfiguration_latest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Bool
latest :: Maybe Bool
$sel:latest:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Bool
latest} -> Maybe Bool
latest) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Bool
a -> AutoScalingConfiguration
s {$sel:latest:AutoScalingConfiguration' :: Maybe Bool
latest = Maybe Bool
a} :: AutoScalingConfiguration)

-- | The maximum number of concurrent requests that an instance processes. If
-- the number of concurrent requests exceeds this limit, App Runner scales
-- the service up.
autoScalingConfiguration_maxConcurrency :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Int)
autoScalingConfiguration_maxConcurrency :: Lens' AutoScalingConfiguration (Maybe Int)
autoScalingConfiguration_maxConcurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Int
maxConcurrency :: Maybe Int
$sel:maxConcurrency:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
maxConcurrency} -> Maybe Int
maxConcurrency) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Int
a -> AutoScalingConfiguration
s {$sel:maxConcurrency:AutoScalingConfiguration' :: Maybe Int
maxConcurrency = Maybe Int
a} :: AutoScalingConfiguration)

-- | The maximum number of instances that a service scales up to. At most
-- @MaxSize@ instances actively serve traffic for your service.
autoScalingConfiguration_maxSize :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Int)
autoScalingConfiguration_maxSize :: Lens' AutoScalingConfiguration (Maybe Int)
autoScalingConfiguration_maxSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Int
maxSize :: Maybe Int
$sel:maxSize:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
maxSize} -> Maybe Int
maxSize) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Int
a -> AutoScalingConfiguration
s {$sel:maxSize:AutoScalingConfiguration' :: Maybe Int
maxSize = Maybe Int
a} :: AutoScalingConfiguration)

-- | The minimum number of instances that App Runner provisions for a
-- service. The service always has at least @MinSize@ provisioned
-- instances. Some of them actively serve traffic. The rest of them
-- (provisioned and inactive instances) are a cost-effective compute
-- capacity reserve and are ready to be quickly activated. You pay for
-- memory usage of all the provisioned instances. You pay for CPU usage of
-- only the active subset.
--
-- App Runner temporarily doubles the number of provisioned instances
-- during deployments, to maintain the same capacity for both old and new
-- code.
autoScalingConfiguration_minSize :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe Prelude.Int)
autoScalingConfiguration_minSize :: Lens' AutoScalingConfiguration (Maybe Int)
autoScalingConfiguration_minSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe Int
minSize :: Maybe Int
$sel:minSize:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
minSize} -> Maybe Int
minSize) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe Int
a -> AutoScalingConfiguration
s {$sel:minSize:AutoScalingConfiguration' :: Maybe Int
minSize = Maybe Int
a} :: AutoScalingConfiguration)

-- | The current state of the auto scaling configuration. If the status of a
-- configuration revision is @INACTIVE@, it was deleted and can\'t be used.
-- Inactive configuration revisions are permanently removed some time after
-- they are deleted.
autoScalingConfiguration_status :: Lens.Lens' AutoScalingConfiguration (Prelude.Maybe AutoScalingConfigurationStatus)
autoScalingConfiguration_status :: Lens'
  AutoScalingConfiguration (Maybe AutoScalingConfigurationStatus)
autoScalingConfiguration_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoScalingConfiguration' {Maybe AutoScalingConfigurationStatus
status :: Maybe AutoScalingConfigurationStatus
$sel:status:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe AutoScalingConfigurationStatus
status} -> Maybe AutoScalingConfigurationStatus
status) (\s :: AutoScalingConfiguration
s@AutoScalingConfiguration' {} Maybe AutoScalingConfigurationStatus
a -> AutoScalingConfiguration
s {$sel:status:AutoScalingConfiguration' :: Maybe AutoScalingConfigurationStatus
status = Maybe AutoScalingConfigurationStatus
a} :: AutoScalingConfiguration)

instance Data.FromJSON AutoScalingConfiguration where
  parseJSON :: Value -> Parser AutoScalingConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AutoScalingConfiguration"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe AutoScalingConfigurationStatus
-> AutoScalingConfiguration
AutoScalingConfiguration'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AutoScalingConfigurationArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AutoScalingConfigurationName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AutoScalingConfigurationRevision")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DeletedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Latest")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxConcurrency")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MaxSize")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"MinSize")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
      )

instance Prelude.Hashable AutoScalingConfiguration where
  hashWithSalt :: Int -> AutoScalingConfiguration -> Int
hashWithSalt Int
_salt AutoScalingConfiguration' {Maybe Bool
Maybe Int
Maybe Text
Maybe POSIX
Maybe AutoScalingConfigurationStatus
status :: Maybe AutoScalingConfigurationStatus
minSize :: Maybe Int
maxSize :: Maybe Int
maxConcurrency :: Maybe Int
latest :: Maybe Bool
deletedAt :: Maybe POSIX
createdAt :: Maybe POSIX
autoScalingConfigurationRevision :: Maybe Int
autoScalingConfigurationName :: Maybe Text
autoScalingConfigurationArn :: Maybe Text
$sel:status:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe AutoScalingConfigurationStatus
$sel:minSize:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:maxSize:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:maxConcurrency:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:latest:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Bool
$sel:deletedAt:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe POSIX
$sel:createdAt:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe POSIX
$sel:autoScalingConfigurationRevision:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:autoScalingConfigurationName:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Text
$sel:autoScalingConfigurationArn:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoScalingConfigurationArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoScalingConfigurationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
autoScalingConfigurationRevision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
deletedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
latest
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxConcurrency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutoScalingConfigurationStatus
status

instance Prelude.NFData AutoScalingConfiguration where
  rnf :: AutoScalingConfiguration -> ()
rnf AutoScalingConfiguration' {Maybe Bool
Maybe Int
Maybe Text
Maybe POSIX
Maybe AutoScalingConfigurationStatus
status :: Maybe AutoScalingConfigurationStatus
minSize :: Maybe Int
maxSize :: Maybe Int
maxConcurrency :: Maybe Int
latest :: Maybe Bool
deletedAt :: Maybe POSIX
createdAt :: Maybe POSIX
autoScalingConfigurationRevision :: Maybe Int
autoScalingConfigurationName :: Maybe Text
autoScalingConfigurationArn :: Maybe Text
$sel:status:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe AutoScalingConfigurationStatus
$sel:minSize:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:maxSize:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:maxConcurrency:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:latest:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Bool
$sel:deletedAt:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe POSIX
$sel:createdAt:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe POSIX
$sel:autoScalingConfigurationRevision:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Int
$sel:autoScalingConfigurationName:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Text
$sel:autoScalingConfigurationArn:AutoScalingConfiguration' :: AutoScalingConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoScalingConfigurationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoScalingConfigurationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
autoScalingConfigurationRevision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
deletedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
latest
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxConcurrency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoScalingConfigurationStatus
status