{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Glue.CreateDevEndpoint
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new development endpoint.
module Amazonka.Glue.CreateDevEndpoint
  ( -- * Creating a Request
    CreateDevEndpoint (..),
    newCreateDevEndpoint,

    -- * Request Lenses
    createDevEndpoint_arguments,
    createDevEndpoint_extraJarsS3Path,
    createDevEndpoint_extraPythonLibsS3Path,
    createDevEndpoint_glueVersion,
    createDevEndpoint_numberOfNodes,
    createDevEndpoint_numberOfWorkers,
    createDevEndpoint_publicKey,
    createDevEndpoint_publicKeys,
    createDevEndpoint_securityConfiguration,
    createDevEndpoint_securityGroupIds,
    createDevEndpoint_subnetId,
    createDevEndpoint_tags,
    createDevEndpoint_workerType,
    createDevEndpoint_endpointName,
    createDevEndpoint_roleArn,

    -- * Destructuring the Response
    CreateDevEndpointResponse (..),
    newCreateDevEndpointResponse,

    -- * Response Lenses
    createDevEndpointResponse_arguments,
    createDevEndpointResponse_availabilityZone,
    createDevEndpointResponse_createdTimestamp,
    createDevEndpointResponse_endpointName,
    createDevEndpointResponse_extraJarsS3Path,
    createDevEndpointResponse_extraPythonLibsS3Path,
    createDevEndpointResponse_failureReason,
    createDevEndpointResponse_glueVersion,
    createDevEndpointResponse_numberOfNodes,
    createDevEndpointResponse_numberOfWorkers,
    createDevEndpointResponse_roleArn,
    createDevEndpointResponse_securityConfiguration,
    createDevEndpointResponse_securityGroupIds,
    createDevEndpointResponse_status,
    createDevEndpointResponse_subnetId,
    createDevEndpointResponse_vpcId,
    createDevEndpointResponse_workerType,
    createDevEndpointResponse_yarnEndpointAddress,
    createDevEndpointResponse_zeppelinRemoteSparkInterpreterPort,
    createDevEndpointResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateDevEndpoint' smart constructor.
data CreateDevEndpoint = CreateDevEndpoint'
  { -- | A map of arguments used to configure the @DevEndpoint@.
    CreateDevEndpoint -> Maybe (HashMap Text Text)
arguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The path to one or more Java @.jar@ files in an S3 bucket that should be
    -- loaded in your @DevEndpoint@.
    CreateDevEndpoint -> Maybe Text
extraJarsS3Path :: Prelude.Maybe Prelude.Text,
    -- | The paths to one or more Python libraries in an Amazon S3 bucket that
    -- should be loaded in your @DevEndpoint@. Multiple values must be complete
    -- paths separated by a comma.
    --
    -- You can only use pure Python libraries with a @DevEndpoint@. Libraries
    -- that rely on C extensions, such as the
    -- <http://pandas.pydata.org/ pandas> Python data analysis library, are not
    -- yet supported.
    CreateDevEndpoint -> Maybe Text
extraPythonLibsS3Path :: Prelude.Maybe Prelude.Text,
    -- | Glue version determines the versions of Apache Spark and Python that
    -- Glue supports. The Python version indicates the version supported for
    -- running your ETL scripts on development endpoints.
    --
    -- For more information about the available Glue versions and corresponding
    -- Spark and Python versions, see
    -- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
    -- in the developer guide.
    --
    -- Development endpoints that are created without specifying a Glue version
    -- default to Glue 0.9.
    --
    -- You can specify a version of Python support for development endpoints by
    -- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
    -- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
    -- defaults to Python 2.
    CreateDevEndpoint -> Maybe Text
glueVersion :: Prelude.Maybe Prelude.Text,
    -- | The number of Glue Data Processing Units (DPUs) to allocate to this
    -- @DevEndpoint@.
    CreateDevEndpoint -> Maybe Int
numberOfNodes :: Prelude.Maybe Prelude.Int,
    -- | The number of workers of a defined @workerType@ that are allocated to
    -- the development endpoint.
    --
    -- The maximum number of workers you can define are 299 for @G.1X@, and 149
    -- for @G.2X@.
    CreateDevEndpoint -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | The public key to be used by this @DevEndpoint@ for authentication. This
    -- attribute is provided for backward compatibility because the recommended
    -- attribute to use is public keys.
    CreateDevEndpoint -> Maybe Text
publicKey :: Prelude.Maybe Prelude.Text,
    -- | A list of public keys to be used by the development endpoints for
    -- authentication. The use of this attribute is preferred over a single
    -- public key because the public keys allow you to have a different private
    -- key per client.
    --
    -- If you previously created an endpoint with a public key, you must remove
    -- that key to be able to set a list of public keys. Call the
    -- @UpdateDevEndpoint@ API with the public key content in the
    -- @deletePublicKeys@ attribute, and the list of new keys in the
    -- @addPublicKeys@ attribute.
    CreateDevEndpoint -> Maybe [Text]
publicKeys :: Prelude.Maybe [Prelude.Text],
    -- | The name of the @SecurityConfiguration@ structure to be used with this
    -- @DevEndpoint@.
    CreateDevEndpoint -> Maybe Text
securityConfiguration :: Prelude.Maybe Prelude.Text,
    -- | Security group IDs for the security groups to be used by the new
    -- @DevEndpoint@.
    CreateDevEndpoint -> Maybe [Text]
securityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The subnet ID for the new @DevEndpoint@ to use.
    CreateDevEndpoint -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | The tags to use with this DevEndpoint. You may use tags to limit access
    -- to the DevEndpoint. For more information about tags in Glue, see
    -- <https://docs.aws.amazon.com/glue/latest/dg/monitor-tags.html Amazon Web Services Tags in Glue>
    -- in the developer guide.
    CreateDevEndpoint -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The type of predefined worker that is allocated to the development
    -- endpoint. Accepts a value of Standard, G.1X, or G.2X.
    --
    -- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
    --     of memory and a 50GB disk, and 2 executors per worker.
    --
    -- -   For the @G.1X@ worker type, each worker maps to 1 DPU (4 vCPU, 16 GB
    --     of memory, 64 GB disk), and provides 1 executor per worker. We
    --     recommend this worker type for memory-intensive jobs.
    --
    -- -   For the @G.2X@ worker type, each worker maps to 2 DPU (8 vCPU, 32 GB
    --     of memory, 128 GB disk), and provides 1 executor per worker. We
    --     recommend this worker type for memory-intensive jobs.
    --
    -- Known issue: when a development endpoint is created with the @G.2X@
    -- @WorkerType@ configuration, the Spark drivers for the development
    -- endpoint will run on 4 vCPU, 16 GB of memory, and a 64 GB disk.
    CreateDevEndpoint -> Maybe WorkerType
workerType :: Prelude.Maybe WorkerType,
    -- | The name to be assigned to the new @DevEndpoint@.
    CreateDevEndpoint -> Text
endpointName :: Prelude.Text,
    -- | The IAM role for the @DevEndpoint@.
    CreateDevEndpoint -> Text
roleArn :: Prelude.Text
  }
  deriving (CreateDevEndpoint -> CreateDevEndpoint -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDevEndpoint -> CreateDevEndpoint -> Bool
$c/= :: CreateDevEndpoint -> CreateDevEndpoint -> Bool
== :: CreateDevEndpoint -> CreateDevEndpoint -> Bool
$c== :: CreateDevEndpoint -> CreateDevEndpoint -> Bool
Prelude.Eq, ReadPrec [CreateDevEndpoint]
ReadPrec CreateDevEndpoint
Int -> ReadS CreateDevEndpoint
ReadS [CreateDevEndpoint]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDevEndpoint]
$creadListPrec :: ReadPrec [CreateDevEndpoint]
readPrec :: ReadPrec CreateDevEndpoint
$creadPrec :: ReadPrec CreateDevEndpoint
readList :: ReadS [CreateDevEndpoint]
$creadList :: ReadS [CreateDevEndpoint]
readsPrec :: Int -> ReadS CreateDevEndpoint
$creadsPrec :: Int -> ReadS CreateDevEndpoint
Prelude.Read, Int -> CreateDevEndpoint -> ShowS
[CreateDevEndpoint] -> ShowS
CreateDevEndpoint -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDevEndpoint] -> ShowS
$cshowList :: [CreateDevEndpoint] -> ShowS
show :: CreateDevEndpoint -> String
$cshow :: CreateDevEndpoint -> String
showsPrec :: Int -> CreateDevEndpoint -> ShowS
$cshowsPrec :: Int -> CreateDevEndpoint -> ShowS
Prelude.Show, forall x. Rep CreateDevEndpoint x -> CreateDevEndpoint
forall x. CreateDevEndpoint -> Rep CreateDevEndpoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDevEndpoint x -> CreateDevEndpoint
$cfrom :: forall x. CreateDevEndpoint -> Rep CreateDevEndpoint x
Prelude.Generic)

