{-# 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.OpsWorks.Types.Layer
-- 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.OpsWorks.Types.Layer where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.OpsWorks.Types.CloudWatchLogsConfiguration
import Amazonka.OpsWorks.Types.LayerAttributesKeys
import Amazonka.OpsWorks.Types.LayerType
import Amazonka.OpsWorks.Types.LifecycleEventConfiguration
import Amazonka.OpsWorks.Types.Recipes
import Amazonka.OpsWorks.Types.VolumeConfiguration
import qualified Amazonka.Prelude as Prelude

-- | Describes a layer.
--
-- /See:/ 'newLayer' smart constructor.
data Layer = Layer'
  { -- | The Amazon Resource Number (ARN) of a layer.
    Layer -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The layer attributes.
    --
    -- For the @HaproxyStatsPassword@, @MysqlRootPassword@, and
    -- @GangliaPassword@ attributes, AWS OpsWorks Stacks returns
    -- @*****FILTERED*****@ instead of the actual value
    --
    -- For an ECS Cluster layer, AWS OpsWorks Stacks the @EcsClusterArn@
    -- attribute is set to the cluster\'s ARN.
    Layer -> Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes :: Prelude.Maybe (Prelude.HashMap LayerAttributesKeys (Prelude.Maybe Prelude.Text)),
    -- | Whether to automatically assign an
    -- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/elastic-ip-addresses-eip.html Elastic IP address>
    -- to the layer\'s instances. For more information, see
    -- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinglayers-basics-edit.html How to Edit a Layer>.
    Layer -> Maybe Bool
autoAssignElasticIps :: Prelude.Maybe Prelude.Bool,
    -- | For stacks that are running in a VPC, whether to automatically assign a
    -- public IP address to the layer\'s instances. For more information, see
    -- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinglayers-basics-edit.html How to Edit a Layer>.
    Layer -> Maybe Bool
autoAssignPublicIps :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon CloudWatch Logs configuration settings for the layer.
    Layer -> Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration :: Prelude.Maybe CloudWatchLogsConfiguration,
    -- | Date when the layer was created.
    Layer -> Maybe Text
createdAt :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the default IAM profile to be used for the layer\'s EC2
    -- instances. For more information about IAM ARNs, see
    -- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html Using Identifiers>.
    Layer -> Maybe Text
customInstanceProfileArn :: Prelude.Maybe Prelude.Text,
    -- | A JSON formatted string containing the layer\'s custom stack
    -- configuration and deployment attributes.
    Layer -> Maybe Text
customJson :: Prelude.Maybe Prelude.Text,
    -- | A @LayerCustomRecipes@ object that specifies the layer\'s custom
    -- recipes.
    Layer -> Maybe Recipes
customRecipes :: Prelude.Maybe Recipes,
    -- | An array containing the layer\'s custom security group IDs.
    Layer -> Maybe [Text]
customSecurityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | AWS OpsWorks Stacks supports five lifecycle events: __setup__,
    -- __configuration__, __deploy__, __undeploy__, and __shutdown__. For each
    -- layer, AWS OpsWorks Stacks runs a set of standard recipes for each
    -- event. You can also provide custom recipes for any or all layers and
    -- events. AWS OpsWorks Stacks runs custom event recipes after the standard
    -- recipes. @LayerCustomRecipes@ specifies the custom recipes for a
    -- particular layer to be run in response to each of the five events.
    --
    -- To specify a recipe, use the cookbook\'s directory name in the
    -- repository followed by two colons and the recipe name, which is the
    -- recipe\'s file name without the @.rb@ extension. For example:
    -- @phpapp2::dbsetup@ specifies the @dbsetup.rb@ recipe in the
    -- repository\'s @phpapp2@ folder.
    Layer -> Maybe Recipes
defaultRecipes :: Prelude.Maybe Recipes,
    -- | An array containing the layer\'s security group names.
    Layer -> Maybe [Text]
defaultSecurityGroupNames :: Prelude.Maybe [Prelude.Text],
    -- | Whether auto healing is disabled for the layer.
    Layer -> Maybe Bool
enableAutoHealing :: Prelude.Maybe Prelude.Bool,
    -- | Whether to install operating system and package updates when the
    -- instance boots. The default value is @true@. If this value is set to
    -- @false@, you must then update your instances manually by using
    -- CreateDeployment to run the @update_dependencies@ stack command or
    -- manually running @yum@ (Amazon Linux) or @apt-get@ (Ubuntu) on the
    -- instances.
    --
    -- We strongly recommend using the default value of @true@, to ensure that
    -- your instances have the latest security updates.
    Layer -> Maybe Bool
installUpdatesOnBoot :: Prelude.Maybe Prelude.Bool,
    -- | The layer ID.
    Layer -> Maybe Text
layerId :: Prelude.Maybe Prelude.Text,
    -- | A @LifeCycleEventConfiguration@ object that specifies the Shutdown event
    -- configuration.
    Layer -> Maybe LifecycleEventConfiguration
lifecycleEventConfiguration :: Prelude.Maybe LifecycleEventConfiguration,
    -- | The layer name.
    Layer -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | An array of @Package@ objects that describe the layer\'s packages.
    Layer -> Maybe [Text]
packages :: Prelude.Maybe [Prelude.Text],
    -- | The layer short name.
    Layer -> Maybe Text
shortname :: Prelude.Maybe Prelude.Text,
    -- | The layer stack ID.
    Layer -> Maybe Text
stackId :: Prelude.Maybe Prelude.Text,
    -- | The layer type.
    Layer -> Maybe LayerType
type' :: Prelude.Maybe LayerType,
    -- | Whether the layer uses Amazon EBS-optimized instances.
    Layer -> Maybe Bool
useEbsOptimizedInstances :: Prelude.Maybe Prelude.Bool,
    -- | A @VolumeConfigurations@ object that describes the layer\'s Amazon EBS
    -- volumes.
    Layer -> Maybe [VolumeConfiguration]
volumeConfigurations :: Prelude.Maybe [VolumeConfiguration]
  }
  deriving (Layer -> Layer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Layer -> Layer -> Bool
$c/= :: Layer -> Layer -> Bool
== :: Layer -> Layer -> Bool
$c== :: Layer -> Layer -> Bool
Prelude.Eq, ReadPrec [Layer]
ReadPrec Layer
Int -> ReadS Layer
ReadS [Layer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Layer]
$creadListPrec :: ReadPrec [Layer]
readPrec :: ReadPrec Layer
$creadPrec :: ReadPrec Layer
readList :: ReadS [Layer]
$creadList :: ReadS [Layer]
readsPrec :: Int -> ReadS Layer
$creadsPrec :: Int -> ReadS Layer
Prelude.Read, Int -> Layer -> ShowS
[Layer] -> ShowS
Layer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Layer] -> ShowS
$cshowList :: [Layer] -> ShowS
show :: Layer -> String
$cshow :: Layer -> String
showsPrec :: Int -> Layer -> ShowS
$cshowsPrec :: Int -> Layer -> ShowS
Prelude.Show, forall x. Rep Layer x -> Layer
forall x. Layer -> Rep Layer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Layer x -> Layer
$cfrom :: forall x. Layer -> Rep Layer x
Prelude.Generic)

