{-# 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.MwAA.Types.Environment
-- 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.MwAA.Types.Environment where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MwAA.Types.EnvironmentStatus
import Amazonka.MwAA.Types.LastUpdate
import Amazonka.MwAA.Types.LoggingConfiguration
import Amazonka.MwAA.Types.NetworkConfiguration
import Amazonka.MwAA.Types.WebserverAccessMode
import qualified Amazonka.Prelude as Prelude

-- | Describes an Amazon Managed Workflows for Apache Airflow (MWAA)
-- environment.
--
-- /See:/ 'newEnvironment' smart constructor.
data Environment = Environment'
  { -- | A list of key-value pairs containing the Apache Airflow configuration
    -- options attached to your environment. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-env-variables.html Apache Airflow configuration options>.
    Environment -> Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text (Data.Sensitive Prelude.Text))),
    -- | The Apache Airflow version on your environment. Valid values: @1.10.12@,
    -- @2.0.2@, @2.2.2@, and @2.4.3@.
    Environment -> Maybe Text
airflowVersion :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon MWAA environment.
    Environment -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The day and time the environment was created.
    Environment -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | The relative path to the DAGs folder on your Amazon S3 bucket. For
    -- example, @dags@. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-folder.html Adding or updating DAGs>.
    Environment -> Maybe Text
dagS3Path :: Prelude.Maybe Prelude.Text,
    -- | The environment class type. Valid values: @mw1.small@, @mw1.medium@,
    -- @mw1.large@. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/environment-class.html Amazon MWAA environment class>.
    Environment -> Maybe Text
environmentClass :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the execution role in IAM that allows
    -- MWAA to access Amazon Web Services resources in your environment. For
    -- example, @arn:aws:iam::123456789:role\/my-execution-role@. To learn
    -- more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-create-role.html Amazon MWAA Execution role>.
    Environment -> Maybe Text
executionRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services Key Management Service (KMS) encryption key used
    -- to encrypt the data in your environment.
    Environment -> Maybe Text
kmsKey :: Prelude.Maybe Prelude.Text,
    -- | The status of the last update on the environment.
    Environment -> Maybe LastUpdate
lastUpdate :: Prelude.Maybe LastUpdate,
    -- | The Apache Airflow logs published to CloudWatch Logs.
    Environment -> Maybe LoggingConfiguration
loggingConfiguration :: Prelude.Maybe LoggingConfiguration,
    -- | The maximum number of workers that run in your environment. For example,
    -- @20@.
    Environment -> Maybe Natural
maxWorkers :: Prelude.Maybe Prelude.Natural,
    -- | The minimum number of workers that run in your environment. For example,
    -- @2@.
    Environment -> Maybe Natural
minWorkers :: Prelude.Maybe Prelude.Natural,
    -- | The name of the Amazon MWAA environment. For example,
    -- @MyMWAAEnvironment@.
    Environment -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Describes the VPC networking components used to secure and enable
    -- network traffic between the Amazon Web Services resources for your
    -- environment. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/networking-about.html About networking on Amazon MWAA>.
    Environment -> Maybe NetworkConfiguration
networkConfiguration :: Prelude.Maybe NetworkConfiguration,
    -- | The version of the plugins.zip file on your Amazon S3 bucket. To learn
    -- more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-import-plugins.html Installing custom plugins>.
    Environment -> Maybe Text
pluginsS3ObjectVersion :: Prelude.Maybe Prelude.Text,
    -- | The relative path to the @plugins.zip@ file on your Amazon S3 bucket.
    -- For example, @plugins.zip@. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-import-plugins.html Installing custom plugins>.
    Environment -> Maybe Text
pluginsS3Path :: Prelude.Maybe Prelude.Text,
    -- | The version of the requirements.txt file on your Amazon S3 bucket. To
    -- learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/working-dags-dependencies.html Installing Python dependencies>.
    Environment -> Maybe Text
requirementsS3ObjectVersion :: Prelude.Maybe Prelude.Text,
    -- | The relative path to the @requirements.txt@ file on your Amazon S3
    -- bucket. For example, @requirements.txt@. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/working-dags-dependencies.html Installing Python dependencies>.
    Environment -> Maybe Text
requirementsS3Path :: Prelude.Maybe Prelude.Text,
    -- | The number of Apache Airflow schedulers that run in your Amazon MWAA
    -- environment.
    Environment -> Maybe Int
schedulers :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Resource Name (ARN) for the service-linked role of the
    -- environment. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-slr.html Amazon MWAA Service-linked role>.
    Environment -> Maybe Text
serviceRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon S3 bucket where your DAG
    -- code and supporting files are stored. For example,
    -- @arn:aws:s3:::my-airflow-bucket-unique-name@. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-s3-bucket.html Create an Amazon S3 bucket for Amazon MWAA>.
    Environment -> Maybe Text