-- |
-- Create a value of 'CreateDevEndpoint' 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:
--
-- 'arguments', 'createDevEndpoint_arguments' - A map of arguments used to configure the @DevEndpoint@.
--
-- 'extraJarsS3Path', 'createDevEndpoint_extraJarsS3Path' - The path to one or more Java @.jar@ files in an S3 bucket that should be
-- loaded in your @DevEndpoint@.
--
-- 'extraPythonLibsS3Path', 'createDevEndpoint_extraPythonLibsS3Path' - The paths to one or more Python libraries in an Amazon S3 bucket that
-- should be loaded in your @DevEndpoint@. Multiple values must be complete
-- paths separated by a comma.
--
-- You can only use pure Python libraries with a @DevEndpoint@. Libraries
-- that rely on C extensions, such as the
-- <http://pandas.pydata.org/ pandas> Python data analysis library, are not
-- yet supported.
--
-- 'glueVersion', 'createDevEndpoint_glueVersion' - Glue version determines the versions of Apache Spark and Python that
-- Glue supports. The Python version indicates the version supported for
-- running your ETL scripts on development endpoints.
--
-- For more information about the available Glue versions and corresponding
-- Spark and Python versions, see
-- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
-- in the developer guide.
--
-- Development endpoints that are created without specifying a Glue version
-- default to Glue 0.9.
--
-- You can specify a version of Python support for development endpoints by
-- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
-- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
-- defaults to Python 2.
--
-- 'numberOfNodes', 'createDevEndpoint_numberOfNodes' - The number of Glue Data Processing Units (DPUs) to allocate to this
-- @DevEndpoint@.
--
-- 'numberOfWorkers', 'createDevEndpoint_numberOfWorkers' - The number of workers of a defined @workerType@ that are allocated to
-- the development endpoint.
--
-- The maximum number of workers you can define are 299 for @G.1X@, and 149
-- for @G.2X@.
--
-- 'publicKey', 'createDevEndpoint_publicKey' - The public key to be used by this @DevEndpoint@ for authentication. This
-- attribute is provided for backward compatibility because the recommended
-- attribute to use is public keys.
--
-- 'publicKeys', 'createDevEndpoint_publicKeys' - A list of public keys to be used by the development endpoints for
-- authentication. The use of this attribute is preferred over a single
-- public key because the public keys allow you to have a different private
-- key per client.
--
-- If you previously created an endpoint with a public key, you must remove
-- that key to be able to set a list of public keys. Call the
-- @UpdateDevEndpoint@ API with the public key content in the
-- @deletePublicKeys@ attribute, and the list of new keys in the
-- @addPublicKeys@ attribute.
--
-- 'securityConfiguration', 'createDevEndpoint_securityConfiguration' - The name of the @SecurityConfiguration@ structure to be used with this
-- @DevEndpoint@.
--
-- 'securityGroupIds', 'createDevEndpoint_securityGroupIds' - Security group IDs for the security groups to be used by the new
-- @DevEndpoint@.
--
-- 'subnetId', 'createDevEndpoint_subnetId' - The subnet ID for the new @DevEndpoint@ to use.
--
-- 'tags', 'createDevEndpoint_tags' - The tags to use with this DevEndpoint. You may use tags to limit access
-- to the DevEndpoint. For more information about tags in Glue, see
-- <https://docs.aws.amazon.com/glue/latest/dg/monitor-tags.html Amazon Web Services Tags in Glue>
-- in the developer guide.
--
-- 'workerType', 'createDevEndpoint_workerType' - The type of predefined worker that is allocated to the development
-- endpoint. Accepts a value of Standard, G.1X, or G.2X.
--
-- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
--     of memory and a 50GB disk, and 2 executors per worker.
--
-- -   For the @G.1X@ worker type, each worker maps to 1 DPU (4 vCPU, 16 GB
--     of memory, 64 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- -   For the @G.2X@ worker type, each worker maps to 2 DPU (8 vCPU, 32 GB
--     of memory, 128 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- Known issue: when a development endpoint is created with the @G.2X@
-- @WorkerType@ configuration, the Spark drivers for the development
-- endpoint will run on 4 vCPU, 16 GB of memory, and a 64 GB disk.
--
-- 'endpointName', 'createDevEndpoint_endpointName' - The name to be assigned to the new @DevEndpoint@.
--
-- 'roleArn', 'createDevEndpoint_roleArn' - The IAM role for the @DevEndpoint@.
newCreateDevEndpoint ::
  -- | 'endpointName'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  CreateDevEndpoint
newCreateDevEndpoint :: Text -> Text -> CreateDevEndpoint
newCreateDevEndpoint Text
pEndpointName_ Text
pRoleArn_ =
  CreateDevEndpoint'
    { $sel:arguments:CreateDevEndpoint' :: Maybe (HashMap Text Text)
arguments = forall a. Maybe a
Prelude.Nothing,
      $sel:extraJarsS3Path:CreateDevEndpoint' :: Maybe Text
extraJarsS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:extraPythonLibsS3Path:CreateDevEndpoint' :: Maybe Text
extraPythonLibsS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:glueVersion:CreateDevEndpoint' :: Maybe Text
glueVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfNodes:CreateDevEndpoint' :: Maybe Int
numberOfNodes = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfWorkers:CreateDevEndpoint' :: Maybe Int
numberOfWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:publicKey:CreateDevEndpoint' :: Maybe Text
publicKey = forall a. Maybe a
Prelude.Nothing,
      $sel:publicKeys:CreateDevEndpoint' :: Maybe [Text]
publicKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:securityConfiguration:CreateDevEndpoint' :: Maybe Text
securityConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupIds:CreateDevEndpoint' :: Maybe [Text]
securityGroupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:CreateDevEndpoint' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateDevEndpoint' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:workerType:CreateDevEndpoint' :: Maybe WorkerType
workerType = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointName:CreateDevEndpoint' :: Text
endpointName = Text
pEndpointName_,
      $sel:roleArn:CreateDevEndpoint' :: Text
roleArn = Text
pRoleArn_
    }

-- | A map of arguments used to configure the @DevEndpoint@.
createDevEndpoint_arguments :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createDevEndpoint_arguments :: Lens' CreateDevEndpoint (Maybe (HashMap Text Text))
createDevEndpoint_arguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe (HashMap Text Text)
arguments :: Maybe (HashMap Text Text)
$sel:arguments:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
arguments} -> Maybe (HashMap Text Text)
arguments) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe (HashMap Text Text)
a -> CreateDevEndpoint
s {$sel:arguments:CreateDevEndpoint' :: Maybe (HashMap Text Text)
arguments = Maybe (HashMap Text Text)
a} :: CreateDevEndpoint) 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 path to one or more Java @.jar@ files in an S3 bucket that should be
-- loaded in your @DevEndpoint@.
createDevEndpoint_extraJarsS3Path :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Text)
createDevEndpoint_extraJarsS3Path :: Lens' CreateDevEndpoint (Maybe Text)
createDevEndpoint_extraJarsS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Text
extraJarsS3Path :: Maybe Text
$sel:extraJarsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
extraJarsS3Path} -> Maybe Text
extraJarsS3Path) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Text
a -> CreateDevEndpoint
s {$sel:extraJarsS3Path:CreateDevEndpoint' :: Maybe Text
extraJarsS3Path = Maybe Text
a} :: CreateDevEndpoint)