-- |
-- Create a value of 'Layer' 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:
--
-- 'arn', 'layer_arn' - The Amazon Resource Number (ARN) of a layer.
--
-- 'attributes', 'layer_attributes' - The layer attributes.
--
-- For the @HaproxyStatsPassword@, @MysqlRootPassword@, and
-- @GangliaPassword@ attributes, AWS OpsWorks Stacks returns
-- @*****FILTERED*****@ instead of the actual value
--
-- For an ECS Cluster layer, AWS OpsWorks Stacks the @EcsClusterArn@
-- attribute is set to the cluster\'s ARN.
--
-- 'autoAssignElasticIps', 'layer_autoAssignElasticIps' - Whether to automatically assign an
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/elastic-ip-addresses-eip.html Elastic IP address>
-- to the layer\'s instances. For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinglayers-basics-edit.html How to Edit a Layer>.
--
-- 'autoAssignPublicIps', 'layer_autoAssignPublicIps' - For stacks that are running in a VPC, whether to automatically assign a
-- public IP address to the layer\'s instances. For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinglayers-basics-edit.html How to Edit a Layer>.
--
-- 'cloudWatchLogsConfiguration', 'layer_cloudWatchLogsConfiguration' - The Amazon CloudWatch Logs configuration settings for the layer.
--
-- 'createdAt', 'layer_createdAt' - Date when the layer was created.
--
-- 'customInstanceProfileArn', 'layer_customInstanceProfileArn' - The ARN of the default IAM profile to be used for the layer\'s EC2
-- instances. For more information about IAM ARNs, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html Using Identifiers>.
--
-- 'customJson', 'layer_customJson' - A JSON formatted string containing the layer\'s custom stack
-- configuration and deployment attributes.
--
-- 'customRecipes', 'layer_customRecipes' - A @LayerCustomRecipes@ object that specifies the layer\'s custom
-- recipes.
--
-- 'customSecurityGroupIds', 'layer_customSecurityGroupIds' - An array containing the layer\'s custom security group IDs.
--
-- 'defaultRecipes', 'layer_defaultRecipes' - AWS OpsWorks Stacks supports five lifecycle events: __setup__,
-- __configuration__, __deploy__, __undeploy__, and __shutdown__. For each
-- layer, AWS OpsWorks Stacks runs a set of standard recipes for each
-- event. You can also provide custom recipes for any or all layers and
-- events. AWS OpsWorks Stacks runs custom event recipes after the standard
-- recipes. @LayerCustomRecipes@ specifies the custom recipes for a
-- particular layer to be run in response to each of the five events.
--
-- To specify a recipe, use the cookbook\'s directory name in the
-- repository followed by two colons and the recipe name, which is the
-- recipe\'s file name without the @.rb@ extension. For example:
-- @phpapp2::dbsetup@ specifies the @dbsetup.rb@ recipe in the
-- repository\'s @phpapp2@ folder.
--
-- 'defaultSecurityGroupNames', 'layer_defaultSecurityGroupNames' - An array containing the layer\'s security group names.
--
-- 'enableAutoHealing', 'layer_enableAutoHealing' - Whether auto healing is disabled for the layer.
--
-- 'installUpdatesOnBoot', 'layer_installUpdatesOnBoot' - Whether to install operating system and package updates when the
-- instance boots. The default value is @true@. If this value is set to
-- @false@, you must then update your instances manually by using
-- CreateDeployment to run the @update_dependencies@ stack command or
-- manually running @yum@ (Amazon Linux) or @apt-get@ (Ubuntu) on the
-- instances.
--
-- We strongly recommend using the default value of @true@, to ensure that
-- your instances have the latest security updates.
--
-- 'layerId', 'layer_layerId' - The layer ID.
--
-- 'lifecycleEventConfiguration', 'layer_lifecycleEventConfiguration' - A @LifeCycleEventConfiguration@ object that specifies the Shutdown event
-- configuration.
--
-- 'name', 'layer_name' - The layer name.
--
-- 'packages', 'layer_packages' - An array of @Package@ objects that describe the layer\'s packages.
--
-- 'shortname', 'layer_shortname' - The layer short name.
--
-- 'stackId', 'layer_stackId' - The layer stack ID.
--
-- 'type'', 'layer_type' - The layer type.
--
-- 'useEbsOptimizedInstances', 'layer_useEbsOptimizedInstances' - Whether the layer uses Amazon EBS-optimized instances.
--
-- 'volumeConfigurations', 'layer_volumeConfigurations' - A @VolumeConfigurations@ object that describes the layer\'s Amazon EBS
-- volumes.
newLayer ::
  Layer
