{-# 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.Personalize.Types.HPOConfig
-- 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.Personalize.Types.HPOConfig where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Personalize.Types.HPOObjective
import Amazonka.Personalize.Types.HPOResourceConfig
import Amazonka.Personalize.Types.HyperParameterRanges
import qualified Amazonka.Prelude as Prelude

-- | Describes the properties for hyperparameter optimization (HPO).
--
-- /See:/ 'newHPOConfig' smart constructor.
data HPOConfig = HPOConfig'
  { -- | The hyperparameters and their allowable ranges.
    HPOConfig -> Maybe HyperParameterRanges
algorithmHyperParameterRanges :: Prelude.Maybe HyperParameterRanges,
    -- | The metric to optimize during HPO.
    --
    -- Amazon Personalize doesn\'t support configuring the @hpoObjective@ at
    -- this time.
    HPOConfig -> Maybe HPOObjective
hpoObjective :: Prelude.Maybe HPOObjective,
    -- | Describes the resource configuration for HPO.
    HPOConfig -> Maybe HPOResourceConfig
hpoResourceConfig :: Prelude.Maybe HPOResourceConfig
  }
  deriving (HPOConfig -> HPOConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HPOConfig -> HPOConfig -> Bool
$c/= :: HPOConfig -> HPOConfig -> Bool
== :: HPOConfig -> HPOConfig -> Bool
$c== :: HPOConfig -> HPOConfig -> Bool
Prelude.Eq, ReadPrec [HPOConfig]
ReadPrec HPOConfig
Int -> ReadS HPOConfig
ReadS [HPOConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HPOConfig]
$creadListPrec :: ReadPrec [HPOConfig]
readPrec :: ReadPrec HPOConfig
$creadPrec :: ReadPrec HPOConfig
readList :: ReadS [HPOConfig]
$creadList :: ReadS [HPOConfig]
readsPrec :: Int -> ReadS HPOConfig
$creadsPrec :: Int -> ReadS HPOConfig
Prelude.Read, Int -> HPOConfig -> ShowS
[HPOConfig] -> ShowS
HPOConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HPOConfig] -> ShowS
$cshowList :: [HPOConfig] -> ShowS
show :: HPOConfig -> String
$cshow :: HPOConfig -> String
showsPrec :: Int -> HPOConfig -> ShowS
$cshowsPrec :: Int -> HPOConfig -> ShowS
Prelude.Show, forall x. Rep HPOConfig x -> HPOConfig
forall x. HPOConfig -> Rep HPOConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HPOConfig x -> HPOConfig
$cfrom :: forall x. HPOConfig -> Rep HPOConfig x
Prelude.Generic)

-- |
-- Create a value of 'HPOConfig' 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:
--
-- 'algorithmHyperParameterRanges', 'hPOConfig_algorithmHyperParameterRanges' - The hyperparameters and their allowable ranges.
--
-- 'hpoObjective', 'hPOConfig_hpoObjective' - The metric to optimize during HPO.
--
-- Amazon Personalize doesn\'t support configuring the @hpoObjective@ at
-- this time.
--
-- 'hpoResourceConfig', 'hPOConfig_hpoResourceConfig' - Describes the resource configuration for HPO.
newHPOConfig ::
  HPOConfig
newHPOConfig :: HPOConfig
newHPOConfig =
  HPOConfig'
    { $sel:algorithmHyperParameterRanges:HPOConfig' :: Maybe HyperParameterRanges
algorithmHyperParameterRanges =
        forall a. Maybe a
Prelude.Nothing,
      $sel:hpoObjective:HPOConfig' :: Maybe HPOObjective
hpoObjective = forall a. Maybe a
Prelude.Nothing,
      $sel:hpoResourceConfig:HPOConfig' :: Maybe HPOResourceConfig
hpoResourceConfig = forall a. Maybe a
Prelude.Nothing
    }

-- | The hyperparameters and their allowable ranges.
hPOConfig_algorithmHyperParameterRanges :: Lens.Lens' HPOConfig (Prelude.Maybe HyperParameterRanges)
hPOConfig_algorithmHyperParameterRanges :: Lens' HPOConfig (Maybe HyperParameterRanges)
hPOConfig_algorithmHyperParameterRanges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HPOConfig' {Maybe HyperParameterRanges
algorithmHyperParameterRanges :: Maybe HyperParameterRanges
$sel:algorithmHyperParameterRanges:HPOConfig' :: HPOConfig -> Maybe HyperParameterRanges
algorithmHyperParameterRanges} -> Maybe HyperParameterRanges
algorithmHyperParameterRanges) (\s :: HPOConfig
s@HPOConfig' {} Maybe HyperParameterRanges
a -> HPOConfig
s {$sel:algorithmHyperParameterRanges:HPOConfig' :: Maybe HyperParameterRanges
algorithmHyperParameterRanges = Maybe HyperParameterRanges
a} :: HPOConfig)