-- | The paths to one or more Python libraries in an Amazon S3 bucket that
-- should be loaded in your @DevEndpoint@. Multiple values must be complete
-- paths separated by a comma.
--
-- You can only use pure Python libraries with a @DevEndpoint@. Libraries
-- that rely on C extensions, such as the
-- <http://pandas.pydata.org/ pandas> Python data analysis library, are not
-- yet supported.
createDevEndpoint_extraPythonLibsS3Path :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Text)
createDevEndpoint_extraPythonLibsS3Path :: Lens' CreateDevEndpoint (Maybe Text)
createDevEndpoint_extraPythonLibsS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Text
extraPythonLibsS3Path :: Maybe Text
$sel:extraPythonLibsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
extraPythonLibsS3Path} -> Maybe Text
extraPythonLibsS3Path) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Text
a -> CreateDevEndpoint
s {$sel:extraPythonLibsS3Path:CreateDevEndpoint' :: Maybe Text
extraPythonLibsS3Path = Maybe Text
a} :: CreateDevEndpoint)

-- | Glue version determines the versions of Apache Spark and Python that
-- Glue supports. The Python version indicates the version supported for
-- running your ETL scripts on development endpoints.
--
-- For more information about the available Glue versions and corresponding
-- Spark and Python versions, see
-- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
-- in the developer guide.
--
-- Development endpoints that are created without specifying a Glue version
-- default to Glue 0.9.
--
-- You can specify a version of Python support for development endpoints by
-- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
-- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
-- defaults to Python 2.
createDevEndpoint_glueVersion :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Text)
createDevEndpoint_glueVersion :: Lens' CreateDevEndpoint (Maybe Text)
createDevEndpoint_glueVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Text
glueVersion :: Maybe Text
$sel:glueVersion:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
glueVersion} -> Maybe Text
glueVersion) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Text
a -> CreateDevEndpoint
s {$sel:glueVersion:CreateDevEndpoint' :: Maybe Text
glueVersion = Maybe Text
a} :: CreateDevEndpoint)

-- | The number of Glue Data Processing Units (DPUs) to allocate to this
-- @DevEndpoint@.
createDevEndpoint_numberOfNodes :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Int)
createDevEndpoint_numberOfNodes :: Lens' CreateDevEndpoint (Maybe Int)
createDevEndpoint_numberOfNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Int
numberOfNodes :: Maybe Int
$sel:numberOfNodes:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
numberOfNodes} -> Maybe Int
numberOfNodes) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Int
a -> CreateDevEndpoint
s {$sel:numberOfNodes:CreateDevEndpoint' :: Maybe Int
numberOfNodes = Maybe Int
a} :: CreateDevEndpoint)

-- | The number of workers of a defined @workerType@ that are allocated to
-- the development endpoint.
--
-- The maximum number of workers you can define are 299 for @G.1X@, and 149
-- for @G.2X@.
createDevEndpoint_numberOfWorkers :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Int)
createDevEndpoint_numberOfWorkers :: Lens' CreateDevEndpoint (Maybe Int)
createDevEndpoint_numberOfWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Int
numberOfWorkers :: Maybe Int
$sel:numberOfWorkers:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
numberOfWorkers} -> Maybe Int
numberOfWorkers) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Int
a -> CreateDevEndpoint
s {$sel:numberOfWorkers:CreateDevEndpoint' :: Maybe Int
numberOfWorkers = Maybe Int
a} :: CreateDevEndpoint)

-- | The public key to be used by this @DevEndpoint@ for authentication. This
-- attribute is provided for backward compatibility because the recommended
-- attribute to use is public keys.
createDevEndpoint_publicKey :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Text)
createDevEndpoint_publicKey :: Lens' CreateDevEndpoint (Maybe Text)
createDevEndpoint_publicKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Text
publicKey :: Maybe Text
$sel:publicKey:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
publicKey} -> Maybe Text
publicKey) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Text
a -> CreateDevEndpoint
s {$sel:publicKey:CreateDevEndpoint' :: Maybe Text
publicKey = Maybe Text
a} :: CreateDevEndpoint)