newLayer :: Layer
newLayer =
  Layer'
    { $sel:arn:Layer' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:attributes:Layer' :: Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:autoAssignElasticIps:Layer' :: Maybe Bool
autoAssignElasticIps = forall a. Maybe a
Prelude.Nothing,
      $sel:autoAssignPublicIps:Layer' :: Maybe Bool
autoAssignPublicIps = forall a. Maybe a
Prelude.Nothing,
      $sel:cloudWatchLogsConfiguration:Layer' :: Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:Layer' :: Maybe Text
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:customInstanceProfileArn:Layer' :: Maybe Text
customInstanceProfileArn = forall a. Maybe a
Prelude.Nothing,
      $sel:customJson:Layer' :: Maybe Text
customJson = forall a. Maybe a
Prelude.Nothing,
      $sel:customRecipes:Layer' :: Maybe Recipes
customRecipes = forall a. Maybe a
Prelude.Nothing,
      $sel:customSecurityGroupIds:Layer' :: Maybe [Text]
customSecurityGroupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultRecipes:Layer' :: Maybe Recipes
defaultRecipes = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultSecurityGroupNames:Layer' :: Maybe [Text]
defaultSecurityGroupNames = forall a. Maybe a
Prelude.Nothing,
      $sel:enableAutoHealing:Layer' :: Maybe Bool
enableAutoHealing = forall a. Maybe a
Prelude.Nothing,
      $sel:installUpdatesOnBoot:Layer' :: Maybe Bool
installUpdatesOnBoot = forall a. Maybe a
Prelude.Nothing,
      $sel:layerId:Layer' :: Maybe Text
layerId = forall a. Maybe a
Prelude.Nothing,
      $sel:lifecycleEventConfiguration:Layer' :: Maybe LifecycleEventConfiguration
lifecycleEventConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Layer' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:packages:Layer' :: Maybe [Text]
packages = forall a. Maybe a
Prelude.Nothing,
      $sel:shortname:Layer' :: Maybe Text
shortname = forall a. Maybe a
Prelude.Nothing,
      $sel:stackId:Layer' :: Maybe Text
stackId = forall a. Maybe a
Prelude.Nothing,
      $sel:type':Layer' :: Maybe LayerType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:useEbsOptimizedInstances:Layer' :: Maybe Bool
useEbsOptimizedInstances = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeConfigurations:Layer' :: Maybe [VolumeConfiguration]
volumeConfigurations = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Number (ARN) of a layer.
layer_arn :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_arn :: Lens' Layer (Maybe Text)
layer_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
arn :: Maybe Text
$sel:arn:Layer' :: Layer -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:arn:Layer' :: Maybe Text
arn = Maybe Text
a} :: Layer)