sourceBucketArn :: Prelude.Maybe Prelude.Text,
    -- | The status of the Amazon MWAA environment. Valid values:
    --
    -- -   @CREATING@ - Indicates the request to create the environment is in
    --     progress.
    --
    -- -   @CREATE_FAILED@ - Indicates the request to create the environment
    --     failed, and the environment could not be created.
    --
    -- -   @AVAILABLE@ - Indicates the request was successful and the
    --     environment is ready to use.
    --
    -- -   @UPDATING@ - Indicates the request to update the environment is in
    --     progress.
    --
    -- -   @DELETING@ - Indicates the request to delete the environment is in
    --     progress.
    --
    -- -   @DELETED@ - Indicates the request to delete the environment is
    --     complete, and the environment has been deleted.
    --
    -- -   @UNAVAILABLE@ - Indicates the request failed, but the environment
    --     was unable to rollback and is not in a stable state.
    --
    -- -   @UPDATE_FAILED@ - Indicates the request to update the environment
    --     failed, and the environment has rolled back successfully and is
    --     ready to use.
    --
    -- We recommend reviewing our troubleshooting guide for a list of common
    -- errors and their solutions. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/troubleshooting.html Amazon MWAA troubleshooting>.
    Environment -> Maybe EnvironmentStatus
status :: Prelude.Maybe EnvironmentStatus,
    -- | The key-value tag pairs associated to your environment. For example,
    -- @\"Environment\": \"Staging\"@. To learn more, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>.
    Environment -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Apache Airflow /Web server/ access mode. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-networking.html Apache Airflow access modes>.
    Environment -> Maybe WebserverAccessMode
webserverAccessMode :: Prelude.Maybe WebserverAccessMode,
    -- | The Apache Airflow /Web server/ host name for the Amazon MWAA
    -- environment. To learn more, see
    -- <https://docs.aws.amazon.com/mwaa/latest/userguide/access-airflow-ui.html Accessing the Apache Airflow UI>.
    Environment -> Maybe Text
webserverUrl :: Prelude.Maybe Prelude.Text,
    -- | The day and time of the week in Coordinated Universal Time (UTC) 24-hour
    -- standard time that weekly maintenance updates are scheduled. For
    -- example: @TUE:03:30@.
    Environment -> Maybe Text
weeklyMaintenanceWindowStart :: Prelude.Maybe Prelude.Text
  }
  deriving (Environment -> Environment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Environment -> Environment -> Bool
$c/= :: Environment -> Environment -> Bool
== :: Environment -> Environment -> Bool
$c== :: Environment -> Environment -> Bool
Prelude.Eq, Int -> Environment -> ShowS
[Environment] -> ShowS
Environment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Environment] -> ShowS
$cshowList :: [Environment] -> ShowS
show :: Environment -> String
$cshow :: Environment -> String
showsPrec :: Int -> Environment -> ShowS
$cshowsPrec :: Int -> Environment -> ShowS
Prelude.Show, forall x. Rep Environment x -> Environment
forall x. Environment -> Rep Environment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Environment x -> Environment
$cfrom :: forall x. Environment -> Rep Environment x
Prelude.Generic)