-- | A list of public keys to be used by the development endpoints for
-- authentication. The use of this attribute is preferred over a single
-- public key because the public keys allow you to have a different private
-- key per client.
--
-- If you previously created an endpoint with a public key, you must remove
-- that key to be able to set a list of public keys. Call the
-- @UpdateDevEndpoint@ API with the public key content in the
-- @deletePublicKeys@ attribute, and the list of new keys in the
-- @addPublicKeys@ attribute.
createDevEndpoint_publicKeys :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe [Prelude.Text])
createDevEndpoint_publicKeys :: Lens' CreateDevEndpoint (Maybe [Text])
createDevEndpoint_publicKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe [Text]
publicKeys :: Maybe [Text]
$sel:publicKeys:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
publicKeys} -> Maybe [Text]
publicKeys) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe [Text]
a -> CreateDevEndpoint
s {$sel:publicKeys:CreateDevEndpoint' :: Maybe [Text]
publicKeys = Maybe [Text]
a} :: CreateDevEndpoint) 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 name of the @SecurityConfiguration@ structure to be used with this
-- @DevEndpoint@.
createDevEndpoint_securityConfiguration :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Text)
createDevEndpoint_securityConfiguration :: Lens' CreateDevEndpoint (Maybe Text)
createDevEndpoint_securityConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Text
securityConfiguration :: Maybe Text
$sel:securityConfiguration:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
securityConfiguration} -> Maybe Text
securityConfiguration) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Text
a -> CreateDevEndpoint
s {$sel:securityConfiguration:CreateDevEndpoint' :: Maybe Text
securityConfiguration = Maybe Text
a} :: CreateDevEndpoint)

-- | Security group IDs for the security groups to be used by the new
-- @DevEndpoint@.
createDevEndpoint_securityGroupIds :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe [Prelude.Text])
createDevEndpoint_securityGroupIds :: Lens' CreateDevEndpoint (Maybe [Text])
createDevEndpoint_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe [Text]
securityGroupIds :: Maybe [Text]
$sel:securityGroupIds:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
securityGroupIds} -> Maybe [Text]
securityGroupIds) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe [Text]
a -> CreateDevEndpoint
s {$sel:securityGroupIds:CreateDevEndpoint' :: Maybe [Text]
securityGroupIds = Maybe [Text]
a} :: CreateDevEndpoint) 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 subnet ID for the new @DevEndpoint@ to use.
createDevEndpoint_subnetId :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe Prelude.Text)
createDevEndpoint_subnetId :: Lens' CreateDevEndpoint (Maybe Text)
createDevEndpoint_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe Text
a -> CreateDevEndpoint
s {$sel:subnetId:CreateDevEndpoint' :: Maybe Text
subnetId = Maybe Text
a} :: CreateDevEndpoint)

-- | The tags to use with this DevEndpoint. You may use tags to limit access
-- to the DevEndpoint. For more information about tags in Glue, see
-- <https://docs.aws.amazon.com/glue/latest/dg/monitor-tags.html Amazon Web Services Tags in Glue>
-- in the developer guide.
createDevEndpoint_tags :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createDevEndpoint_tags :: Lens' CreateDevEndpoint (Maybe (HashMap Text Text))
createDevEndpoint_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe (HashMap Text Text)
a -> CreateDevEndpoint
s {$sel:tags:CreateDevEndpoint' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateDevEndpoint) 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 type of predefined worker that is allocated to the development
-- endpoint. Accepts a value of Standard, G.1X, or G.2X.
--
-- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
--     of memory and a 50GB disk, and 2 executors per worker.
--
-- -   For the @G.1X@ worker type, each worker maps to 1 DPU (4 vCPU, 16 GB
--     of memory, 64 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- -   For the @G.2X@ worker type, each worker maps to 2 DPU (8 vCPU, 32 GB
--     of memory, 128 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- Known issue: when a development endpoint is created with the @G.2X@
-- @WorkerType@ configuration, the Spark drivers for the development
-- endpoint will run on 4 vCPU, 16 GB of memory, and a 64 GB disk.
createDevEndpoint_workerType :: Lens.Lens' CreateDevEndpoint (Prelude.Maybe WorkerType)
createDevEndpoint_workerType :: Lens' CreateDevEndpoint (Maybe WorkerType)
createDevEndpoint_workerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Maybe WorkerType
workerType :: Maybe WorkerType
$sel:workerType:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe WorkerType
workerType} -> Maybe WorkerType
workerType) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Maybe WorkerType
a -> CreateDevEndpoint
s {$sel:workerType:CreateDevEndpoint' :: Maybe WorkerType
workerType = Maybe WorkerType
a} :: CreateDevEndpoint)

-- | The name to be assigned to the new @DevEndpoint@.
createDevEndpoint_endpointName :: Lens.Lens' CreateDevEndpoint Prelude.Text
createDevEndpoint_endpointName :: Lens' CreateDevEndpoint Text
createDevEndpoint_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Text
endpointName :: Text
$sel:endpointName:CreateDevEndpoint' :: CreateDevEndpoint -> Text
endpointName} -> Text
endpointName) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Text
a -> CreateDevEndpoint
s {$sel:endpointName:CreateDevEndpoint' :: Text
endpointName = Text
a} :: CreateDevEndpoint)

-- | The IAM role for the @DevEndpoint@.
createDevEndpoint_roleArn :: Lens.Lens' CreateDevEndpoint Prelude.Text
createDevEndpoint_roleArn :: Lens' CreateDevEndpoint Text
createDevEndpoint_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpoint' {Text
roleArn :: Text
$sel:roleArn:CreateDevEndpoint' :: CreateDevEndpoint -> Text
roleArn} -> Text
roleArn) (\s :: CreateDevEndpoint
s@CreateDevEndpoint' {} Text
a -> CreateDevEndpoint
s {$sel:roleArn:CreateDevEndpoint' :: Text
roleArn = Text
a} :: CreateDevEndpoint)

instance Core.AWSRequest CreateDevEndpoint where
  type
    AWSResponse CreateDevEndpoint =
      CreateDevEndpointResponse
  request :: (Service -> Service)
-> CreateDevEndpoint -> Request CreateDevEndpoint
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateDevEndpoint
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDevEndpoint)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe WorkerType
-> Maybe Text
-> Maybe Int
-> Int
-> CreateDevEndpointResponse
CreateDevEndpointResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Arguments" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"AvailabilityZone")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedTimestamp")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"EndpointName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ExtraJarsS3Path")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ExtraPythonLibsS3Path")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FailureReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GlueVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NumberOfNodes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NumberOfWorkers")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SecurityConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SecurityGroupIds"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"SubnetId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VpcId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"WorkerType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"YarnEndpointAddress")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ZeppelinRemoteSparkInterpreterPort")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateDevEndpoint where
  hashWithSalt :: Int -> CreateDevEndpoint -> Int
hashWithSalt Int
_salt CreateDevEndpoint' {Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe WorkerType
Text
roleArn :: Text
endpointName :: Text
workerType :: Maybe WorkerType
tags :: Maybe (HashMap Text Text)
subnetId :: Maybe Text
securityGroupIds :: Maybe [Text]
securityConfiguration :: Maybe Text
publicKeys :: Maybe [Text]
publicKey :: Maybe Text
numberOfWorkers :: Maybe Int
numberOfNodes :: Maybe Int
glueVersion :: Maybe Text
extraPythonLibsS3Path :: Maybe Text
extraJarsS3Path :: Maybe Text
arguments :: Maybe (HashMap Text Text)
$sel:roleArn:CreateDevEndpoint' :: CreateDevEndpoint -> Text
$sel:endpointName:CreateDevEndpoint' :: CreateDevEndpoint -> Text
$sel:workerType:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe WorkerType
$sel:tags:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
$sel:subnetId:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:securityGroupIds:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
$sel:securityConfiguration:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:publicKeys:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
$sel:publicKey:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:numberOfWorkers:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
$sel:numberOfNodes:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
$sel:glueVersion:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:extraPythonLibsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:extraJarsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:arguments:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
arguments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
extraJarsS3Path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
extraPythonLibsS3Path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
glueVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numberOfNodes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numberOfWorkers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
publicKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
publicKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
securityConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
securityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subnetId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkerType
workerType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData CreateDevEndpoint where
  rnf :: CreateDevEndpoint -> ()
