{-# 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.SageMaker.Types.ResolvedAttributes
-- 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.SageMaker.Types.ResolvedAttributes 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
import Amazonka.SageMaker.Types.AutoMLJobCompletionCriteria
import Amazonka.SageMaker.Types.AutoMLJobObjective
import Amazonka.SageMaker.Types.ProblemType

-- | The resolved attributes.
--
-- /See:/ 'newResolvedAttributes' smart constructor.
data ResolvedAttributes = ResolvedAttributes'
  { ResolvedAttributes -> Maybe AutoMLJobObjective
autoMLJobObjective :: Prelude.Maybe AutoMLJobObjective,
    ResolvedAttributes -> Maybe AutoMLJobCompletionCriteria
completionCriteria :: Prelude.Maybe AutoMLJobCompletionCriteria,
    -- | The problem type.
    ResolvedAttributes -> Maybe ProblemType
problemType :: Prelude.Maybe ProblemType
  }
  deriving (ResolvedAttributes -> ResolvedAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResolvedAttributes -> ResolvedAttributes -> Bool
$c/= :: ResolvedAttributes -> ResolvedAttributes -> Bool
== :: ResolvedAttributes -> ResolvedAttributes -> Bool
$c== :: ResolvedAttributes -> ResolvedAttributes -> Bool
Prelude.Eq, ReadPrec [ResolvedAttributes]
ReadPrec ResolvedAttributes
Int -> ReadS ResolvedAttributes
ReadS [ResolvedAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResolvedAttributes]
$creadListPrec :: ReadPrec [ResolvedAttributes]
readPrec :: ReadPrec ResolvedAttributes
$creadPrec :: ReadPrec ResolvedAttributes
readList :: ReadS [ResolvedAttributes]
$creadList :: ReadS [ResolvedAttributes]
readsPrec :: Int -> ReadS ResolvedAttributes
$creadsPrec :: Int -> ReadS ResolvedAttributes
Prelude.Read, Int -> ResolvedAttributes -> ShowS
[ResolvedAttributes] -> ShowS
ResolvedAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolvedAttributes] -> ShowS
$cshowList :: [ResolvedAttributes] -> ShowS
show :: ResolvedAttributes -> String
$cshow :: ResolvedAttributes -> String
showsPrec :: Int -> ResolvedAttributes -> ShowS
$cshowsPrec :: Int -> ResolvedAttributes -> ShowS
Prelude.Show, forall x. Rep ResolvedAttributes x -> ResolvedAttributes
forall x. ResolvedAttributes -> Rep ResolvedAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResolvedAttributes x -> ResolvedAttributes
$cfrom :: forall x. ResolvedAttributes -> Rep ResolvedAttributes x
Prelude.Generic)

-- |
-- Create a value of 'ResolvedAttributes' 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:
--
-- 'autoMLJobObjective', 'resolvedAttributes_autoMLJobObjective' - Undocumented member.
--
-- 'completionCriteria', 'resolvedAttributes_completionCriteria' - Undocumented member.
--
-- 'problemType', 'resolvedAttributes_problemType' - The problem type.
newResolvedAttributes ::
  ResolvedAttributes
newResolvedAttributes :: ResolvedAttributes
newResolvedAttributes =
  ResolvedAttributes'
    { $sel:autoMLJobObjective:ResolvedAttributes' :: Maybe AutoMLJobObjective
autoMLJobObjective =
        forall a. Maybe a
Prelude.Nothing,
      $sel:completionCriteria:ResolvedAttributes' :: Maybe AutoMLJobCompletionCriteria
completionCriteria = forall a. Maybe a
Prelude.Nothing,
      $sel:problemType:ResolvedAttributes' :: Maybe ProblemType
problemType = forall a. Maybe a
Prelude.Nothing
    }

-- | Undocumented member.
resolvedAttributes_autoMLJobObjective :: Lens.Lens' ResolvedAttributes (Prelude.Maybe AutoMLJobObjective)
resolvedAttributes_autoMLJobObjective :: Lens' ResolvedAttributes (Maybe AutoMLJobObjective)
resolvedAttributes_autoMLJobObjective = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolvedAttributes' {Maybe AutoMLJobObjective
autoMLJobObjective :: Maybe AutoMLJobObjective
$sel:autoMLJobObjective:ResolvedAttributes' :: ResolvedAttributes -> Maybe AutoMLJobObjective
autoMLJobObjective} -> Maybe AutoMLJobObjective
autoMLJobObjective) (\s :: ResolvedAttributes
s@ResolvedAttributes' {} Maybe AutoMLJobObjective
a -> ResolvedAttributes
s {$sel:autoMLJobObjective:ResolvedAttributes' :: Maybe AutoMLJobObjective
autoMLJobObjective = Maybe AutoMLJobObjective
a} :: ResolvedAttributes)