-- | The layer attributes.
--
-- For the @HaproxyStatsPassword@, @MysqlRootPassword@, and
-- @GangliaPassword@ attributes, AWS OpsWorks Stacks returns
-- @*****FILTERED*****@ instead of the actual value
--
-- For an ECS Cluster layer, AWS OpsWorks Stacks the @EcsClusterArn@
-- attribute is set to the cluster\'s ARN.
layer_attributes :: Lens.Lens' Layer (Prelude.Maybe (Prelude.HashMap LayerAttributesKeys (Prelude.Maybe Prelude.Text)))
layer_attributes :: Lens' Layer (Maybe (HashMap LayerAttributesKeys (Maybe Text)))
layer_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes :: Maybe (HashMap LayerAttributesKeys (Maybe Text))
$sel:attributes:Layer' :: Layer -> Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes} -> Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes) (\s :: Layer
s@Layer' {} Maybe (HashMap LayerAttributesKeys (Maybe Text))
a -> Layer
s {$sel:attributes:Layer' :: Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes = Maybe (HashMap LayerAttributesKeys (Maybe Text))
a} :: Layer) 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

-- | Whether to automatically assign an
-- <https://docs.aws.amazon.com/AWSEC2/latest/UserGuide/elastic-ip-addresses-eip.html Elastic IP address>
-- to the layer\'s instances. For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinglayers-basics-edit.html How to Edit a Layer>.
layer_autoAssignElasticIps :: Lens.Lens' Layer (Prelude.Maybe Prelude.Bool)
layer_autoAssignElasticIps :: Lens' Layer (Maybe Bool)
layer_autoAssignElasticIps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Bool
autoAssignElasticIps :: Maybe Bool
$sel:autoAssignElasticIps:Layer' :: Layer -> Maybe Bool
autoAssignElasticIps} -> Maybe Bool
autoAssignElasticIps) (\s :: Layer
s@Layer' {} Maybe Bool
a -> Layer
s {$sel:autoAssignElasticIps:Layer' :: Maybe Bool
autoAssignElasticIps = Maybe Bool
a} :: Layer)

-- | For stacks that are running in a VPC, whether to automatically assign a
-- public IP address to the layer\'s instances. For more information, see
-- <https://docs.aws.amazon.com/opsworks/latest/userguide/workinglayers-basics-edit.html How to Edit a Layer>.
layer_autoAssignPublicIps :: Lens.Lens' Layer (Prelude.Maybe Prelude.Bool)
layer_autoAssignPublicIps :: Lens' Layer (Maybe Bool)
layer_autoAssignPublicIps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Bool
autoAssignPublicIps :: Maybe Bool
$sel:autoAssignPublicIps:Layer' :: Layer -> Maybe Bool
autoAssignPublicIps} -> Maybe Bool
autoAssignPublicIps) (\s :: Layer
s@Layer' {} Maybe Bool
a -> Layer
s {$sel:autoAssignPublicIps:Layer' :: Maybe Bool
autoAssignPublicIps = Maybe Bool
a} :: Layer)

-- | The Amazon CloudWatch Logs configuration settings for the layer.
layer_cloudWatchLogsConfiguration :: Lens.Lens' Layer (Prelude.Maybe CloudWatchLogsConfiguration)
layer_cloudWatchLogsConfiguration :: Lens' Layer (Maybe CloudWatchLogsConfiguration)
layer_cloudWatchLogsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration :: Maybe CloudWatchLogsConfiguration
$sel:cloudWatchLogsConfiguration:Layer' :: Layer -> Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration} -> Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration) (\s :: Layer
s@Layer' {} Maybe CloudWatchLogsConfiguration
a -> Layer
s {$sel:cloudWatchLogsConfiguration:Layer' :: Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration = Maybe CloudWatchLogsConfiguration
a} :: Layer)

-- | Date when the layer was created.
layer_createdAt :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_createdAt :: Lens' Layer (Maybe Text)
layer_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
createdAt :: Maybe Text
$sel:createdAt:Layer' :: Layer -> Maybe Text
createdAt} -> Maybe Text
createdAt) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:createdAt:Layer' :: Maybe Text
createdAt = Maybe Text
a} :: Layer)

-- | The ARN of the default IAM profile to be used for the layer\'s EC2
-- instances. For more information about IAM ARNs, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/Using_Identifiers.html Using Identifiers>.
layer_customInstanceProfileArn :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_customInstanceProfileArn :: Lens' Layer (Maybe Text)
layer_customInstanceProfileArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
customInstanceProfileArn :: Maybe Text
$sel:customInstanceProfileArn:Layer' :: Layer -> Maybe Text
customInstanceProfileArn} -> Maybe Text
customInstanceProfileArn) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:customInstanceProfileArn:Layer' :: Maybe Text
customInstanceProfileArn = Maybe Text
a} :: Layer)

-- | A JSON formatted string containing the layer\'s custom stack
-- configuration and deployment attributes.
layer_customJson :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_customJson :: Lens' Layer (Maybe Text)
layer_customJson = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
customJson :: Maybe Text
$sel:customJson:Layer' :: Layer -> Maybe Text
customJson} -> Maybe Text
customJson) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:customJson:Layer' :: Maybe Text
customJson = Maybe Text
a} :: Layer)