rnf CreateDevEndpoint' {Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe WorkerType
Text
roleArn :: Text
endpointName :: Text
workerType :: Maybe WorkerType
tags :: Maybe (HashMap Text Text)
subnetId :: Maybe Text
securityGroupIds :: Maybe [Text]
securityConfiguration :: Maybe Text
publicKeys :: Maybe [Text]
publicKey :: Maybe Text
numberOfWorkers :: Maybe Int
numberOfNodes :: Maybe Int
glueVersion :: Maybe Text
extraPythonLibsS3Path :: Maybe Text
extraJarsS3Path :: Maybe Text
arguments :: Maybe (HashMap Text Text)
$sel:roleArn:CreateDevEndpoint' :: CreateDevEndpoint -> Text
$sel:endpointName:CreateDevEndpoint' :: CreateDevEndpoint -> Text
$sel:workerType:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe WorkerType
$sel:tags:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
$sel:subnetId:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:securityGroupIds:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
$sel:securityConfiguration:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:publicKeys:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
$sel:publicKey:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:numberOfWorkers:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
$sel:numberOfNodes:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
$sel:glueVersion:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:extraPythonLibsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:extraJarsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:arguments:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
arguments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
extraJarsS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
extraPythonLibsS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
glueVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfNodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfWorkers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
publicKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
publicKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
securityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
      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 WorkerType
workerType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
endpointName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

instance Data.ToHeaders CreateDevEndpoint where
  toHeaders :: CreateDevEndpoint -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"AWSGlue.CreateDevEndpoint" :: Prelude.ByteString),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateDevEndpoint where
  toJSON :: CreateDevEndpoint -> Value