-- | The metric to optimize during HPO.
--
-- Amazon Personalize doesn\'t support configuring the @hpoObjective@ at
-- this time.
hPOConfig_hpoObjective :: Lens.Lens' HPOConfig (Prelude.Maybe HPOObjective)
hPOConfig_hpoObjective :: Lens' HPOConfig (Maybe HPOObjective)
hPOConfig_hpoObjective = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HPOConfig' {Maybe HPOObjective
hpoObjective :: Maybe HPOObjective
$sel:hpoObjective:HPOConfig' :: HPOConfig -> Maybe HPOObjective
hpoObjective} -> Maybe HPOObjective
hpoObjective) (\s :: HPOConfig
s@HPOConfig' {} Maybe HPOObjective
a -> HPOConfig
s {$sel:hpoObjective:HPOConfig' :: Maybe HPOObjective
hpoObjective = Maybe HPOObjective
a} :: HPOConfig)

-- | Describes the resource configuration for HPO.
hPOConfig_hpoResourceConfig :: Lens.Lens' HPOConfig (Prelude.Maybe HPOResourceConfig)
hPOConfig_hpoResourceConfig :: Lens' HPOConfig (Maybe HPOResourceConfig)
hPOConfig_hpoResourceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HPOConfig' {Maybe HPOResourceConfig
hpoResourceConfig :: Maybe HPOResourceConfig
$sel:hpoResourceConfig:HPOConfig' :: HPOConfig -> Maybe HPOResourceConfig
hpoResourceConfig} -> Maybe HPOResourceConfig
hpoResourceConfig) (\s :: HPOConfig
s@HPOConfig' {} Maybe HPOResourceConfig
a -> HPOConfig
s {$sel:hpoResourceConfig:HPOConfig' :: Maybe HPOResourceConfig
hpoResourceConfig = Maybe HPOResourceConfig
a} :: HPOConfig)

instance Data.FromJSON HPOConfig where
  parseJSON :: Value -> Parser HPOConfig
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HPOConfig"
      ( \Object
x ->
          Maybe HyperParameterRanges
-> Maybe HPOObjective -> Maybe HPOResourceConfig -> HPOConfig
HPOConfig'
            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
"algorithmHyperParameterRanges")
            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
"hpoObjective")
            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
"hpoResourceConfig")
      )

instance Prelude.Hashable HPOConfig where
  hashWithSalt :: Int -> HPOConfig -> Int
hashWithSalt Int
_salt HPOConfig' {Maybe HPOObjective
Maybe HPOResourceConfig
Maybe HyperParameterRanges
hpoResourceConfig :: Maybe HPOResourceConfig
hpoObjective :: Maybe HPOObjective
algorithmHyperParameterRanges :: Maybe HyperParameterRanges
$sel:hpoResourceConfig:HPOConfig' :: HPOConfig -> Maybe HPOResourceConfig
$sel:hpoObjective:HPOConfig' :: HPOConfig -> Maybe HPOObjective
$sel:algorithmHyperParameterRanges:HPOConfig' :: HPOConfig -> Maybe HyperParameterRanges
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HyperParameterRanges
algorithmHyperParameterRanges
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HPOObjective
hpoObjective
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HPOResourceConfig
hpoResourceConfig

instance Prelude.NFData HPOConfig where
  rnf :: HPOConfig -> ()
rnf HPOConfig' {Maybe HPOObjective
Maybe HPOResourceConfig
Maybe HyperParameterRanges
hpoResourceConfig :: Maybe HPOResourceConfig
hpoObjective :: Maybe HPOObjective
algorithmHyperParameterRanges :: Maybe HyperParameterRanges
$sel:hpoResourceConfig:HPOConfig' :: HPOConfig -> Maybe HPOResourceConfig
$sel:hpoObjective:HPOConfig' :: HPOConfig -> Maybe HPOObjective
$sel:algorithmHyperParameterRanges:HPOConfig' :: HPOConfig -> Maybe HyperParameterRanges
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe HyperParameterRanges
algorithmHyperParameterRanges
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HPOObjective
hpoObjective
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HPOResourceConfig
hpoResourceConfig

instance Data.ToJSON HPOConfig where
  toJSON :: HPOConfig -> Value
toJSON HPOConfig' {Maybe HPOObjective
Maybe HPOResourceConfig
Maybe HyperParameterRanges
hpoResourceConfig :: Maybe HPOResourceConfig
hpoObjective :: Maybe HPOObjective
algorithmHyperParameterRanges :: Maybe HyperParameterRanges
$sel:hpoResourceConfig:HPOConfig' :: HPOConfig -> Maybe HPOResourceConfig
$sel:hpoObjective:HPOConfig' :: HPOConfig -> Maybe HPOObjective
$sel:algorithmHyperParameterRanges:HPOConfig' :: HPOConfig -> Maybe HyperParameterRanges
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"algorithmHyperParameterRanges" 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 HyperParameterRanges
algorithmHyperParameterRanges,
            (Key
"hpoObjective" 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 HPOObjective
hpoObjective,
            (Key
"hpoResourceConfig" 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 HPOResourceConfig
hpoResourceConfig
          ]
      )