-- | A @LayerCustomRecipes@ object that specifies the layer\'s custom
-- recipes.
layer_customRecipes :: Lens.Lens' Layer (Prelude.Maybe Recipes)
layer_customRecipes :: Lens' Layer (Maybe Recipes)
layer_customRecipes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Recipes
customRecipes :: Maybe Recipes
$sel:customRecipes:Layer' :: Layer -> Maybe Recipes
customRecipes} -> Maybe Recipes
customRecipes) (\s :: Layer
s@Layer' {} Maybe Recipes
a -> Layer
s {$sel:customRecipes:Layer' :: Maybe Recipes
customRecipes = Maybe Recipes
a} :: Layer)

-- | An array containing the layer\'s custom security group IDs.
layer_customSecurityGroupIds :: Lens.Lens' Layer (Prelude.Maybe [Prelude.Text])
layer_customSecurityGroupIds :: Lens' Layer (Maybe [Text])
layer_customSecurityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe [Text]
customSecurityGroupIds :: Maybe [Text]
$sel:customSecurityGroupIds:Layer' :: Layer -> Maybe [Text]
customSecurityGroupIds} -> Maybe [Text]
customSecurityGroupIds) (\s :: Layer
s@Layer' {} Maybe [Text]
a -> Layer
s {$sel:customSecurityGroupIds:Layer' :: Maybe [Text]
customSecurityGroupIds = Maybe [Text]
a} :: Layer) 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

-- | AWS OpsWorks Stacks supports five lifecycle events: __setup__,
-- __configuration__, __deploy__, __undeploy__, and __shutdown__. For each
-- layer, AWS OpsWorks Stacks runs a set of standard recipes for each
-- event. You can also provide custom recipes for any or all layers and
-- events. AWS OpsWorks Stacks runs custom event recipes after the standard
-- recipes. @LayerCustomRecipes@ specifies the custom recipes for a
-- particular layer to be run in response to each of the five events.
--
-- To specify a recipe, use the cookbook\'s directory name in the
-- repository followed by two colons and the recipe name, which is the
-- recipe\'s file name without the @.rb@ extension. For example:
-- @phpapp2::dbsetup@ specifies the @dbsetup.rb@ recipe in the
-- repository\'s @phpapp2@ folder.
layer_defaultRecipes :: Lens.Lens' Layer (Prelude.Maybe Recipes)
layer_defaultRecipes :: Lens' Layer (Maybe Recipes)
layer_defaultRecipes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Recipes
defaultRecipes :: Maybe Recipes
$sel:defaultRecipes:Layer' :: Layer -> Maybe Recipes
defaultRecipes} -> Maybe Recipes
defaultRecipes) (\s :: Layer
s@Layer' {} Maybe Recipes
a -> Layer
s {$sel:defaultRecipes:Layer' :: Maybe Recipes
defaultRecipes = Maybe Recipes
a} :: Layer)

-- | An array containing the layer\'s security group names.
layer_defaultSecurityGroupNames :: Lens.Lens' Layer (Prelude.Maybe [Prelude.Text])
layer_defaultSecurityGroupNames :: Lens' Layer (Maybe [Text])
layer_defaultSecurityGroupNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe [Text]
defaultSecurityGroupNames :: Maybe [Text]
$sel:defaultSecurityGroupNames:Layer' :: Layer -> Maybe [Text]
defaultSecurityGroupNames} -> Maybe [Text]
defaultSecurityGroupNames) (\s :: Layer
s@Layer' {} Maybe [Text]
a -> Layer
s {$sel:defaultSecurityGroupNames:Layer' :: Maybe [Text]
defaultSecurityGroupNames = Maybe [Text]
a} :: Layer) 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

-- | Whether auto healing is disabled for the layer.
layer_enableAutoHealing :: Lens.Lens' Layer (Prelude.Maybe Prelude.Bool)
layer_enableAutoHealing :: Lens' Layer (Maybe Bool)
layer_enableAutoHealing = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Bool
enableAutoHealing :: Maybe Bool
$sel:enableAutoHealing:Layer' :: Layer -> Maybe Bool
enableAutoHealing} -> Maybe Bool
enableAutoHealing) (\s :: Layer
s@Layer' {} Maybe Bool
a -> Layer
s {$sel:enableAutoHealing:Layer' :: Maybe Bool
enableAutoHealing = Maybe Bool
a} :: Layer)

-- | Whether to install operating system and package updates when the
-- instance boots. The default value is @true@. If this value is set to
-- @false@, you must then update your instances manually by using
-- CreateDeployment to run the @update_dependencies@ stack command or
-- manually running @yum@ (Amazon Linux) or @apt-get@ (Ubuntu) on the
-- instances.
--
-- We strongly recommend using the default value of @true@, to ensure that
-- your instances have the latest security updates.
layer_installUpdatesOnBoot :: Lens.Lens' Layer (Prelude.Maybe Prelude.Bool)
layer_installUpdatesOnBoot :: Lens' Layer (Maybe Bool)
layer_installUpdatesOnBoot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Bool
installUpdatesOnBoot :: Maybe Bool
$sel:installUpdatesOnBoot:Layer' :: Layer -> Maybe Bool
installUpdatesOnBoot} -> Maybe Bool
installUpdatesOnBoot) (\s :: Layer
s@Layer' {} Maybe Bool
a -> Layer
s {$sel:installUpdatesOnBoot:Layer' :: Maybe Bool
installUpdatesOnBoot = Maybe Bool
a} :: Layer)