toJSON CreateDevEndpoint' {Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe WorkerType
Text
roleArn :: Text
endpointName :: Text
workerType :: Maybe WorkerType
tags :: Maybe (HashMap Text Text)
subnetId :: Maybe Text
securityGroupIds :: Maybe [Text]
securityConfiguration :: Maybe Text
publicKeys :: Maybe [Text]
publicKey :: Maybe Text
numberOfWorkers :: Maybe Int
numberOfNodes :: Maybe Int
glueVersion :: Maybe Text
extraPythonLibsS3Path :: Maybe Text
extraJarsS3Path :: Maybe Text
arguments :: Maybe (HashMap Text Text)
$sel:roleArn:CreateDevEndpoint' :: CreateDevEndpoint -> Text
$sel:endpointName:CreateDevEndpoint' :: CreateDevEndpoint -> Text
$sel:workerType:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe WorkerType
$sel:tags:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
$sel:subnetId:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:securityGroupIds:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
$sel:securityConfiguration:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:publicKeys:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe [Text]
$sel:publicKey:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:numberOfWorkers:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
$sel:numberOfNodes:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Int
$sel:glueVersion:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:extraPythonLibsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:extraJarsS3Path:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe Text
$sel:arguments:CreateDevEndpoint' :: CreateDevEndpoint -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Arguments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
arguments,
            (Key
"ExtraJarsS3Path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
extraJarsS3Path,
            (Key
"ExtraPythonLibsS3Path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
extraPythonLibsS3Path,
            (Key
"GlueVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
glueVersion,
            (Key
"NumberOfNodes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
numberOfNodes,
            (Key
"NumberOfWorkers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
numberOfWorkers,
            (Key
"PublicKey" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
publicKey,
            (Key
"PublicKeys" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
publicKeys,
            (Key
"SecurityConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
securityConfiguration,
            (Key
"SecurityGroupIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
securityGroupIds,
            (Key
"SubnetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
subnetId,
            (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            (Key
"WorkerType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WorkerType
workerType,
            forall a. a -> Maybe a
Prelude.Just (Key
"EndpointName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointName),
            forall a. a -> Maybe a
Prelude.Just (Key
"RoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn)
          ]
      )

instance Data.ToPath CreateDevEndpoint where
  toPath :: CreateDevEndpoint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery CreateDevEndpoint where
  toQuery :: CreateDevEndpoint -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newCreateDevEndpointResponse' smart constructor.
data CreateDevEndpointResponse = CreateDevEndpointResponse'
  { -- | The map of arguments used to configure this @DevEndpoint@.
    --
    -- Valid arguments are:
    --
    -- -   @\"--enable-glue-datacatalog\": \"\"@
    --
    -- You can specify a version of Python support for development endpoints by
    -- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
    -- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
    -- defaults to Python 2.
    CreateDevEndpointResponse -> Maybe (HashMap Text Text)
arguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The Amazon Web Services Availability Zone where this @DevEndpoint@ is
    -- located.
    CreateDevEndpointResponse -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | The point in time at which this @DevEndpoint@ was created.
    CreateDevEndpointResponse -> Maybe POSIX
createdTimestamp :: Prelude.Maybe Data.POSIX,
    -- | The name assigned to the new @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
endpointName :: Prelude.Maybe Prelude.Text,
    -- | Path to one or more Java @.jar@ files in an S3 bucket that will be
    -- loaded in your @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
extraJarsS3Path :: Prelude.Maybe Prelude.Text,
    -- | The paths to one or more Python libraries in an S3 bucket that will be
    -- loaded in your @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
extraPythonLibsS3Path :: Prelude.Maybe Prelude.Text,
    -- | The reason for a current failure in this @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | Glue version determines the versions of Apache Spark and Python that
    -- Glue supports. The Python version indicates the version supported for
    -- running your ETL scripts on development endpoints.
    --
    -- For more information about the available Glue versions and corresponding
    -- Spark and Python versions, see
    -- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
    -- in the developer guide.
    CreateDevEndpointResponse -> Maybe Text
glueVersion :: Prelude.Maybe Prelude.Text,
    -- | The number of Glue Data Processing Units (DPUs) allocated to this
    -- DevEndpoint.
    CreateDevEndpointResponse -> Maybe Int
numberOfNodes :: Prelude.Maybe Prelude.Int,
    -- | The number of workers of a defined @workerType@ that are allocated to
    -- the development endpoint.
    CreateDevEndpointResponse -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the role assigned to the new
    -- @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the @SecurityConfiguration@ structure being used with this
    -- @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
securityConfiguration :: Prelude.Maybe Prelude.Text,
    -- | The security groups assigned to the new @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe [Text]
securityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The current status of the new @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The subnet ID assigned to the new @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
subnetId :: Prelude.Maybe Prelude.Text,
    -- | The ID of the virtual private cloud (VPC) used by this @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The type of predefined worker that is allocated to the development
    -- endpoint. May be a value of Standard, G.1X, or G.2X.
    CreateDevEndpointResponse -> Maybe WorkerType
workerType :: Prelude.Maybe WorkerType,
    -- | The address of the YARN endpoint used by this @DevEndpoint@.
    CreateDevEndpointResponse -> Maybe Text
yarnEndpointAddress :: Prelude.Maybe Prelude.Text,
    -- | The Apache Zeppelin port for the remote Apache Spark interpreter.
    CreateDevEndpointResponse -> Maybe Int
zeppelinRemoteSparkInterpreterPort :: Prelude.Maybe Prelude.Int,
    -- | The response's http status code.
    CreateDevEndpointResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDevEndpointResponse -> CreateDevEndpointResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDevEndpointResponse -> CreateDevEndpointResponse -> Bool
$c/= :: CreateDevEndpointResponse -> CreateDevEndpointResponse -> Bool
== :: CreateDevEndpointResponse -> CreateDevEndpointResponse -> Bool
$c== :: CreateDevEndpointResponse -> CreateDevEndpointResponse -> Bool
Prelude.Eq, ReadPrec [CreateDevEndpointResponse]
ReadPrec CreateDevEndpointResponse
Int -> ReadS CreateDevEndpointResponse
ReadS [CreateDevEndpointResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDevEndpointResponse]
$creadListPrec :: ReadPrec [CreateDevEndpointResponse]
readPrec :: ReadPrec CreateDevEndpointResponse
$creadPrec :: ReadPrec CreateDevEndpointResponse
readList :: ReadS [CreateDevEndpointResponse]
$creadList :: ReadS [CreateDevEndpointResponse]
readsPrec :: Int -> ReadS CreateDevEndpointResponse
$creadsPrec :: Int -> ReadS CreateDevEndpointResponse
Prelude.Read, Int -> CreateDevEndpointResponse -> ShowS
[CreateDevEndpointResponse] -> ShowS
CreateDevEndpointResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDevEndpointResponse] -> ShowS
$cshowList :: [CreateDevEndpointResponse] -> ShowS
show :: CreateDevEndpointResponse -> String
$cshow :: CreateDevEndpointResponse -> String
showsPrec :: Int -> CreateDevEndpointResponse -> ShowS
$cshowsPrec :: Int -> CreateDevEndpointResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDevEndpointResponse x -> CreateDevEndpointResponse
forall x.
CreateDevEndpointResponse -> Rep CreateDevEndpointResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDevEndpointResponse x -> CreateDevEndpointResponse
$cfrom :: forall x.
CreateDevEndpointResponse -> Rep CreateDevEndpointResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDevEndpointResponse' 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:
--
-- 'arguments', 'createDevEndpointResponse_arguments' - The map of arguments used to configure this @DevEndpoint@.
--
-- Valid arguments are:
--
-- -   @\"--enable-glue-datacatalog\": \"\"@
--
-- You can specify a version of Python support for development endpoints by
-- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
-- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
-- defaults to Python 2.
--
-- 'availabilityZone', 'createDevEndpointResponse_availabilityZone' - The Amazon Web Services Availability Zone where this @DevEndpoint@ is
-- located.
--
-- 'createdTimestamp', 'createDevEndpointResponse_createdTimestamp' - The point in time at which this @DevEndpoint@ was created.
--
-- 'endpointName', 'createDevEndpointResponse_endpointName' - The name assigned to the new @DevEndpoint@.
--
-- 'extraJarsS3Path', 'createDevEndpointResponse_extraJarsS3Path' - Path to one or more Java @.jar@ files in an S3 bucket that will be
-- loaded in your @DevEndpoint@.
--
-- 'extraPythonLibsS3Path', 'createDevEndpointResponse_extraPythonLibsS3Path' - The paths to one or more Python libraries in an S3 bucket that will be
-- loaded in your @DevEndpoint@.
--
-- 'failureReason', 'createDevEndpointResponse_failureReason' - The reason for a current failure in this @DevEndpoint@.
--
-- 'glueVersion', 'createDevEndpointResponse_glueVersion' - Glue version determines the versions of Apache Spark and Python that
-- Glue supports. The Python version indicates the version supported for
-- running your ETL scripts on development endpoints.
--
-- For more information about the available Glue versions and corresponding
-- Spark and Python versions, see
-- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
-- in the developer guide.
--
-- 'numberOfNodes', 'createDevEndpointResponse_numberOfNodes' - The number of Glue Data Processing Units (DPUs) allocated to this
-- DevEndpoint.
--
-- 'numberOfWorkers', 'createDevEndpointResponse_numberOfWorkers' - The number of workers of a defined @workerType@ that are allocated to
-- the development endpoint.
--
-- 'roleArn', 'createDevEndpointResponse_roleArn' - The Amazon Resource Name (ARN) of the role assigned to the new
-- @DevEndpoint@.
--
-- 'securityConfiguration', 'createDevEndpointResponse_securityConfiguration' - The name of the @SecurityConfiguration@ structure being used with this
-- @DevEndpoint@.
--
-- 'securityGroupIds', 'createDevEndpointResponse_securityGroupIds' - The security groups assigned to the new @DevEndpoint@.
--
-- 'status', 'createDevEndpointResponse_status' - The current status of the new @DevEndpoint@.
--
-- 'subnetId', 'createDevEndpointResponse_subnetId' - The subnet ID assigned to the new @DevEndpoint@.
--
-- 'vpcId', 'createDevEndpointResponse_vpcId' - The ID of the virtual private cloud (VPC) used by this @DevEndpoint@.
--
-- 'workerType', 'createDevEndpointResponse_workerType' - The type of predefined worker that is allocated to the development
-- endpoint. May be a value of Standard, G.1X, or G.2X.
--
-- 'yarnEndpointAddress', 'createDevEndpointResponse_yarnEndpointAddress' - The address of the YARN endpoint used by this @DevEndpoint@.
--
-- 'zeppelinRemoteSparkInterpreterPort', 'createDevEndpointResponse_zeppelinRemoteSparkInterpreterPort' - The Apache Zeppelin port for the remote Apache Spark interpreter.
--
-- 'httpStatus', 'createDevEndpointResponse_httpStatus' - The response's http status code.
newCreateDevEndpointResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDevEndpointResponse
newCreateDevEndpointResponse :: Int -> CreateDevEndpointResponse
newCreateDevEndpointResponse Int
pHttpStatus_ =
  CreateDevEndpointResponse'
    { $sel:arguments:CreateDevEndpointResponse' :: Maybe (HashMap Text Text)
arguments =
        forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:CreateDevEndpointResponse' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:createdTimestamp:CreateDevEndpointResponse' :: Maybe POSIX
createdTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:endpointName:CreateDevEndpointResponse' :: Maybe Text
endpointName = forall a. Maybe a
Prelude.Nothing,
      $sel:extraJarsS3Path:CreateDevEndpointResponse' :: Maybe Text
extraJarsS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:extraPythonLibsS3Path:CreateDevEndpointResponse' :: Maybe Text
extraPythonLibsS3Path = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:CreateDevEndpointResponse' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:glueVersion:CreateDevEndpointResponse' :: Maybe Text
glueVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfNodes:CreateDevEndpointResponse' :: Maybe Int
numberOfNodes = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfWorkers:CreateDevEndpointResponse' :: Maybe Int
numberOfWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:CreateDevEndpointResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:securityConfiguration:CreateDevEndpointResponse' :: Maybe Text
securityConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupIds:CreateDevEndpointResponse' :: Maybe [Text]
securityGroupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateDevEndpointResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:CreateDevEndpointResponse' :: Maybe Text
subnetId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:CreateDevEndpointResponse' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:workerType:CreateDevEndpointResponse' :: Maybe WorkerType
workerType = forall a. Maybe a
Prelude.Nothing,
      $sel:yarnEndpointAddress:CreateDevEndpointResponse' :: Maybe Text
yarnEndpointAddress = forall a. Maybe a
Prelude.Nothing,
      $sel:zeppelinRemoteSparkInterpreterPort:CreateDevEndpointResponse' :: Maybe Int
zeppelinRemoteSparkInterpreterPort =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDevEndpointResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The map of arguments used to configure this @DevEndpoint@.
--
-- Valid arguments are:
--
-- -   @\"--enable-glue-datacatalog\": \"\"@
--
-- You can specify a version of Python support for development endpoints by
-- using the @Arguments@ parameter in the @CreateDevEndpoint@ or
-- @UpdateDevEndpoint@ APIs. If no arguments are provided, the version
-- defaults to Python 2.
createDevEndpointResponse_arguments :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createDevEndpointResponse_arguments :: Lens' CreateDevEndpointResponse (Maybe (HashMap Text Text))
createDevEndpointResponse_arguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe (HashMap Text Text)
arguments :: Maybe (HashMap Text Text)
$sel:arguments:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe (HashMap Text Text)
arguments} -> Maybe (HashMap Text Text)
arguments) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe (HashMap Text Text)
a -> CreateDevEndpointResponse
s {$sel:arguments:CreateDevEndpointResponse' :: Maybe (HashMap Text Text)
arguments = Maybe (HashMap Text Text)
a} :: CreateDevEndpointResponse) 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 Amazon Web Services Availability Zone where this @DevEndpoint@ is
-- located.
createDevEndpointResponse_availabilityZone :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_availabilityZone :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
availabilityZone :: Maybe Text
$sel:availabilityZone:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
availabilityZone} -> Maybe Text
availabilityZone) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:availabilityZone:CreateDevEndpointResponse' :: Maybe Text
availabilityZone = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The point in time at which this @DevEndpoint@ was created.
createDevEndpointResponse_createdTimestamp :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.UTCTime)
createDevEndpointResponse_createdTimestamp :: Lens' CreateDevEndpointResponse (Maybe UTCTime)
createDevEndpointResponse_createdTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe POSIX
createdTimestamp :: Maybe POSIX
$sel:createdTimestamp:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe POSIX
createdTimestamp} -> Maybe POSIX
createdTimestamp) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe POSIX
a -> CreateDevEndpointResponse
s {$sel:createdTimestamp:CreateDevEndpointResponse' :: Maybe POSIX
createdTimestamp = Maybe POSIX
a} :: CreateDevEndpointResponse) 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 name assigned to the new @DevEndpoint@.
createDevEndpointResponse_endpointName :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_endpointName :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
endpointName :: Maybe Text
$sel:endpointName:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
endpointName} -> Maybe Text
endpointName) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:endpointName:CreateDevEndpointResponse' :: Maybe Text
endpointName = Maybe Text
a} :: CreateDevEndpointResponse)