-- | Undocumented member.
resolvedAttributes_completionCriteria :: Lens.Lens' ResolvedAttributes (Prelude.Maybe AutoMLJobCompletionCriteria)
resolvedAttributes_completionCriteria :: Lens' ResolvedAttributes (Maybe AutoMLJobCompletionCriteria)
resolvedAttributes_completionCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolvedAttributes' {Maybe AutoMLJobCompletionCriteria
completionCriteria :: Maybe AutoMLJobCompletionCriteria
$sel:completionCriteria:ResolvedAttributes' :: ResolvedAttributes -> Maybe AutoMLJobCompletionCriteria
completionCriteria} -> Maybe AutoMLJobCompletionCriteria
completionCriteria) (\s :: ResolvedAttributes
s@ResolvedAttributes' {} Maybe AutoMLJobCompletionCriteria
a -> ResolvedAttributes
s {$sel:completionCriteria:ResolvedAttributes' :: Maybe AutoMLJobCompletionCriteria
completionCriteria = Maybe AutoMLJobCompletionCriteria
a} :: ResolvedAttributes)

-- | The problem type.
resolvedAttributes_problemType :: Lens.Lens' ResolvedAttributes (Prelude.Maybe ProblemType)
resolvedAttributes_problemType :: Lens' ResolvedAttributes (Maybe ProblemType)
resolvedAttributes_problemType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ResolvedAttributes' {Maybe ProblemType
problemType :: Maybe ProblemType
$sel:problemType:ResolvedAttributes' :: ResolvedAttributes -> Maybe ProblemType
problemType} -> Maybe ProblemType
problemType) (\s :: ResolvedAttributes
s@ResolvedAttributes' {} Maybe ProblemType
a -> ResolvedAttributes
s {$sel:problemType:ResolvedAttributes' :: Maybe ProblemType
problemType = Maybe ProblemType
a} :: ResolvedAttributes)

instance Data.FromJSON ResolvedAttributes where
  parseJSON :: Value -> Parser ResolvedAttributes
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ResolvedAttributes"
      ( \Object
x ->
          Maybe AutoMLJobObjective
-> Maybe AutoMLJobCompletionCriteria
-> Maybe ProblemType
-> ResolvedAttributes
ResolvedAttributes'
            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
"AutoMLJobObjective")
            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
"CompletionCriteria")
            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
"ProblemType")
      )

instance Prelude.Hashable ResolvedAttributes where
  hashWithSalt :: Int -> ResolvedAttributes -> Int
hashWithSalt Int
_salt ResolvedAttributes' {Maybe AutoMLJobCompletionCriteria
Maybe AutoMLJobObjective
Maybe ProblemType
problemType :: Maybe ProblemType
completionCriteria :: Maybe AutoMLJobCompletionCriteria
autoMLJobObjective :: Maybe AutoMLJobObjective
$sel:problemType:ResolvedAttributes' :: ResolvedAttributes -> Maybe ProblemType
$sel:completionCriteria:ResolvedAttributes' :: ResolvedAttributes -> Maybe AutoMLJobCompletionCriteria
$sel:autoMLJobObjective:ResolvedAttributes' :: ResolvedAttributes -> Maybe AutoMLJobObjective
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutoMLJobObjective
autoMLJobObjective
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutoMLJobCompletionCriteria
completionCriteria
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProblemType
problemType

instance Prelude.NFData ResolvedAttributes where
  rnf :: ResolvedAttributes -> ()
rnf ResolvedAttributes' {Maybe AutoMLJobCompletionCriteria
Maybe AutoMLJobObjective
Maybe ProblemType
problemType :: Maybe ProblemType
completionCriteria :: Maybe AutoMLJobCompletionCriteria
autoMLJobObjective :: Maybe AutoMLJobObjective
$sel:problemType:ResolvedAttributes' :: ResolvedAttributes -> Maybe ProblemType
$sel:completionCriteria:ResolvedAttributes' :: ResolvedAttributes -> Maybe AutoMLJobCompletionCriteria
$sel:autoMLJobObjective:ResolvedAttributes' :: ResolvedAttributes -> Maybe AutoMLJobObjective
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoMLJobObjective
autoMLJobObjective
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoMLJobCompletionCriteria
completionCriteria
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProblemType
problemType