-- |
-- Create a value of 'Environment' 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:
--
-- 'airflowConfigurationOptions', 'environment_airflowConfigurationOptions' - A list of key-value pairs containing the Apache Airflow configuration
-- options attached to your environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-env-variables.html Apache Airflow configuration options>.
--
-- 'airflowVersion', 'environment_airflowVersion' - The Apache Airflow version on your environment. Valid values: @1.10.12@,
-- @2.0.2@, @2.2.2@, and @2.4.3@.
--
-- 'arn', 'environment_arn' - The Amazon Resource Name (ARN) of the Amazon MWAA environment.
--
-- 'createdAt', 'environment_createdAt' - The day and time the environment was created.
--
-- 'dagS3Path', 'environment_dagS3Path' - The relative path to the DAGs folder on your Amazon S3 bucket. For
-- example, @dags@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-folder.html Adding or updating DAGs>.
--
-- 'environmentClass', 'environment_environmentClass' - The environment class type. Valid values: @mw1.small@, @mw1.medium@,
-- @mw1.large@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/environment-class.html Amazon MWAA environment class>.
--
-- 'executionRoleArn', 'environment_executionRoleArn' - The Amazon Resource Name (ARN) of the execution role in IAM that allows
-- MWAA to access Amazon Web Services resources in your environment. For
-- example, @arn:aws:iam::123456789:role\/my-execution-role@. To learn
-- more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-create-role.html Amazon MWAA Execution role>.
--
-- 'kmsKey', 'environment_kmsKey' - The Amazon Web Services Key Management Service (KMS) encryption key used
-- to encrypt the data in your environment.
--
-- 'lastUpdate', 'environment_lastUpdate' - The status of the last update on the environment.
--
-- 'loggingConfiguration', 'environment_loggingConfiguration' - The Apache Airflow logs published to CloudWatch Logs.
--
-- 'maxWorkers', 'environment_maxWorkers' - The maximum number of workers that run in your environment. For example,
-- @20@.
--
-- 'minWorkers', 'environment_minWorkers' - The minimum number of workers that run in your environment. For example,
-- @2@.
--
-- 'name', 'environment_name' - The name of the Amazon MWAA environment. For example,
-- @MyMWAAEnvironment@.
--
-- 'networkConfiguration', 'environment_networkConfiguration' - Describes the VPC networking components used to secure and enable
-- network traffic between the Amazon Web Services resources for your
-- environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/networking-about.html About networking on Amazon MWAA>.
--
-- 'pluginsS3ObjectVersion', 'environment_pluginsS3ObjectVersion' - The version of the plugins.zip file on your Amazon S3 bucket. To learn
-- more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-import-plugins.html Installing custom plugins>.
--
-- 'pluginsS3Path', 'environment_pluginsS3Path' - The relative path to the @plugins.zip@ file on your Amazon S3 bucket.
-- For example, @plugins.zip@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-import-plugins.html Installing custom plugins>.
--
-- 'requirementsS3ObjectVersion', 'environment_requirementsS3ObjectVersion' - The version of the requirements.txt file on your Amazon S3 bucket. To
-- learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/working-dags-dependencies.html Installing Python dependencies>.
--
-- 'requirementsS3Path', 'environment_requirementsS3Path' - The relative path to the @requirements.txt@ file on your Amazon S3
-- bucket. For example, @requirements.txt@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/working-dags-dependencies.html Installing Python dependencies>.
--
-- 'schedulers', 'environment_schedulers' - The number of Apache Airflow schedulers that run in your Amazon MWAA
-- environment.
--
-- 'serviceRoleArn', 'environment_serviceRoleArn' - The Amazon Resource Name (ARN) for the service-linked role of the
-- environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-slr.html Amazon MWAA Service-linked role>.
--
-- 'sourceBucketArn', 'environment_sourceBucketArn' - The Amazon Resource Name (ARN) of the Amazon S3 bucket where your DAG
-- code and supporting files are stored. For example,
-- @arn:aws:s3:::my-airflow-bucket-unique-name@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-s3-bucket.html Create an Amazon S3 bucket for Amazon MWAA>.
--
-- 'status', 'environment_status' - The status of the Amazon MWAA environment. Valid values:
--
-- -   @CREATING@ - Indicates the request to create the environment is in
--     progress.
--
-- -   @CREATE_FAILED@ - Indicates the request to create the environment
--     failed, and the environment could not be created.
--
-- -   @AVAILABLE@ - Indicates the request was successful and the
--     environment is ready to use.
--
-- -   @UPDATING@ - Indicates the request to update the environment is in
--     progress.
--
-- -   @DELETING@ - Indicates the request to delete the environment is in
--     progress.
--
-- -   @DELETED@ - Indicates the request to delete the environment is
--     complete, and the environment has been deleted.
--
-- -   @UNAVAILABLE@ - Indicates the request failed, but the environment
--     was unable to rollback and is not in a stable state.
--
-- -   @UPDATE_FAILED@ - Indicates the request to update the environment
--     failed, and the environment has rolled back successfully and is
--     ready to use.
--
-- We recommend reviewing our troubleshooting guide for a list of common
-- errors and their solutions. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/troubleshooting.html Amazon MWAA troubleshooting>.
--
-- 'tags', 'environment_tags' - The key-value tag pairs associated to your environment. For example,
-- @\"Environment\": \"Staging\"@. To learn more, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>.
--
-- 'webserverAccessMode', 'environment_webserverAccessMode' - The Apache Airflow /Web server/ access mode. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-networking.html Apache Airflow access modes>.
--
-- 'webserverUrl', 'environment_webserverUrl' - The Apache Airflow /Web server/ host name for the Amazon MWAA
-- environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/access-airflow-ui.html Accessing the Apache Airflow UI>.
--
-- 'weeklyMaintenanceWindowStart', 'environment_weeklyMaintenanceWindowStart' - The day and time of the week in Coordinated Universal Time (UTC) 24-hour
-- standard time that weekly maintenance updates are scheduled. For
-- example: @TUE:03:30@.
newEnvironment ::
  Environment
newEnvironment :: Environment
newEnvironment =
  Environment'
    { $sel:airflowConfigurationOptions:Environment' :: Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:airflowVersion:Environment' :: Maybe Text
airflowVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:Environment' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:Environment' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:dagS3Path:Environment' :: Maybe Text
dagS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:environmentClass:Environment' :: Maybe Text
environmentClass = forall a. Maybe a
Prelude.Nothing,
      $sel:executionRoleArn:Environment' :: Maybe Text
executionRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKey:Environment' :: Maybe Text
kmsKey = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdate:Environment' :: Maybe LastUpdate
lastUpdate = forall a. Maybe a
Prelude.Nothing,
      $sel:loggingConfiguration:Environment' :: Maybe LoggingConfiguration
loggingConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:maxWorkers:Environment' :: Maybe Natural
maxWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:minWorkers:Environment' :: Maybe Natural
minWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Environment' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:networkConfiguration:Environment' :: Maybe NetworkConfiguration
networkConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:pluginsS3ObjectVersion:Environment' :: Maybe Text
pluginsS3ObjectVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:pluginsS3Path:Environment' :: Maybe Text
pluginsS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:requirementsS3ObjectVersion:Environment' :: Maybe Text
requirementsS3ObjectVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:requirementsS3Path:Environment' :: Maybe Text
requirementsS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:schedulers:Environment' :: Maybe Int
schedulers = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceRoleArn:Environment' :: Maybe Text
serviceRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceBucketArn:Environment' :: Maybe Text
sourceBucketArn = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Environment' :: Maybe EnvironmentStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Environment' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:webserverAccessMode:Environment' :: Maybe WebserverAccessMode
webserverAccessMode = forall a. Maybe a
Prelude.Nothing,
      $sel:webserverUrl:Environment' :: Maybe Text
webserverUrl = forall a. Maybe a
Prelude.Nothing,
      $sel:weeklyMaintenanceWindowStart:Environment' :: Maybe Text
weeklyMaintenanceWindowStart = forall a. Maybe a
Prelude.Nothing
    }