-- | Path to one or more Java @.jar@ files in an S3 bucket that will be
-- loaded in your @DevEndpoint@.
createDevEndpointResponse_extraJarsS3Path :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_extraJarsS3Path :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_extraJarsS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
extraJarsS3Path :: Maybe Text
$sel:extraJarsS3Path:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
extraJarsS3Path} -> Maybe Text
extraJarsS3Path) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:extraJarsS3Path:CreateDevEndpointResponse' :: Maybe Text
extraJarsS3Path = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The paths to one or more Python libraries in an S3 bucket that will be
-- loaded in your @DevEndpoint@.
createDevEndpointResponse_extraPythonLibsS3Path :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_extraPythonLibsS3Path :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_extraPythonLibsS3Path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
extraPythonLibsS3Path :: Maybe Text
$sel:extraPythonLibsS3Path:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
extraPythonLibsS3Path} -> Maybe Text
extraPythonLibsS3Path) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:extraPythonLibsS3Path:CreateDevEndpointResponse' :: Maybe Text
extraPythonLibsS3Path = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The reason for a current failure in this @DevEndpoint@.
createDevEndpointResponse_failureReason :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_failureReason :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:failureReason:CreateDevEndpointResponse' :: Maybe Text
failureReason = Maybe Text
a} :: CreateDevEndpointResponse)

-- | Glue version determines the versions of Apache Spark and Python that
-- Glue supports. The Python version indicates the version supported for
-- running your ETL scripts on development endpoints.
--
-- For more information about the available Glue versions and corresponding
-- Spark and Python versions, see
-- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
-- in the developer guide.
createDevEndpointResponse_glueVersion :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_glueVersion :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_glueVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
glueVersion :: Maybe Text
$sel:glueVersion:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
glueVersion} -> Maybe Text
glueVersion) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:glueVersion:CreateDevEndpointResponse' :: Maybe Text
glueVersion = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The number of Glue Data Processing Units (DPUs) allocated to this
-- DevEndpoint.
createDevEndpointResponse_numberOfNodes :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Int)
createDevEndpointResponse_numberOfNodes :: Lens' CreateDevEndpointResponse (Maybe Int)
createDevEndpointResponse_numberOfNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Int
numberOfNodes :: Maybe Int
$sel:numberOfNodes:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Int
numberOfNodes} -> Maybe Int
numberOfNodes) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Int
a -> CreateDevEndpointResponse
s {$sel:numberOfNodes:CreateDevEndpointResponse' :: Maybe Int
numberOfNodes = Maybe Int
a} :: CreateDevEndpointResponse)

-- | The number of workers of a defined @workerType@ that are allocated to
-- the development endpoint.
createDevEndpointResponse_numberOfWorkers :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Int)
createDevEndpointResponse_numberOfWorkers :: Lens' CreateDevEndpointResponse (Maybe Int)
createDevEndpointResponse_numberOfWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Int
numberOfWorkers :: Maybe Int
$sel:numberOfWorkers:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Int
numberOfWorkers} -> Maybe Int
numberOfWorkers) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Int
a -> CreateDevEndpointResponse
s {$sel:numberOfWorkers:CreateDevEndpointResponse' :: Maybe Int
numberOfWorkers = Maybe Int
a} :: CreateDevEndpointResponse)