-- | The layer ID.
layer_layerId :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_layerId :: Lens' Layer (Maybe Text)
layer_layerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
layerId :: Maybe Text
$sel:layerId:Layer' :: Layer -> Maybe Text
layerId} -> Maybe Text
layerId) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:layerId:Layer' :: Maybe Text
layerId = Maybe Text
a} :: Layer)

-- | A @LifeCycleEventConfiguration@ object that specifies the Shutdown event
-- configuration.
layer_lifecycleEventConfiguration :: Lens.Lens' Layer (Prelude.Maybe LifecycleEventConfiguration)
layer_lifecycleEventConfiguration :: Lens' Layer (Maybe LifecycleEventConfiguration)
layer_lifecycleEventConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe LifecycleEventConfiguration
lifecycleEventConfiguration :: Maybe LifecycleEventConfiguration
$sel:lifecycleEventConfiguration:Layer' :: Layer -> Maybe LifecycleEventConfiguration
lifecycleEventConfiguration} -> Maybe LifecycleEventConfiguration
lifecycleEventConfiguration) (\s :: Layer
s@Layer' {} Maybe LifecycleEventConfiguration
a -> Layer
s {$sel:lifecycleEventConfiguration:Layer' :: Maybe LifecycleEventConfiguration
lifecycleEventConfiguration = Maybe LifecycleEventConfiguration
a} :: Layer)

-- | The layer name.
layer_name :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_name :: Lens' Layer (Maybe Text)
layer_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
name :: Maybe Text
$sel:name:Layer' :: Layer -> Maybe Text
name} -> Maybe Text
name) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:name:Layer' :: Maybe Text
name = Maybe Text
a} :: Layer)

-- | An array of @Package@ objects that describe the layer\'s packages.
layer_packages :: Lens.Lens' Layer (Prelude.Maybe [Prelude.Text])
layer_packages :: Lens' Layer (Maybe [Text])
layer_packages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe [Text]
packages :: Maybe [Text]
$sel:packages:Layer' :: Layer -> Maybe [Text]
packages} -> Maybe [Text]
packages) (\s :: Layer
s@Layer' {} Maybe [Text]
a -> Layer
s {$sel:packages:Layer' :: Maybe [Text]
packages = Maybe [Text]
a} :: Layer) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The layer short name.
layer_shortname :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_shortname :: Lens' Layer (Maybe Text)
layer_shortname = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
shortname :: Maybe Text
$sel:shortname:Layer' :: Layer -> Maybe Text
shortname} -> Maybe Text
shortname) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:shortname:Layer' :: Maybe Text
shortname = Maybe Text
a} :: Layer)

-- | The layer stack ID.
layer_stackId :: Lens.Lens' Layer (Prelude.Maybe Prelude.Text)
layer_stackId :: Lens' Layer (Maybe Text)
layer_stackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Text
stackId :: Maybe Text
$sel:stackId:Layer' :: Layer -> Maybe Text
stackId} -> Maybe Text
stackId) (\s :: Layer
s@Layer' {} Maybe Text
a -> Layer
s {$sel:stackId:Layer' :: Maybe Text
stackId = Maybe Text
a} :: Layer)

-- | The layer type.
layer_type :: Lens.Lens' Layer (Prelude.Maybe LayerType)
layer_type :: Lens' Layer (Maybe LayerType)
layer_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe LayerType
type' :: Maybe LayerType
$sel:type':Layer' :: Layer -> Maybe LayerType
type'} -> Maybe LayerType
type') (\s :: Layer
s@Layer' {} Maybe LayerType
a -> Layer
s {$sel:type':Layer' :: Maybe LayerType
type' = Maybe LayerType
a} :: Layer)

-- | Whether the layer uses Amazon EBS-optimized instances.
layer_useEbsOptimizedInstances :: Lens.Lens' Layer (Prelude.Maybe Prelude.Bool)
layer_useEbsOptimizedInstances :: Lens' Layer (Maybe Bool)
layer_useEbsOptimizedInstances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe Bool
useEbsOptimizedInstances :: Maybe Bool
$sel:useEbsOptimizedInstances:Layer' :: Layer -> Maybe Bool
useEbsOptimizedInstances} -> Maybe Bool
useEbsOptimizedInstances) (\s :: Layer
s@Layer' {} Maybe Bool
a -> Layer
s {$sel:useEbsOptimizedInstances:Layer' :: Maybe Bool
useEbsOptimizedInstances = Maybe Bool
a} :: Layer)