-- | A list of key-value pairs containing the Apache Airflow configuration
-- options attached to your environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-env-variables.html Apache Airflow configuration options>.
environment_airflowConfigurationOptions :: Lens.Lens' Environment (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
environment_airflowConfigurationOptions :: Lens' Environment (Maybe (HashMap Text Text))
environment_airflowConfigurationOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions :: Maybe (Sensitive (HashMap Text (Sensitive Text)))
$sel:airflowConfigurationOptions:Environment' :: Environment -> Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions} -> Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions) (\s :: Environment
s@Environment' {} Maybe (Sensitive (HashMap Text (Sensitive Text)))
a -> Environment
s {$sel:airflowConfigurationOptions:Environment' :: Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions = Maybe (Sensitive (HashMap Text (Sensitive Text)))
a} :: Environment) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The Apache Airflow version on your environment. Valid values: @1.10.12@,
-- @2.0.2@, @2.2.2@, and @2.4.3@.
environment_airflowVersion :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_airflowVersion :: Lens' Environment (Maybe Text)
environment_airflowVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
airflowVersion :: Maybe Text
$sel:airflowVersion:Environment' :: Environment -> Maybe Text
airflowVersion} -> Maybe Text
airflowVersion) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:airflowVersion:Environment' :: Maybe Text
airflowVersion = Maybe Text
a} :: Environment)

-- | The Amazon Resource Name (ARN) of the Amazon MWAA environment.
environment_arn :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_arn :: Lens' Environment (Maybe Text)
environment_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
arn :: Maybe Text
$sel:arn:Environment' :: Environment -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:arn:Environment' :: Maybe Text
arn = Maybe Text
a} :: Environment)

-- | The day and time the environment was created.
environment_createdAt :: Lens.Lens' Environment (Prelude.Maybe Prelude.UTCTime)
environment_createdAt :: Lens' Environment (Maybe UTCTime)
environment_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:Environment' :: Environment -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: Environment
s@Environment' {} Maybe POSIX
a -> Environment
s {$sel:createdAt:Environment' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: Environment) 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 relative path to the DAGs folder on your Amazon S3 bucket. For
-- example, @dags@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-folder.html Adding or updating DAGs>.
environment_dagS3Path :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_dagS3Path :: Lens' Environment (Maybe Text)
environment_dagS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
dagS3Path :: Maybe Text
$sel:dagS3Path:Environment' :: Environment -> Maybe Text
dagS3Path} -> Maybe Text
dagS3Path) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:dagS3Path:Environment' :: Maybe Text
dagS3Path = Maybe Text
a} :: Environment)

-- | The environment class type. Valid values: @mw1.small@, @mw1.medium@,
-- @mw1.large@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/environment-class.html Amazon MWAA environment class>.
environment_environmentClass :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_environmentClass :: Lens' Environment (Maybe Text)
environment_environmentClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
environmentClass :: Maybe Text
$sel:environmentClass:Environment' :: Environment -> Maybe Text
environmentClass} -> Maybe Text
environmentClass) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:environmentClass:Environment' :: Maybe Text
environmentClass = Maybe Text
a} :: Environment)

-- | The Amazon Resource Name (ARN) of the execution role in IAM that allows
-- MWAA to access Amazon Web Services resources in your environment. For
-- example, @arn:aws:iam::123456789:role\/my-execution-role@. To learn
-- more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-create-role.html Amazon MWAA Execution role>.
environment_executionRoleArn :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_executionRoleArn :: Lens' Environment (Maybe Text)
environment_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
executionRoleArn :: Maybe Text
$sel:executionRoleArn:Environment' :: Environment -> Maybe Text
executionRoleArn} -> Maybe Text
executionRoleArn) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:executionRoleArn:Environment' :: Maybe Text
executionRoleArn = Maybe Text
a} :: Environment)

-- | The Amazon Web Services Key Management Service (KMS) encryption key used
-- to encrypt the data in your environment.
environment_kmsKey :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_kmsKey :: Lens' Environment (Maybe Text)
environment_kmsKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
kmsKey :: Maybe Text
$sel:kmsKey:Environment' :: Environment -> Maybe Text
kmsKey} -> Maybe Text
kmsKey) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:kmsKey:Environment' :: Maybe Text
kmsKey = Maybe Text
a} :: Environment)

-- | The status of the last update on the environment.
environment_lastUpdate :: Lens.Lens' Environment (Prelude.Maybe LastUpdate)
environment_lastUpdate :: Lens' Environment (Maybe LastUpdate)
environment_lastUpdate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe LastUpdate
lastUpdate :: Maybe LastUpdate
$sel:lastUpdate:Environment' :: Environment -> Maybe LastUpdate
lastUpdate} -> Maybe LastUpdate
lastUpdate) (\s :: Environment
s@Environment' {} Maybe LastUpdate
a -> Environment
s {$sel:lastUpdate:Environment' :: Maybe LastUpdate
lastUpdate = Maybe LastUpdate
a} :: Environment)

-- | The Apache Airflow logs published to CloudWatch Logs.
environment_loggingConfiguration :: Lens.Lens' Environment (Prelude.Maybe LoggingConfiguration)
environment_loggingConfiguration :: Lens' Environment (Maybe LoggingConfiguration)
environment_loggingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe LoggingConfiguration
loggingConfiguration :: Maybe LoggingConfiguration
$sel:loggingConfiguration:Environment' :: Environment -> Maybe LoggingConfiguration
loggingConfiguration} -> Maybe LoggingConfiguration
loggingConfiguration) (\s :: Environment
s@Environment' {} Maybe LoggingConfiguration
a -> Environment
s {$sel:loggingConfiguration:Environment' :: Maybe LoggingConfiguration
loggingConfiguration = Maybe LoggingConfiguration
a} :: Environment)