-- | The Amazon Resource Name (ARN) of the role assigned to the new
-- @DevEndpoint@.
createDevEndpointResponse_roleArn :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_roleArn :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:roleArn:CreateDevEndpointResponse' :: Maybe Text
roleArn = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The name of the @SecurityConfiguration@ structure being used with this
-- @DevEndpoint@.
createDevEndpointResponse_securityConfiguration :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_securityConfiguration :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_securityConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
securityConfiguration :: Maybe Text
$sel:securityConfiguration:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
securityConfiguration} -> Maybe Text
securityConfiguration) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:securityConfiguration:CreateDevEndpointResponse' :: Maybe Text
securityConfiguration = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The security groups assigned to the new @DevEndpoint@.
createDevEndpointResponse_securityGroupIds :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe [Prelude.Text])
createDevEndpointResponse_securityGroupIds :: Lens' CreateDevEndpointResponse (Maybe [Text])
createDevEndpointResponse_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe [Text]
securityGroupIds :: Maybe [Text]
$sel:securityGroupIds:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe [Text]
securityGroupIds} -> Maybe [Text]
securityGroupIds) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe [Text]
a -> CreateDevEndpointResponse
s {$sel:securityGroupIds:CreateDevEndpointResponse' :: Maybe [Text]
securityGroupIds = Maybe [Text]
a} :: CreateDevEndpointResponse) 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 current status of the new @DevEndpoint@.
createDevEndpointResponse_status :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_status :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
status :: Maybe Text
$sel:status:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:status:CreateDevEndpointResponse' :: Maybe Text
status = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The subnet ID assigned to the new @DevEndpoint@.
createDevEndpointResponse_subnetId :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_subnetId :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
subnetId :: Maybe Text
$sel:subnetId:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
subnetId} -> Maybe Text
subnetId) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:subnetId:CreateDevEndpointResponse' :: Maybe Text
subnetId = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The ID of the virtual private cloud (VPC) used by this @DevEndpoint@.
createDevEndpointResponse_vpcId :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_vpcId :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:vpcId:CreateDevEndpointResponse' :: Maybe Text
vpcId = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The type of predefined worker that is allocated to the development
-- endpoint. May be a value of Standard, G.1X, or G.2X.
createDevEndpointResponse_workerType :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe WorkerType)
createDevEndpointResponse_workerType :: Lens' CreateDevEndpointResponse (Maybe WorkerType)
createDevEndpointResponse_workerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe WorkerType
workerType :: Maybe WorkerType
$sel:workerType:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe WorkerType
workerType} -> Maybe WorkerType
workerType) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe WorkerType
a -> CreateDevEndpointResponse
s {$sel:workerType:CreateDevEndpointResponse' :: Maybe WorkerType
workerType = Maybe WorkerType
a} :: CreateDevEndpointResponse)

-- | The address of the YARN endpoint used by this @DevEndpoint@.
createDevEndpointResponse_yarnEndpointAddress :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Text)
createDevEndpointResponse_yarnEndpointAddress :: Lens' CreateDevEndpointResponse (Maybe Text)
createDevEndpointResponse_yarnEndpointAddress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Text
yarnEndpointAddress :: Maybe Text
$sel:yarnEndpointAddress:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
yarnEndpointAddress} -> Maybe Text
yarnEndpointAddress) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Text
a -> CreateDevEndpointResponse
s {$sel:yarnEndpointAddress:CreateDevEndpointResponse' :: Maybe Text
yarnEndpointAddress = Maybe Text
a} :: CreateDevEndpointResponse)

-- | The Apache Zeppelin port for the remote Apache Spark interpreter.
createDevEndpointResponse_zeppelinRemoteSparkInterpreterPort :: Lens.Lens' CreateDevEndpointResponse (Prelude.Maybe Prelude.Int)
createDevEndpointResponse_zeppelinRemoteSparkInterpreterPort :: Lens' CreateDevEndpointResponse (Maybe Int)
createDevEndpointResponse_zeppelinRemoteSparkInterpreterPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Maybe Int
zeppelinRemoteSparkInterpreterPort :: Maybe Int
$sel:zeppelinRemoteSparkInterpreterPort:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Int
zeppelinRemoteSparkInterpreterPort} -> Maybe Int
zeppelinRemoteSparkInterpreterPort) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Maybe Int
a -> CreateDevEndpointResponse
s {$sel:zeppelinRemoteSparkInterpreterPort:CreateDevEndpointResponse' :: Maybe Int
zeppelinRemoteSparkInterpreterPort = Maybe Int
a} :: CreateDevEndpointResponse)

-- | The response's http status code.
createDevEndpointResponse_httpStatus :: Lens.Lens' CreateDevEndpointResponse Prelude.Int
createDevEndpointResponse_httpStatus :: Lens' CreateDevEndpointResponse Int
createDevEndpointResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDevEndpointResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateDevEndpointResponse
s@CreateDevEndpointResponse' {} Int
a -> CreateDevEndpointResponse
s {$sel:httpStatus:CreateDevEndpointResponse' :: Int
httpStatus = Int
a} :: CreateDevEndpointResponse)

instance Prelude.NFData CreateDevEndpointResponse where
  rnf :: CreateDevEndpointResponse -> ()
rnf CreateDevEndpointResponse' {Int
Maybe Int
Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe WorkerType
httpStatus :: Int
zeppelinRemoteSparkInterpreterPort :: Maybe Int
yarnEndpointAddress :: Maybe Text
workerType :: Maybe WorkerType
vpcId :: Maybe Text
subnetId :: Maybe Text
status :: Maybe Text
securityGroupIds :: Maybe [Text]
securityConfiguration :: Maybe Text
roleArn :: Maybe Text
numberOfWorkers :: Maybe Int
numberOfNodes :: Maybe Int
glueVersion :: Maybe Text
failureReason :: Maybe Text
extraPythonLibsS3Path :: Maybe Text
extraJarsS3Path :: Maybe Text
endpointName :: Maybe Text
createdTimestamp :: Maybe POSIX
availabilityZone :: Maybe Text
arguments :: Maybe (HashMap Text Text)
$sel:httpStatus:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Int
$sel:zeppelinRemoteSparkInterpreterPort:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Int
$sel:yarnEndpointAddress:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:workerType:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe WorkerType
$sel:vpcId:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:subnetId:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:status:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:securityGroupIds:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe [Text]
$sel:securityConfiguration:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:roleArn:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:numberOfWorkers:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Int
$sel:numberOfNodes:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Int
$sel:glueVersion:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:failureReason:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:extraPythonLibsS3Path:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:extraJarsS3Path:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:endpointName:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:createdTimestamp:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe POSIX
$sel:availabilityZone:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe Text
$sel:arguments:CreateDevEndpointResponse' :: CreateDevEndpointResponse -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
arguments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpointName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
extraJarsS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
extraPythonLibsS3Path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
glueVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfNodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfWorkers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
securityConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
securityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subnetId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkerType
workerType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
yarnEndpointAddress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
zeppelinRemoteSparkInterpreterPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus