{-# 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.Athena.Types.EngineConfiguration
-- 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.Athena.Types.EngineConfiguration where

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

-- | Contains data processing unit (DPU) configuration settings and parameter
-- mappings for a notebook engine.
--
-- /See:/ 'newEngineConfiguration' smart constructor.
data EngineConfiguration = EngineConfiguration'
  { -- | Contains additional notebook engine @MAP\<string, string>@ parameter
    -- mappings in the form of key-value pairs. To specify an Amazon S3 URI
    -- that the Jupyter server will download and serve, specify a value for the
    -- StartSessionRequest$NotebookVersion field, and then add a key named
    -- @NotebookFileURI@ to @AdditionalConfigs@ that has value of the Amazon S3
    -- URI.
    EngineConfiguration -> Maybe (HashMap Text Text)
additionalConfigs :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The number of DPUs to use for the coordinator. A coordinator is a
    -- special executor that orchestrates processing work and manages other
    -- executors in a notebook session.
    EngineConfiguration -> Maybe Natural
coordinatorDpuSize :: Prelude.Maybe Prelude.Natural,
    -- | The default number of DPUs to use for executors. An executor is the
    -- smallest unit of compute that a notebook session can request from
    -- Athena.
    EngineConfiguration -> Maybe Natural
defaultExecutorDpuSize :: Prelude.Maybe Prelude.Natural,
    -- | The maximum number of DPUs that can run concurrently.
    EngineConfiguration -> Natural
maxConcurrentDpus :: Prelude.Natural
  }
  deriving (EngineConfiguration -> EngineConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EngineConfiguration -> EngineConfiguration -> Bool
$c/= :: EngineConfiguration -> EngineConfiguration -> Bool
== :: EngineConfiguration -> EngineConfiguration -> Bool
$c== :: EngineConfiguration -> EngineConfiguration -> Bool
Prelude.Eq, ReadPrec [EngineConfiguration]
ReadPrec EngineConfiguration
Int -> ReadS EngineConfiguration
ReadS [EngineConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EngineConfiguration]
$creadListPrec :: ReadPrec [EngineConfiguration]
readPrec :: ReadPrec EngineConfiguration
$creadPrec :: ReadPrec EngineConfiguration
readList :: ReadS [EngineConfiguration]
$creadList :: ReadS [EngineConfiguration]
readsPrec :: Int -> ReadS EngineConfiguration
$creadsPrec :: Int -> ReadS EngineConfiguration
Prelude.Read, Int -> EngineConfiguration -> ShowS
[EngineConfiguration] -> ShowS
EngineConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EngineConfiguration] -> ShowS
$cshowList :: [EngineConfiguration] -> ShowS
show :: EngineConfiguration -> String
$cshow :: EngineConfiguration -> String
showsPrec :: Int -> EngineConfiguration -> ShowS
$cshowsPrec :: Int -> EngineConfiguration -> ShowS
Prelude.Show, forall x. Rep EngineConfiguration x -> EngineConfiguration
forall x. EngineConfiguration -> Rep EngineConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EngineConfiguration x -> EngineConfiguration
$cfrom :: forall x. EngineConfiguration -> Rep EngineConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'EngineConfiguration' 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:
--
-- 'additionalConfigs', 'engineConfiguration_additionalConfigs' - Contains additional notebook engine @MAP\<string, string>@ parameter
-- mappings in the form of key-value pairs. To specify an Amazon S3 URI
-- that the Jupyter server will download and serve, specify a value for the
-- StartSessionRequest$NotebookVersion field, and then add a key named
-- @NotebookFileURI@ to @AdditionalConfigs@ that has value of the Amazon S3
-- URI.
--
-- 'coordinatorDpuSize', 'engineConfiguration_coordinatorDpuSize' - The number of DPUs to use for the coordinator. A coordinator is a
-- special executor that orchestrates processing work and manages other
-- executors in a notebook session.
--
-- 'defaultExecutorDpuSize', 'engineConfiguration_defaultExecutorDpuSize' - The default number of DPUs to use for executors. An executor is the
-- smallest unit of compute that a notebook session can request from
-- Athena.
--
-- 'maxConcurrentDpus', 'engineConfiguration_maxConcurrentDpus' - The maximum number of DPUs that can run concurrently.
newEngineConfiguration ::
  -- | 'maxConcurrentDpus'
  Prelude.Natural ->
  EngineConfiguration
newEngineConfiguration :: Natural -> EngineConfiguration
newEngineConfiguration Natural
pMaxConcurrentDpus_ =
  EngineConfiguration'
    { $sel:additionalConfigs:EngineConfiguration' :: Maybe (HashMap Text Text)
additionalConfigs =
        forall a. Maybe a
Prelude.Nothing,
      $sel:coordinatorDpuSize:EngineConfiguration' :: Maybe Natural
coordinatorDpuSize = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultExecutorDpuSize:EngineConfiguration' :: Maybe Natural
defaultExecutorDpuSize = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrentDpus:EngineConfiguration' :: Natural
maxConcurrentDpus = Natural
pMaxConcurrentDpus_
    }

-- | Contains additional notebook engine @MAP\<string, string>@ parameter
-- mappings in the form of key-value pairs. To specify an Amazon S3 URI
-- that the Jupyter server will download and serve, specify a value for the
-- StartSessionRequest$NotebookVersion field, and then add a key named
-- @NotebookFileURI@ to @AdditionalConfigs@ that has value of the Amazon S3
-- URI.
engineConfiguration_additionalConfigs :: Lens.Lens' EngineConfiguration (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
engineConfiguration_additionalConfigs :: Lens' EngineConfiguration (Maybe (HashMap Text Text))
engineConfiguration_additionalConfigs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EngineConfiguration' {Maybe (HashMap Text Text)
additionalConfigs :: Maybe (HashMap Text Text)
$sel:additionalConfigs:EngineConfiguration' :: EngineConfiguration -> Maybe (HashMap Text Text)
additionalConfigs} -> Maybe (HashMap Text Text)
additionalConfigs) (\s :: EngineConfiguration
s@EngineConfiguration' {} Maybe (HashMap Text Text)
a -> EngineConfiguration
s {$sel:additionalConfigs:EngineConfiguration' :: Maybe (HashMap Text Text)
additionalConfigs = Maybe (HashMap Text Text)
a} :: EngineConfiguration) 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 number of DPUs to use for the coordinator. A coordinator is a
-- special executor that orchestrates processing work and manages other
-- executors in a notebook session.
engineConfiguration_coordinatorDpuSize :: Lens.Lens' EngineConfiguration (Prelude.Maybe Prelude.Natural)
engineConfiguration_coordinatorDpuSize :: Lens' EngineConfiguration (Maybe Natural)
engineConfiguration_coordinatorDpuSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EngineConfiguration' {Maybe Natural
coordinatorDpuSize :: Maybe Natural
$sel:coordinatorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
coordinatorDpuSize} -> Maybe Natural
coordinatorDpuSize) (\s :: EngineConfiguration
s@EngineConfiguration' {} Maybe Natural
a -> EngineConfiguration
s {$sel:coordinatorDpuSize:EngineConfiguration' :: Maybe Natural
coordinatorDpuSize = Maybe Natural
a} :: EngineConfiguration)