-- | The maximum number of workers that run in your environment. For example,
-- @20@.
environment_maxWorkers :: Lens.Lens' Environment (Prelude.Maybe Prelude.Natural)
environment_maxWorkers :: Lens' Environment (Maybe Natural)
environment_maxWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Natural
maxWorkers :: Maybe Natural
$sel:maxWorkers:Environment' :: Environment -> Maybe Natural
maxWorkers} -> Maybe Natural
maxWorkers) (\s :: Environment
s@Environment' {} Maybe Natural
a -> Environment
s {$sel:maxWorkers:Environment' :: Maybe Natural
maxWorkers = Maybe Natural
a} :: Environment)

-- | The minimum number of workers that run in your environment. For example,
-- @2@.
environment_minWorkers :: Lens.Lens' Environment (Prelude.Maybe Prelude.Natural)
environment_minWorkers :: Lens' Environment (Maybe Natural)
environment_minWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Natural
minWorkers :: Maybe Natural
$sel:minWorkers:Environment' :: Environment -> Maybe Natural
minWorkers} -> Maybe Natural
minWorkers) (\s :: Environment
s@Environment' {} Maybe Natural
a -> Environment
s {$sel:minWorkers:Environment' :: Maybe Natural
minWorkers = Maybe Natural
a} :: Environment)

-- | The name of the Amazon MWAA environment. For example,
-- @MyMWAAEnvironment@.
environment_name :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_name :: Lens' Environment (Maybe Text)
environment_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
name :: Maybe Text
$sel:name:Environment' :: Environment -> Maybe Text
name} -> Maybe Text
name) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:name:Environment' :: Maybe Text
name = Maybe Text
a} :: Environment)

-- | Describes the VPC networking components used to secure and enable
-- network traffic between the Amazon Web Services resources for your
-- environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/networking-about.html About networking on Amazon MWAA>.
environment_networkConfiguration :: Lens.Lens' Environment (Prelude.Maybe NetworkConfiguration)
environment_networkConfiguration :: Lens' Environment (Maybe NetworkConfiguration)
environment_networkConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe NetworkConfiguration
networkConfiguration :: Maybe NetworkConfiguration
$sel:networkConfiguration:Environment' :: Environment -> Maybe NetworkConfiguration
networkConfiguration} -> Maybe NetworkConfiguration
networkConfiguration) (\s :: Environment
s@Environment' {} Maybe NetworkConfiguration
a -> Environment
s {$sel:networkConfiguration:Environment' :: Maybe NetworkConfiguration
networkConfiguration = Maybe NetworkConfiguration
a} :: Environment)

-- | The version of the plugins.zip file on your Amazon S3 bucket. To learn
-- more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-import-plugins.html Installing custom plugins>.
environment_pluginsS3ObjectVersion :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_pluginsS3ObjectVersion :: Lens' Environment (Maybe Text)
environment_pluginsS3ObjectVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
pluginsS3ObjectVersion :: Maybe Text
$sel:pluginsS3ObjectVersion:Environment' :: Environment -> Maybe Text
pluginsS3ObjectVersion} -> Maybe Text
pluginsS3ObjectVersion) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:pluginsS3ObjectVersion:Environment' :: Maybe Text
pluginsS3ObjectVersion = Maybe Text
a} :: Environment)

-- | The relative path to the @plugins.zip@ file on your Amazon S3 bucket.
-- For example, @plugins.zip@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-dag-import-plugins.html Installing custom plugins>.
environment_pluginsS3Path :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_pluginsS3Path :: Lens' Environment (Maybe Text)
environment_pluginsS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
pluginsS3Path :: Maybe Text
$sel:pluginsS3Path:Environment' :: Environment -> Maybe Text
pluginsS3Path} -> Maybe Text
pluginsS3Path) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:pluginsS3Path:Environment' :: Maybe Text
pluginsS3Path = Maybe Text
a} :: Environment)

-- | The version of the requirements.txt file on your Amazon S3 bucket. To
-- learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/working-dags-dependencies.html Installing Python dependencies>.
environment_requirementsS3ObjectVersion :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_requirementsS3ObjectVersion :: Lens' Environment (Maybe Text)
environment_requirementsS3ObjectVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
requirementsS3ObjectVersion :: Maybe Text
$sel:requirementsS3ObjectVersion:Environment' :: Environment -> Maybe Text
requirementsS3ObjectVersion} -> Maybe Text
requirementsS3ObjectVersion) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:requirementsS3ObjectVersion:Environment' :: Maybe Text
requirementsS3ObjectVersion = Maybe Text
a} :: Environment)

-- | The relative path to the @requirements.txt@ file on your Amazon S3
-- bucket. For example, @requirements.txt@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/working-dags-dependencies.html Installing Python dependencies>.
environment_requirementsS3Path :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_requirementsS3Path :: Lens' Environment (Maybe Text)
environment_requirementsS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
requirementsS3Path :: Maybe Text
$sel:requirementsS3Path:Environment' :: Environment -> Maybe Text
requirementsS3Path} -> Maybe Text
requirementsS3Path) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:requirementsS3Path:Environment' :: Maybe Text
requirementsS3Path = Maybe Text
a} :: Environment)

-- | The number of Apache Airflow schedulers that run in your Amazon MWAA
-- environment.
environment_schedulers :: Lens.Lens' Environment (Prelude.Maybe Prelude.Int)
environment_schedulers :: Lens' Environment (Maybe Int)
environment_schedulers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Int
schedulers :: Maybe Int
$sel:schedulers:Environment' :: Environment -> Maybe Int
schedulers} -> Maybe Int
schedulers) (\s :: Environment
s@Environment' {} Maybe Int
a -> Environment
s {$sel:schedulers:Environment' :: Maybe Int
schedulers = Maybe Int
a} :: Environment)

-- | The Amazon Resource Name (ARN) for the service-linked role of the
-- environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-slr.html Amazon MWAA Service-linked role>.
environment_serviceRoleArn :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_serviceRoleArn :: Lens' Environment (Maybe Text)
environment_serviceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
serviceRoleArn :: Maybe Text
$sel:serviceRoleArn:Environment' :: Environment -> Maybe Text
serviceRoleArn} -> Maybe Text
serviceRoleArn) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:serviceRoleArn:Environment' :: Maybe Text
serviceRoleArn = Maybe Text
a} :: Environment)

-- | The Amazon Resource Name (ARN) of the Amazon S3 bucket where your DAG
-- code and supporting files are stored. For example,
-- @arn:aws:s3:::my-airflow-bucket-unique-name@. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/mwaa-s3-bucket.html Create an Amazon S3 bucket for Amazon MWAA>.
environment_sourceBucketArn :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_sourceBucketArn :: Lens' Environment (Maybe Text)
environment_sourceBucketArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
sourceBucketArn :: Maybe Text
$sel:sourceBucketArn:Environment' :: Environment -> Maybe Text
sourceBucketArn} -> Maybe Text
sourceBucketArn) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:sourceBucketArn:Environment' :: Maybe Text
sourceBucketArn = Maybe Text
a} :: Environment)

-- | The status of the Amazon MWAA environment. Valid values:
--
-- -   @CREATING@ - Indicates the request to create the environment is in
--     progress.
--
-- -   @CREATE_FAILED@ - Indicates the request to create the environment
--     failed, and the environment could not be created.
--
-- -   @AVAILABLE@ - Indicates the request was successful and the
--     environment is ready to use.
--
-- -   @UPDATING@ - Indicates the request to update the environment is in
--     progress.
--
-- -   @DELETING@ - Indicates the request to delete the environment is in
--     progress.
--
-- -   @DELETED@ - Indicates the request to delete the environment is
--     complete, and the environment has been deleted.
--
-- -   @UNAVAILABLE@ - Indicates the request failed, but the environment
--     was unable to rollback and is not in a stable state.
--
-- -   @UPDATE_FAILED@ - Indicates the request to update the environment
--     failed, and the environment has rolled back successfully and is
--     ready to use.
--
-- We recommend reviewing our troubleshooting guide for a list of common
-- errors and their solutions. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/troubleshooting.html Amazon MWAA troubleshooting>.
environment_status :: Lens.Lens' Environment (Prelude.Maybe EnvironmentStatus)
environment_status :: Lens' Environment (Maybe EnvironmentStatus)
environment_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe EnvironmentStatus
status :: Maybe EnvironmentStatus
$sel:status:Environment' :: Environment -> Maybe EnvironmentStatus
status} -> Maybe EnvironmentStatus
status) (\s :: Environment
s@Environment' {} Maybe EnvironmentStatus
a -> Environment
s {$sel:status:Environment' :: Maybe EnvironmentStatus
status = Maybe EnvironmentStatus
a} :: Environment)

-- | The key-value tag pairs associated to your environment. For example,
-- @\"Environment\": \"Staging\"@. To learn more, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>.
environment_tags :: Lens.Lens' Environment (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
environment_tags :: Lens' Environment (Maybe (HashMap Text Text))
environment_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:Environment' :: Environment -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: Environment
s@Environment' {} Maybe (HashMap Text Text)
a -> Environment
s {$sel:tags:Environment' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: Environment) 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 Apache Airflow /Web server/ access mode. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/configuring-networking.html Apache Airflow access modes>.
environment_webserverAccessMode :: Lens.Lens' Environment (Prelude.Maybe WebserverAccessMode)
environment_webserverAccessMode :: Lens' Environment (Maybe WebserverAccessMode)
environment_webserverAccessMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe WebserverAccessMode
webserverAccessMode :: Maybe WebserverAccessMode
$sel:webserverAccessMode:Environment' :: Environment -> Maybe WebserverAccessMode
webserverAccessMode} -> Maybe WebserverAccessMode
webserverAccessMode) (\s :: Environment
s@Environment' {} Maybe WebserverAccessMode
a -> Environment
s {$sel:webserverAccessMode:Environment' :: Maybe WebserverAccessMode
webserverAccessMode = Maybe WebserverAccessMode
a} :: Environment)

-- | The Apache Airflow /Web server/ host name for the Amazon MWAA
-- environment. To learn more, see
-- <https://docs.aws.amazon.com/mwaa/latest/userguide/access-airflow-ui.html Accessing the Apache Airflow UI>.
environment_webserverUrl :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_webserverUrl :: Lens' Environment (Maybe Text)
environment_webserverUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
webserverUrl :: Maybe Text
$sel:webserverUrl:Environment' :: Environment -> Maybe Text
webserverUrl} -> Maybe Text
webserverUrl) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:webserverUrl:Environment' :: Maybe Text
webserverUrl = Maybe Text
a} :: Environment)