-- | A @VolumeConfigurations@ object that describes the layer\'s Amazon EBS
-- volumes.
layer_volumeConfigurations :: Lens.Lens' Layer (Prelude.Maybe [VolumeConfiguration])
layer_volumeConfigurations :: Lens' Layer (Maybe [VolumeConfiguration])
layer_volumeConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Layer' {Maybe [VolumeConfiguration]
volumeConfigurations :: Maybe [VolumeConfiguration]
$sel:volumeConfigurations:Layer' :: Layer -> Maybe [VolumeConfiguration]
volumeConfigurations} -> Maybe [VolumeConfiguration]
volumeConfigurations) (\s :: Layer
s@Layer' {} Maybe [VolumeConfiguration]
a -> Layer
s {$sel:volumeConfigurations:Layer' :: Maybe [VolumeConfiguration]
volumeConfigurations = Maybe [VolumeConfiguration]
a} :: Layer) 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

instance Data.FromJSON Layer where
  parseJSON :: Value -> Parser Layer
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Layer"
      ( \Object
x ->
          Maybe Text
-> Maybe (HashMap LayerAttributesKeys (Maybe Text))
-> Maybe Bool
-> Maybe Bool
-> Maybe CloudWatchLogsConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Recipes
-> Maybe [Text]
-> Maybe Recipes
-> Maybe [Text]
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe LifecycleEventConfiguration
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe LayerType
-> Maybe Bool
-> Maybe [VolumeConfiguration]
-> Layer
Layer'
            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
"Arn")
            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
"Attributes" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"AutoAssignElasticIps")
            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
"AutoAssignPublicIps")
            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
"CloudWatchLogsConfiguration")
            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
"CustomInstanceProfileArn")
            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
"CustomJson")
            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
"CustomRecipes")
            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
"CustomSecurityGroupIds"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"DefaultRecipes")
            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
"DefaultSecurityGroupNames"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            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
"EnableAutoHealing")
            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
"InstallUpdatesOnBoot")
            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
"LayerId")
            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
"LifecycleEventConfiguration")
            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
"Name")
            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
"Packages" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"Shortname")
            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
"StackId")
            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
"Type")
            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
"UseEbsOptimizedInstances")
            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
"VolumeConfigurations"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable Layer where
  hashWithSalt :: Int -> Layer -> Int
hashWithSalt Int
_salt Layer' {Maybe Bool
Maybe [Text]
Maybe [VolumeConfiguration]
Maybe Text
Maybe (HashMap LayerAttributesKeys (Maybe Text))
Maybe CloudWatchLogsConfiguration
Maybe LayerType
Maybe Recipes
Maybe LifecycleEventConfiguration
volumeConfigurations :: Maybe [VolumeConfiguration]
useEbsOptimizedInstances :: Maybe Bool
type' :: Maybe LayerType
stackId :: Maybe Text
shortname :: Maybe Text
packages :: Maybe [Text]
name :: Maybe Text
lifecycleEventConfiguration :: Maybe LifecycleEventConfiguration
layerId :: Maybe Text
installUpdatesOnBoot :: Maybe Bool
enableAutoHealing :: Maybe Bool
defaultSecurityGroupNames :: Maybe [Text]
defaultRecipes :: Maybe Recipes
customSecurityGroupIds :: Maybe [Text]
customRecipes :: Maybe Recipes
customJson :: Maybe Text
customInstanceProfileArn :: Maybe Text
createdAt :: Maybe Text
cloudWatchLogsConfiguration :: Maybe CloudWatchLogsConfiguration
autoAssignPublicIps :: Maybe Bool
autoAssignElasticIps :: Maybe Bool
attributes :: Maybe (HashMap LayerAttributesKeys (Maybe Text))
arn :: Maybe Text
$sel:volumeConfigurations:Layer' :: Layer -> Maybe [VolumeConfiguration]
$sel:useEbsOptimizedInstances:Layer' :: Layer -> Maybe Bool
$sel:type':Layer' :: Layer -> Maybe LayerType
$sel:stackId:Layer' :: Layer -> Maybe Text
$sel:shortname:Layer' :: Layer -> Maybe Text
$sel:packages:Layer' :: Layer -> Maybe [Text]
$sel:name:Layer' :: Layer -> Maybe Text
$sel:lifecycleEventConfiguration:Layer' :: Layer -> Maybe LifecycleEventConfiguration
$sel:layerId:Layer' :: Layer -> Maybe Text
$sel:installUpdatesOnBoot:Layer' :: Layer -> Maybe Bool
$sel:enableAutoHealing:Layer' :: Layer -> Maybe Bool
$sel:defaultSecurityGroupNames:Layer' :: Layer -> Maybe [Text]
$sel:defaultRecipes:Layer' :: Layer -> Maybe Recipes
$sel:customSecurityGroupIds:Layer' :: Layer -> Maybe [Text]
$sel:customRecipes:Layer' :: Layer -> Maybe Recipes
$sel:customJson:Layer' :: Layer -> Maybe Text
$sel:customInstanceProfileArn:Layer' :: Layer -> Maybe Text
$sel:createdAt:Layer' :: Layer -> Maybe Text
$sel:cloudWatchLogsConfiguration:Layer' :: Layer -> Maybe CloudWatchLogsConfiguration
$sel:autoAssignPublicIps:Layer' :: Layer -> Maybe Bool
$sel:autoAssignElasticIps:Layer' :: Layer -> Maybe Bool
$sel:attributes:Layer' :: Layer -> Maybe (HashMap LayerAttributesKeys (Maybe Text))
$sel:arn:Layer' :: Layer -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
autoAssignElasticIps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
autoAssignPublicIps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customInstanceProfileArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customJson
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Recipes
customRecipes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
customSecurityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Recipes
defaultRecipes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
defaultSecurityGroupNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableAutoHealing
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
installUpdatesOnBoot
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
layerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LifecycleEventConfiguration
lifecycleEventConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
packages
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
shortname
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stackId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LayerType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
useEbsOptimizedInstances
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [VolumeConfiguration]
volumeConfigurations

instance Prelude.NFData Layer where
  rnf :: Layer -> ()
rnf Layer' {Maybe Bool
Maybe [Text]
Maybe [VolumeConfiguration]
Maybe Text
Maybe (HashMap LayerAttributesKeys (Maybe Text))
Maybe CloudWatchLogsConfiguration
Maybe LayerType
Maybe Recipes
Maybe LifecycleEventConfiguration
volumeConfigurations :: Maybe [VolumeConfiguration]
useEbsOptimizedInstances :: Maybe Bool
type' :: Maybe LayerType
stackId :: Maybe Text
shortname :: Maybe Text
packages :: Maybe [Text]
name :: Maybe Text
lifecycleEventConfiguration :: Maybe LifecycleEventConfiguration
layerId :: Maybe Text
installUpdatesOnBoot :: Maybe Bool
enableAutoHealing :: Maybe Bool
defaultSecurityGroupNames :: Maybe [Text]
defaultRecipes :: Maybe Recipes
customSecurityGroupIds :: Maybe [Text]
customRecipes :: Maybe Recipes
customJson :: Maybe Text
customInstanceProfileArn :: Maybe Text
createdAt :: Maybe Text
cloudWatchLogsConfiguration :: Maybe CloudWatchLogsConfiguration
autoAssignPublicIps :: Maybe Bool
autoAssignElasticIps :: Maybe Bool
attributes :: Maybe (HashMap LayerAttributesKeys (Maybe Text))
arn :: Maybe Text
$sel:volumeConfigurations:Layer' :: Layer -> Maybe [VolumeConfiguration]
$sel:useEbsOptimizedInstances:Layer' :: Layer -> Maybe Bool
$sel:type':Layer' :: Layer -> Maybe LayerType
$sel:stackId:Layer' :: Layer -> Maybe Text
$sel:shortname:Layer' :: Layer -> Maybe Text
$sel:packages:Layer' :: Layer -> Maybe [Text]
$sel:name:Layer' :: Layer -> Maybe Text
$sel:lifecycleEventConfiguration:Layer' :: Layer -> Maybe LifecycleEventConfiguration
$sel:layerId:Layer' :: Layer -> Maybe Text
$sel:installUpdatesOnBoot:Layer' :: Layer -> Maybe Bool
$sel:enableAutoHealing:Layer' :: Layer -> Maybe Bool
$sel:defaultSecurityGroupNames:Layer' :: Layer -> Maybe [Text]
$sel:defaultRecipes:Layer' :: Layer -> Maybe Recipes
$sel:customSecurityGroupIds:Layer' :: Layer -> Maybe [Text]
$sel:customRecipes:Layer' :: Layer -> Maybe Recipes
$sel:customJson:Layer' :: Layer -> Maybe Text
$sel:customInstanceProfileArn:Layer' :: Layer -> Maybe Text
$sel:createdAt:Layer' :: Layer -> Maybe Text
$sel:cloudWatchLogsConfiguration:Layer' :: Layer -> Maybe CloudWatchLogsConfiguration
$sel:autoAssignPublicIps:Layer' :: Layer -> Maybe Bool
$sel:autoAssignElasticIps:Layer' :: Layer -> Maybe Bool
$sel:attributes:Layer' :: Layer -> Maybe (HashMap LayerAttributesKeys (Maybe Text))
$sel:arn:Layer' :: Layer -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap LayerAttributesKeys (Maybe Text))
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
autoAssignElasticIps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
autoAssignPublicIps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CloudWatchLogsConfiguration
cloudWatchLogsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customInstanceProfileArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
customJson
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Recipes
customRecipes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
customSecurityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Recipes
defaultRecipes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
defaultSecurityGroupNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableAutoHealing
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
installUpdatesOnBoot
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
layerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe LifecycleEventConfiguration
lifecycleEventConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
packages
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
shortname
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stackId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LayerType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
useEbsOptimizedInstances
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [VolumeConfiguration]
volumeConfigurations