-- | The default number of DPUs to use for executors. An executor is the
-- smallest unit of compute that a notebook session can request from
-- Athena.
engineConfiguration_defaultExecutorDpuSize :: Lens.Lens' EngineConfiguration (Prelude.Maybe Prelude.Natural)
engineConfiguration_defaultExecutorDpuSize :: Lens' EngineConfiguration (Maybe Natural)
engineConfiguration_defaultExecutorDpuSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EngineConfiguration' {Maybe Natural
defaultExecutorDpuSize :: Maybe Natural
$sel:defaultExecutorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
defaultExecutorDpuSize} -> Maybe Natural
defaultExecutorDpuSize) (\s :: EngineConfiguration
s@EngineConfiguration' {} Maybe Natural
a -> EngineConfiguration
s {$sel:defaultExecutorDpuSize:EngineConfiguration' :: Maybe Natural
defaultExecutorDpuSize = Maybe Natural
a} :: EngineConfiguration)

-- | The maximum number of DPUs that can run concurrently.
engineConfiguration_maxConcurrentDpus :: Lens.Lens' EngineConfiguration Prelude.Natural
engineConfiguration_maxConcurrentDpus :: Lens' EngineConfiguration Natural
engineConfiguration_maxConcurrentDpus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\EngineConfiguration' {Natural
maxConcurrentDpus :: Natural
$sel:maxConcurrentDpus:EngineConfiguration' :: EngineConfiguration -> Natural
maxConcurrentDpus} -> Natural
maxConcurrentDpus) (\s :: EngineConfiguration
s@EngineConfiguration' {} Natural
a -> EngineConfiguration
s {$sel:maxConcurrentDpus:EngineConfiguration' :: Natural
maxConcurrentDpus = Natural
a} :: EngineConfiguration)

instance Data.FromJSON EngineConfiguration where
  parseJSON :: Value -> Parser EngineConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"EngineConfiguration"
      ( \Object
x ->
          Maybe (HashMap Text Text)
-> Maybe Natural -> Maybe Natural -> Natural -> EngineConfiguration
EngineConfiguration'
            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
"AdditionalConfigs"
                            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
"CoordinatorDpuSize")
            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
"DefaultExecutorDpuSize")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"MaxConcurrentDpus")
      )

instance Prelude.Hashable EngineConfiguration where
  hashWithSalt :: Int -> EngineConfiguration -> Int
hashWithSalt Int
_salt EngineConfiguration' {Natural
Maybe Natural
Maybe (HashMap Text Text)
maxConcurrentDpus :: Natural
defaultExecutorDpuSize :: Maybe Natural
coordinatorDpuSize :: Maybe Natural
additionalConfigs :: Maybe (HashMap Text Text)
$sel:maxConcurrentDpus:EngineConfiguration' :: EngineConfiguration -> Natural
$sel:defaultExecutorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
$sel:coordinatorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
$sel:additionalConfigs:EngineConfiguration' :: EngineConfiguration -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
additionalConfigs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
coordinatorDpuSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
defaultExecutorDpuSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
maxConcurrentDpus

instance Prelude.NFData EngineConfiguration where
  rnf :: EngineConfiguration -> ()
rnf EngineConfiguration' {Natural
Maybe Natural
Maybe (HashMap Text Text)
maxConcurrentDpus :: Natural
defaultExecutorDpuSize :: Maybe Natural
coordinatorDpuSize :: Maybe Natural
additionalConfigs :: Maybe (HashMap Text Text)
$sel:maxConcurrentDpus:EngineConfiguration' :: EngineConfiguration -> Natural
$sel:defaultExecutorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
$sel:coordinatorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
$sel:additionalConfigs:EngineConfiguration' :: EngineConfiguration -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
additionalConfigs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
coordinatorDpuSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
defaultExecutorDpuSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
maxConcurrentDpus

instance Data.ToJSON EngineConfiguration where
  toJSON :: EngineConfiguration -> Value
toJSON EngineConfiguration' {Natural
Maybe Natural
Maybe (HashMap Text Text)
maxConcurrentDpus :: Natural
defaultExecutorDpuSize :: Maybe Natural
coordinatorDpuSize :: Maybe Natural
additionalConfigs :: Maybe (HashMap Text Text)
$sel:maxConcurrentDpus:EngineConfiguration' :: EngineConfiguration -> Natural
$sel:defaultExecutorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
$sel:coordinatorDpuSize:EngineConfiguration' :: EngineConfiguration -> Maybe Natural
$sel:additionalConfigs:EngineConfiguration' :: EngineConfiguration -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AdditionalConfigs" 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)
additionalConfigs,
            (Key
"CoordinatorDpuSize" 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 Natural
coordinatorDpuSize,
            (Key
"DefaultExecutorDpuSize" 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 Natural
defaultExecutorDpuSize,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"MaxConcurrentDpus" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
maxConcurrentDpus)
          ]
      )