-- | The day and time of the week in Coordinated Universal Time (UTC) 24-hour
-- standard time that weekly maintenance updates are scheduled. For
-- example: @TUE:03:30@.
environment_weeklyMaintenanceWindowStart :: Lens.Lens' Environment (Prelude.Maybe Prelude.Text)
environment_weeklyMaintenanceWindowStart :: Lens' Environment (Maybe Text)
environment_weeklyMaintenanceWindowStart = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Environment' {Maybe Text
weeklyMaintenanceWindowStart :: Maybe Text
$sel:weeklyMaintenanceWindowStart:Environment' :: Environment -> Maybe Text
weeklyMaintenanceWindowStart} -> Maybe Text
weeklyMaintenanceWindowStart) (\s :: Environment
s@Environment' {} Maybe Text
a -> Environment
s {$sel:weeklyMaintenanceWindowStart:Environment' :: Maybe Text
weeklyMaintenanceWindowStart = Maybe Text
a} :: Environment)

instance Data.FromJSON Environment where
  parseJSON :: Value -> Parser Environment
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Environment"
      ( \Object
x ->
          Maybe (Sensitive (HashMap Text (Sensitive Text)))
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LastUpdate
-> Maybe LoggingConfiguration
-> Maybe Natural
-> Maybe Natural
-> Maybe Text
-> Maybe NetworkConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe EnvironmentStatus
-> Maybe (HashMap Text Text)
-> Maybe WebserverAccessMode
-> Maybe Text
-> Maybe Text
-> Environment
Environment'
            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
"AirflowConfigurationOptions"
                            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
"AirflowVersion")
            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
"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
"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
"DagS3Path")
            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
"EnvironmentClass")
            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
"ExecutionRoleArn")
            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
"KmsKey")
            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
"LastUpdate")
            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
"LoggingConfiguration")
            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
"MaxWorkers")
            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
"MinWorkers")
            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
"NetworkConfiguration")
            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
"PluginsS3ObjectVersion")
            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
"PluginsS3Path")
            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
"RequirementsS3ObjectVersion")
            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
"RequirementsS3Path")
            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
"Schedulers")
            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
"ServiceRoleArn")
            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
"SourceBucketArn")
            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")
            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
"Tags" 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
"WebserverAccessMode")
            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
"WebserverUrl")
            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
"WeeklyMaintenanceWindowStart")
      )

instance Prelude.Hashable Environment where
  hashWithSalt :: Int -> Environment -> Int
hashWithSalt Int
_salt Environment' {Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text (Sensitive Text)))
Maybe POSIX
Maybe EnvironmentStatus
Maybe LoggingConfiguration
Maybe NetworkConfiguration
Maybe LastUpdate
Maybe WebserverAccessMode
weeklyMaintenanceWindowStart :: Maybe Text
webserverUrl :: Maybe Text
webserverAccessMode :: Maybe WebserverAccessMode
tags :: Maybe (HashMap Text Text)
status :: Maybe EnvironmentStatus
sourceBucketArn :: Maybe Text
serviceRoleArn :: Maybe Text
schedulers :: Maybe Int
requirementsS3Path :: Maybe Text
requirementsS3ObjectVersion :: Maybe Text
pluginsS3Path :: Maybe Text
pluginsS3ObjectVersion :: Maybe Text
networkConfiguration :: Maybe NetworkConfiguration
name :: Maybe Text
minWorkers :: Maybe Natural
maxWorkers :: Maybe Natural
loggingConfiguration :: Maybe LoggingConfiguration
lastUpdate :: Maybe LastUpdate
kmsKey :: Maybe Text
executionRoleArn :: Maybe Text
environmentClass :: Maybe Text
dagS3Path :: Maybe Text
createdAt :: Maybe POSIX
arn :: Maybe Text
airflowVersion :: Maybe Text
airflowConfigurationOptions :: Maybe (Sensitive (HashMap Text (Sensitive Text)))
$sel:weeklyMaintenanceWindowStart:Environment' :: Environment -> Maybe Text
$sel:webserverUrl:Environment' :: Environment -> Maybe Text
$sel:webserverAccessMode:Environment' :: Environment -> Maybe WebserverAccessMode
$sel:tags:Environment' :: Environment -> Maybe (HashMap Text Text)
$sel:status:Environment' :: Environment -> Maybe EnvironmentStatus
$sel:sourceBucketArn:Environment' :: Environment -> Maybe Text
$sel:serviceRoleArn:Environment' :: Environment -> Maybe Text
$sel:schedulers:Environment' :: Environment -> Maybe Int
$sel:requirementsS3Path:Environment' :: Environment -> Maybe Text
$sel:requirementsS3ObjectVersion:Environment' :: Environment -> Maybe Text
$sel:pluginsS3Path:Environment' :: Environment -> Maybe Text
$sel:pluginsS3ObjectVersion:Environment' :: Environment -> Maybe Text
$sel:networkConfiguration:Environment' :: Environment -> Maybe NetworkConfiguration
$sel:name:Environment' :: Environment -> Maybe Text
$sel:minWorkers:Environment' :: Environment -> Maybe Natural
$sel:maxWorkers:Environment' :: Environment -> Maybe Natural
$sel:loggingConfiguration:Environment' :: Environment -> Maybe LoggingConfiguration
$sel:lastUpdate:Environment' :: Environment -> Maybe LastUpdate
$sel:kmsKey:Environment' :: Environment -> Maybe Text
$sel:executionRoleArn:Environment' :: Environment -> Maybe Text
$sel:environmentClass:Environment' :: Environment -> Maybe Text
$sel:dagS3Path:Environment' :: Environment -> Maybe Text
$sel:createdAt:Environment' :: Environment -> Maybe POSIX
$sel:arn:Environment' :: Environment -> Maybe Text
$sel:airflowVersion:Environment' :: Environment -> Maybe Text
$sel:airflowConfigurationOptions:Environment' :: Environment -> Maybe (Sensitive (HashMap Text (Sensitive Text)))
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
airflowVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dagS3Path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
environmentClass
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
executionRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LastUpdate
lastUpdate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LoggingConfiguration
loggingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxWorkers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
minWorkers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkConfiguration
networkConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pluginsS3ObjectVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pluginsS3Path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
requirementsS3ObjectVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
requirementsS3Path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
schedulers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceBucketArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EnvironmentStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WebserverAccessMode
webserverAccessMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
webserverUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
weeklyMaintenanceWindowStart

instance Prelude.NFData Environment where
  rnf :: Environment -> ()
rnf Environment' {Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text (Sensitive Text)))
Maybe POSIX
Maybe EnvironmentStatus
Maybe LoggingConfiguration
Maybe NetworkConfiguration
Maybe LastUpdate
Maybe WebserverAccessMode
weeklyMaintenanceWindowStart :: Maybe Text
webserverUrl :: Maybe Text
webserverAccessMode :: Maybe WebserverAccessMode
tags :: Maybe (HashMap Text Text)
status :: Maybe EnvironmentStatus
sourceBucketArn :: Maybe Text
serviceRoleArn :: Maybe Text
schedulers :: Maybe Int
requirementsS3Path :: Maybe Text
requirementsS3ObjectVersion :: Maybe Text
pluginsS3Path :: Maybe Text
pluginsS3ObjectVersion :: Maybe Text
networkConfiguration :: Maybe NetworkConfiguration
name :: Maybe Text
minWorkers :: Maybe Natural
maxWorkers :: Maybe Natural
loggingConfiguration :: Maybe LoggingConfiguration
lastUpdate :: Maybe LastUpdate
kmsKey :: Maybe Text
executionRoleArn :: Maybe Text
environmentClass :: Maybe Text
dagS3Path :: Maybe Text
createdAt :: Maybe POSIX
arn :: Maybe Text
airflowVersion :: Maybe Text
airflowConfigurationOptions :: Maybe (Sensitive (HashMap Text (Sensitive Text)))
$sel:weeklyMaintenanceWindowStart:Environment' :: Environment -> Maybe Text
$sel:webserverUrl:Environment' :: Environment -> Maybe Text
$sel:webserverAccessMode:Environment' :: Environment -> Maybe WebserverAccessMode
$sel:tags:Environment' :: Environment -> Maybe (HashMap Text Text)
$sel:status:Environment' :: Environment -> Maybe EnvironmentStatus
$sel:sourceBucketArn:Environment' :: Environment -> Maybe Text
$sel:serviceRoleArn:Environment' :: Environment -> Maybe Text
$sel:schedulers:Environment' :: Environment -> Maybe Int
$sel:requirementsS3Path:Environment' :: Environment -> Maybe Text
$sel:requirementsS3ObjectVersion:Environment' :: Environment -> Maybe Text
$sel:pluginsS3Path:Environment' :: Environment -> Maybe Text
$sel:pluginsS3ObjectVersion:Environment' :: Environment -> Maybe Text
$sel:networkConfiguration:Environment' :: Environment -> Maybe NetworkConfiguration
$sel:name:Environment' :: Environment -> Maybe Text
$sel:minWorkers:Environment' :: Environment -> Maybe Natural
$sel:maxWorkers:Environment' :: Environment -> Maybe Natural
$sel:loggingConfiguration:Environment' :: Environment -> Maybe LoggingConfiguration
$sel:lastUpdate:Environment' :: Environment -> Maybe LastUpdate
$sel:kmsKey:Environment' :: Environment -> Maybe Text
$sel:executionRoleArn:Environment' :: Environment -> Maybe Text
$sel:environmentClass:Environment' :: Environment -> Maybe Text
$sel:dagS3Path:Environment' :: Environment -> Maybe Text
$sel:createdAt:Environment' :: Environment -> Maybe POSIX
$sel:arn:Environment' :: Environment -> Maybe Text
$sel:airflowVersion:Environment' :: Environment -> Maybe Text
$sel:airflowConfigurationOptions:Environment' :: Environment -> Maybe (Sensitive (HashMap Text (Sensitive Text)))
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text (Sensitive Text)))
airflowConfigurationOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
airflowVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dagS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
environmentClass
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LastUpdate
lastUpdate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LoggingConfiguration
loggingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxWorkers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
minWorkers
      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 NetworkConfiguration
networkConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pluginsS3ObjectVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pluginsS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
requirementsS3ObjectVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requirementsS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
schedulers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sourceBucketArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EnvironmentStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe WebserverAccessMode
webserverAccessMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
webserverUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
weeklyMaintenanceWindowStart