{-# 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 #-}
module Amazonka.SageMaker.DescribeAutoMLJob
  ( 
    DescribeAutoMLJob (..),
    newDescribeAutoMLJob,
    
    describeAutoMLJob_autoMLJobName,
    
    DescribeAutoMLJobResponse (..),
    newDescribeAutoMLJobResponse,
    
    describeAutoMLJobResponse_autoMLJobArtifacts,
    describeAutoMLJobResponse_autoMLJobConfig,
    describeAutoMLJobResponse_autoMLJobObjective,
    describeAutoMLJobResponse_bestCandidate,
    describeAutoMLJobResponse_endTime,
    describeAutoMLJobResponse_failureReason,
    describeAutoMLJobResponse_generateCandidateDefinitionsOnly,
    describeAutoMLJobResponse_modelDeployConfig,
    describeAutoMLJobResponse_modelDeployResult,
    describeAutoMLJobResponse_partialFailureReasons,
    describeAutoMLJobResponse_problemType,
    describeAutoMLJobResponse_resolvedAttributes,
    describeAutoMLJobResponse_httpStatus,
    describeAutoMLJobResponse_autoMLJobName,
    describeAutoMLJobResponse_autoMLJobArn,
    describeAutoMLJobResponse_inputDataConfig,
    describeAutoMLJobResponse_outputDataConfig,
    describeAutoMLJobResponse_roleArn,
    describeAutoMLJobResponse_creationTime,
    describeAutoMLJobResponse_lastModifiedTime,
    describeAutoMLJobResponse_autoMLJobStatus,
    describeAutoMLJobResponse_autoMLJobSecondaryStatus,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMaker.Types
data DescribeAutoMLJob = DescribeAutoMLJob'
  { 
    DescribeAutoMLJob -> Text
autoMLJobName :: Prelude.Text
  }
  deriving (DescribeAutoMLJob -> DescribeAutoMLJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAutoMLJob -> DescribeAutoMLJob -> Bool
$c/= :: DescribeAutoMLJob -> DescribeAutoMLJob -> Bool
== :: DescribeAutoMLJob -> DescribeAutoMLJob -> Bool
$c== :: DescribeAutoMLJob -> DescribeAutoMLJob -> Bool
Prelude.Eq, ReadPrec [DescribeAutoMLJob]
ReadPrec DescribeAutoMLJob
Int -> ReadS DescribeAutoMLJob
ReadS [DescribeAutoMLJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAutoMLJob]
$creadListPrec :: ReadPrec [DescribeAutoMLJob]
readPrec :: ReadPrec DescribeAutoMLJob
$creadPrec :: ReadPrec DescribeAutoMLJob
readList :: ReadS [DescribeAutoMLJob]
$creadList :: ReadS [DescribeAutoMLJob]
readsPrec :: Int -> ReadS DescribeAutoMLJob
$creadsPrec :: Int -> ReadS DescribeAutoMLJob
Prelude.Read, Int -> DescribeAutoMLJob -> ShowS
[DescribeAutoMLJob] -> ShowS
DescribeAutoMLJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAutoMLJob] -> ShowS
$cshowList :: [DescribeAutoMLJob] -> ShowS
show :: DescribeAutoMLJob -> String
$cshow :: DescribeAutoMLJob -> String
showsPrec :: Int -> DescribeAutoMLJob -> ShowS
$cshowsPrec :: Int -> DescribeAutoMLJob -> ShowS
Prelude.Show, forall x. Rep DescribeAutoMLJob x -> DescribeAutoMLJob
forall x. DescribeAutoMLJob -> Rep DescribeAutoMLJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAutoMLJob x -> DescribeAutoMLJob
$cfrom :: forall x. DescribeAutoMLJob -> Rep DescribeAutoMLJob x
Prelude.Generic)
newDescribeAutoMLJob ::
  
  Prelude.Text ->
  DescribeAutoMLJob
newDescribeAutoMLJob :: Text -> DescribeAutoMLJob
newDescribeAutoMLJob Text
pAutoMLJobName_ =
  DescribeAutoMLJob' {$sel:autoMLJobName:DescribeAutoMLJob' :: Text
autoMLJobName = Text
pAutoMLJobName_}
describeAutoMLJob_autoMLJobName :: Lens.Lens' DescribeAutoMLJob Prelude.Text
describeAutoMLJob_autoMLJobName :: Lens' DescribeAutoMLJob Text
describeAutoMLJob_autoMLJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJob' {Text
autoMLJobName :: Text
$sel:autoMLJobName:DescribeAutoMLJob' :: DescribeAutoMLJob -> Text
autoMLJobName} -> Text
autoMLJobName) (\s :: DescribeAutoMLJob
s@DescribeAutoMLJob' {} Text
a -> DescribeAutoMLJob
s {$sel:autoMLJobName:DescribeAutoMLJob' :: Text
autoMLJobName = Text
a} :: DescribeAutoMLJob)
instance Core.AWSRequest DescribeAutoMLJob where
  type
    AWSResponse DescribeAutoMLJob =
      DescribeAutoMLJobResponse
  request :: (Service -> Service)
-> DescribeAutoMLJob -> Request DescribeAutoMLJob
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 DescribeAutoMLJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAutoMLJob)))
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 AutoMLJobArtifacts
-> Maybe AutoMLJobConfig
-> Maybe AutoMLJobObjective
-> Maybe AutoMLCandidate
-> Maybe POSIX
-> Maybe Text
-> Maybe Bool
-> Maybe ModelDeployConfig
-> Maybe ModelDeployResult
-> Maybe (NonEmpty AutoMLPartialFailureReason)
-> Maybe ProblemType
-> Maybe ResolvedAttributes
-> Int
-> Text
-> Text
-> NonEmpty AutoMLChannel
-> AutoMLOutputDataConfig
-> Text
-> POSIX
-> POSIX
-> AutoMLJobStatus
-> AutoMLJobSecondaryStatus
-> DescribeAutoMLJobResponse
DescribeAutoMLJobResponse'
            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
"AutoMLJobArtifacts")
            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
"AutoMLJobConfig")
            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
"AutoMLJobObjective")
            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
"BestCandidate")
            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
"EndTime")
            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
"GenerateCandidateDefinitionsOnly")
            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
"ModelDeployConfig")
            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
"ModelDeployResult")
            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
"PartialFailureReasons")
            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
"ProblemType")
            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
"ResolvedAttributes")
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"AutoMLJobName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"AutoMLJobArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"InputDataConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"OutputDataConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 a
Data..:> Key
"CreationTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"LastModifiedTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"AutoMLJobStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"AutoMLJobSecondaryStatus")
      )
instance Prelude.Hashable DescribeAutoMLJob where
  hashWithSalt :: Int -> DescribeAutoMLJob -> Int
hashWithSalt Int
_salt DescribeAutoMLJob' {Text
autoMLJobName :: Text
$sel:autoMLJobName:DescribeAutoMLJob' :: DescribeAutoMLJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoMLJobName
instance Prelude.NFData DescribeAutoMLJob where
  rnf :: DescribeAutoMLJob -> ()
rnf DescribeAutoMLJob' {Text
autoMLJobName :: Text
$sel:autoMLJobName:DescribeAutoMLJob' :: DescribeAutoMLJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
autoMLJobName
instance Data.ToHeaders DescribeAutoMLJob where
  toHeaders :: DescribeAutoMLJob -> 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
"SageMaker.DescribeAutoMLJob" ::
                          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 DescribeAutoMLJob where
  toJSON :: DescribeAutoMLJob -> Value
toJSON DescribeAutoMLJob' {Text
autoMLJobName :: Text
$sel:autoMLJobName:DescribeAutoMLJob' :: DescribeAutoMLJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"AutoMLJobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
autoMLJobName)
          ]
      )
instance Data.ToPath DescribeAutoMLJob where
  toPath :: DescribeAutoMLJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DescribeAutoMLJob where
  toQuery :: DescribeAutoMLJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data DescribeAutoMLJobResponse = DescribeAutoMLJobResponse'
  { 
    
    DescribeAutoMLJobResponse -> Maybe AutoMLJobArtifacts
autoMLJobArtifacts :: Prelude.Maybe AutoMLJobArtifacts,
    
    DescribeAutoMLJobResponse -> Maybe AutoMLJobConfig
autoMLJobConfig :: Prelude.Maybe AutoMLJobConfig,
    
    DescribeAutoMLJobResponse -> Maybe AutoMLJobObjective
autoMLJobObjective :: Prelude.Maybe AutoMLJobObjective,
    
    
    
    
    DescribeAutoMLJobResponse -> Maybe AutoMLCandidate
bestCandidate :: Prelude.Maybe AutoMLCandidate,
    
    DescribeAutoMLJobResponse -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    
    DescribeAutoMLJobResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    
    
    DescribeAutoMLJobResponse -> Maybe Bool
generateCandidateDefinitionsOnly :: Prelude.Maybe Prelude.Bool,
    
    
    DescribeAutoMLJobResponse -> Maybe ModelDeployConfig
modelDeployConfig :: Prelude.Maybe ModelDeployConfig,
    
    DescribeAutoMLJobResponse -> Maybe ModelDeployResult
modelDeployResult :: Prelude.Maybe ModelDeployResult,
    
    DescribeAutoMLJobResponse
-> Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons :: Prelude.Maybe (Prelude.NonEmpty AutoMLPartialFailureReason),
    
    DescribeAutoMLJobResponse -> Maybe ProblemType
problemType :: Prelude.Maybe ProblemType,
    
    
    
    
    DescribeAutoMLJobResponse -> Maybe ResolvedAttributes
resolvedAttributes :: Prelude.Maybe ResolvedAttributes,
    
    DescribeAutoMLJobResponse -> Int
httpStatus :: Prelude.Int,
    
    DescribeAutoMLJobResponse -> Text
autoMLJobName :: Prelude.Text,
    
    DescribeAutoMLJobResponse -> Text
autoMLJobArn :: Prelude.Text,
    
    DescribeAutoMLJobResponse -> NonEmpty AutoMLChannel
inputDataConfig :: Prelude.NonEmpty AutoMLChannel,
    
    DescribeAutoMLJobResponse -> AutoMLOutputDataConfig
outputDataConfig :: AutoMLOutputDataConfig,
    
    
    
    DescribeAutoMLJobResponse -> Text
roleArn :: Prelude.Text,
    
    DescribeAutoMLJobResponse -> POSIX
creationTime :: Data.POSIX,
    
    DescribeAutoMLJobResponse -> POSIX
lastModifiedTime :: Data.POSIX,
    
    DescribeAutoMLJobResponse -> AutoMLJobStatus
autoMLJobStatus :: AutoMLJobStatus,
    
    DescribeAutoMLJobResponse -> AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus
  }
  deriving (DescribeAutoMLJobResponse -> DescribeAutoMLJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAutoMLJobResponse -> DescribeAutoMLJobResponse -> Bool
$c/= :: DescribeAutoMLJobResponse -> DescribeAutoMLJobResponse -> Bool
== :: DescribeAutoMLJobResponse -> DescribeAutoMLJobResponse -> Bool
$c== :: DescribeAutoMLJobResponse -> DescribeAutoMLJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAutoMLJobResponse]
ReadPrec DescribeAutoMLJobResponse
Int -> ReadS DescribeAutoMLJobResponse
ReadS [DescribeAutoMLJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAutoMLJobResponse]
$creadListPrec :: ReadPrec [DescribeAutoMLJobResponse]
readPrec :: ReadPrec DescribeAutoMLJobResponse
$creadPrec :: ReadPrec DescribeAutoMLJobResponse
readList :: ReadS [DescribeAutoMLJobResponse]
$creadList :: ReadS [DescribeAutoMLJobResponse]
readsPrec :: Int -> ReadS DescribeAutoMLJobResponse
$creadsPrec :: Int -> ReadS DescribeAutoMLJobResponse
Prelude.Read, Int -> DescribeAutoMLJobResponse -> ShowS
[DescribeAutoMLJobResponse] -> ShowS
DescribeAutoMLJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAutoMLJobResponse] -> ShowS
$cshowList :: [DescribeAutoMLJobResponse] -> ShowS
show :: DescribeAutoMLJobResponse -> String
$cshow :: DescribeAutoMLJobResponse -> String
showsPrec :: Int -> DescribeAutoMLJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeAutoMLJobResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAutoMLJobResponse x -> DescribeAutoMLJobResponse
forall x.
DescribeAutoMLJobResponse -> Rep DescribeAutoMLJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAutoMLJobResponse x -> DescribeAutoMLJobResponse
$cfrom :: forall x.
DescribeAutoMLJobResponse -> Rep DescribeAutoMLJobResponse x
Prelude.Generic)
newDescribeAutoMLJobResponse ::
  
  Prelude.Int ->
  
  Prelude.Text ->
  
  Prelude.Text ->
  
  Prelude.NonEmpty AutoMLChannel ->
  
  AutoMLOutputDataConfig ->
  
  Prelude.Text ->
  
  Prelude.UTCTime ->
  
  Prelude.UTCTime ->
  
  AutoMLJobStatus ->
  
  AutoMLJobSecondaryStatus ->
  DescribeAutoMLJobResponse
newDescribeAutoMLJobResponse :: Int
-> Text
-> Text
-> NonEmpty AutoMLChannel
-> AutoMLOutputDataConfig
-> Text
-> UTCTime
-> UTCTime
-> AutoMLJobStatus
-> AutoMLJobSecondaryStatus
-> DescribeAutoMLJobResponse
newDescribeAutoMLJobResponse
  Int
pHttpStatus_
  Text
pAutoMLJobName_
  Text
pAutoMLJobArn_
  NonEmpty AutoMLChannel
pInputDataConfig_
  AutoMLOutputDataConfig
pOutputDataConfig_
  Text
pRoleArn_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_
  AutoMLJobStatus
pAutoMLJobStatus_
  AutoMLJobSecondaryStatus
pAutoMLJobSecondaryStatus_ =
    DescribeAutoMLJobResponse'
      { $sel:autoMLJobArtifacts:DescribeAutoMLJobResponse' :: Maybe AutoMLJobArtifacts
autoMLJobArtifacts =
          forall a. Maybe a
Prelude.Nothing,
        $sel:autoMLJobConfig:DescribeAutoMLJobResponse' :: Maybe AutoMLJobConfig
autoMLJobConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:autoMLJobObjective:DescribeAutoMLJobResponse' :: Maybe AutoMLJobObjective
autoMLJobObjective = forall a. Maybe a
Prelude.Nothing,
        $sel:bestCandidate:DescribeAutoMLJobResponse' :: Maybe AutoMLCandidate
bestCandidate = forall a. Maybe a
Prelude.Nothing,
        $sel:endTime:DescribeAutoMLJobResponse' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:DescribeAutoMLJobResponse' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:generateCandidateDefinitionsOnly:DescribeAutoMLJobResponse' :: Maybe Bool
generateCandidateDefinitionsOnly =
          forall a. Maybe a
Prelude.Nothing,
        $sel:modelDeployConfig:DescribeAutoMLJobResponse' :: Maybe ModelDeployConfig
modelDeployConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:modelDeployResult:DescribeAutoMLJobResponse' :: Maybe ModelDeployResult
modelDeployResult = forall a. Maybe a
Prelude.Nothing,
        $sel:partialFailureReasons:DescribeAutoMLJobResponse' :: Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons = forall a. Maybe a
Prelude.Nothing,
        $sel:problemType:DescribeAutoMLJobResponse' :: Maybe ProblemType
problemType = forall a. Maybe a
Prelude.Nothing,
        $sel:resolvedAttributes:DescribeAutoMLJobResponse' :: Maybe ResolvedAttributes
resolvedAttributes = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeAutoMLJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:autoMLJobName:DescribeAutoMLJobResponse' :: Text
autoMLJobName = Text
pAutoMLJobName_,
        $sel:autoMLJobArn:DescribeAutoMLJobResponse' :: Text
autoMLJobArn = Text
pAutoMLJobArn_,
        $sel:inputDataConfig:DescribeAutoMLJobResponse' :: NonEmpty AutoMLChannel
inputDataConfig =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty AutoMLChannel
pInputDataConfig_,
        $sel:outputDataConfig:DescribeAutoMLJobResponse' :: AutoMLOutputDataConfig
outputDataConfig = AutoMLOutputDataConfig
pOutputDataConfig_,
        $sel:roleArn:DescribeAutoMLJobResponse' :: Text
roleArn = Text
pRoleArn_,
        $sel:creationTime:DescribeAutoMLJobResponse' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:DescribeAutoMLJobResponse' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_,
        $sel:autoMLJobStatus:DescribeAutoMLJobResponse' :: AutoMLJobStatus
autoMLJobStatus = AutoMLJobStatus
pAutoMLJobStatus_,
        $sel:autoMLJobSecondaryStatus:DescribeAutoMLJobResponse' :: AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus =
          AutoMLJobSecondaryStatus
pAutoMLJobSecondaryStatus_
      }
describeAutoMLJobResponse_autoMLJobArtifacts :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe AutoMLJobArtifacts)
describeAutoMLJobResponse_autoMLJobArtifacts :: Lens' DescribeAutoMLJobResponse (Maybe AutoMLJobArtifacts)
describeAutoMLJobResponse_autoMLJobArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe AutoMLJobArtifacts
autoMLJobArtifacts :: Maybe AutoMLJobArtifacts
$sel:autoMLJobArtifacts:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLJobArtifacts
autoMLJobArtifacts} -> Maybe AutoMLJobArtifacts
autoMLJobArtifacts) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe AutoMLJobArtifacts
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobArtifacts:DescribeAutoMLJobResponse' :: Maybe AutoMLJobArtifacts
autoMLJobArtifacts = Maybe AutoMLJobArtifacts
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_autoMLJobConfig :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe AutoMLJobConfig)
describeAutoMLJobResponse_autoMLJobConfig :: Lens' DescribeAutoMLJobResponse (Maybe AutoMLJobConfig)
describeAutoMLJobResponse_autoMLJobConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe AutoMLJobConfig
autoMLJobConfig :: Maybe AutoMLJobConfig
$sel:autoMLJobConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLJobConfig
autoMLJobConfig} -> Maybe AutoMLJobConfig
autoMLJobConfig) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe AutoMLJobConfig
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobConfig:DescribeAutoMLJobResponse' :: Maybe AutoMLJobConfig
autoMLJobConfig = Maybe AutoMLJobConfig
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_autoMLJobObjective :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe AutoMLJobObjective)
describeAutoMLJobResponse_autoMLJobObjective :: Lens' DescribeAutoMLJobResponse (Maybe AutoMLJobObjective)
describeAutoMLJobResponse_autoMLJobObjective = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe AutoMLJobObjective
autoMLJobObjective :: Maybe AutoMLJobObjective
$sel:autoMLJobObjective:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLJobObjective
autoMLJobObjective} -> Maybe AutoMLJobObjective
autoMLJobObjective) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe AutoMLJobObjective
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobObjective:DescribeAutoMLJobResponse' :: Maybe AutoMLJobObjective
autoMLJobObjective = Maybe AutoMLJobObjective
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_bestCandidate :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe AutoMLCandidate)
describeAutoMLJobResponse_bestCandidate :: Lens' DescribeAutoMLJobResponse (Maybe AutoMLCandidate)
describeAutoMLJobResponse_bestCandidate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe AutoMLCandidate
bestCandidate :: Maybe AutoMLCandidate
$sel:bestCandidate:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLCandidate
bestCandidate} -> Maybe AutoMLCandidate
bestCandidate) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe AutoMLCandidate
a -> DescribeAutoMLJobResponse
s {$sel:bestCandidate:DescribeAutoMLJobResponse' :: Maybe AutoMLCandidate
bestCandidate = Maybe AutoMLCandidate
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_endTime :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe Prelude.UTCTime)
describeAutoMLJobResponse_endTime :: Lens' DescribeAutoMLJobResponse (Maybe UTCTime)
describeAutoMLJobResponse_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe POSIX
a -> DescribeAutoMLJobResponse
s {$sel:endTime:DescribeAutoMLJobResponse' :: Maybe POSIX
endTime = Maybe POSIX
a} :: DescribeAutoMLJobResponse) 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
describeAutoMLJobResponse_failureReason :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe Prelude.Text)
describeAutoMLJobResponse_failureReason :: Lens' DescribeAutoMLJobResponse (Maybe Text)
describeAutoMLJobResponse_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe Text
a -> DescribeAutoMLJobResponse
s {$sel:failureReason:DescribeAutoMLJobResponse' :: Maybe Text
failureReason = Maybe Text
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_generateCandidateDefinitionsOnly :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe Prelude.Bool)
describeAutoMLJobResponse_generateCandidateDefinitionsOnly :: Lens' DescribeAutoMLJobResponse (Maybe Bool)
describeAutoMLJobResponse_generateCandidateDefinitionsOnly = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe Bool
generateCandidateDefinitionsOnly :: Maybe Bool
$sel:generateCandidateDefinitionsOnly:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe Bool
generateCandidateDefinitionsOnly} -> Maybe Bool
generateCandidateDefinitionsOnly) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe Bool
a -> DescribeAutoMLJobResponse
s {$sel:generateCandidateDefinitionsOnly:DescribeAutoMLJobResponse' :: Maybe Bool
generateCandidateDefinitionsOnly = Maybe Bool
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_modelDeployConfig :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe ModelDeployConfig)
describeAutoMLJobResponse_modelDeployConfig :: Lens' DescribeAutoMLJobResponse (Maybe ModelDeployConfig)
describeAutoMLJobResponse_modelDeployConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe ModelDeployConfig
modelDeployConfig :: Maybe ModelDeployConfig
$sel:modelDeployConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ModelDeployConfig
modelDeployConfig} -> Maybe ModelDeployConfig
modelDeployConfig) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe ModelDeployConfig
a -> DescribeAutoMLJobResponse
s {$sel:modelDeployConfig:DescribeAutoMLJobResponse' :: Maybe ModelDeployConfig
modelDeployConfig = Maybe ModelDeployConfig
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_modelDeployResult :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe ModelDeployResult)
describeAutoMLJobResponse_modelDeployResult :: Lens' DescribeAutoMLJobResponse (Maybe ModelDeployResult)
describeAutoMLJobResponse_modelDeployResult = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe ModelDeployResult
modelDeployResult :: Maybe ModelDeployResult
$sel:modelDeployResult:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ModelDeployResult
modelDeployResult} -> Maybe ModelDeployResult
modelDeployResult) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe ModelDeployResult
a -> DescribeAutoMLJobResponse
s {$sel:modelDeployResult:DescribeAutoMLJobResponse' :: Maybe ModelDeployResult
modelDeployResult = Maybe ModelDeployResult
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_partialFailureReasons :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe (Prelude.NonEmpty AutoMLPartialFailureReason))
describeAutoMLJobResponse_partialFailureReasons :: Lens'
  DescribeAutoMLJobResponse
  (Maybe (NonEmpty AutoMLPartialFailureReason))
describeAutoMLJobResponse_partialFailureReasons = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons :: Maybe (NonEmpty AutoMLPartialFailureReason)
$sel:partialFailureReasons:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse
-> Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons} -> Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe (NonEmpty AutoMLPartialFailureReason)
a -> DescribeAutoMLJobResponse
s {$sel:partialFailureReasons:DescribeAutoMLJobResponse' :: Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons = Maybe (NonEmpty AutoMLPartialFailureReason)
a} :: DescribeAutoMLJobResponse) 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
describeAutoMLJobResponse_problemType :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe ProblemType)
describeAutoMLJobResponse_problemType :: Lens' DescribeAutoMLJobResponse (Maybe ProblemType)
describeAutoMLJobResponse_problemType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe ProblemType
problemType :: Maybe ProblemType
$sel:problemType:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ProblemType
problemType} -> Maybe ProblemType
problemType) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe ProblemType
a -> DescribeAutoMLJobResponse
s {$sel:problemType:DescribeAutoMLJobResponse' :: Maybe ProblemType
problemType = Maybe ProblemType
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_resolvedAttributes :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.Maybe ResolvedAttributes)
describeAutoMLJobResponse_resolvedAttributes :: Lens' DescribeAutoMLJobResponse (Maybe ResolvedAttributes)
describeAutoMLJobResponse_resolvedAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Maybe ResolvedAttributes
resolvedAttributes :: Maybe ResolvedAttributes
$sel:resolvedAttributes:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ResolvedAttributes
resolvedAttributes} -> Maybe ResolvedAttributes
resolvedAttributes) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Maybe ResolvedAttributes
a -> DescribeAutoMLJobResponse
s {$sel:resolvedAttributes:DescribeAutoMLJobResponse' :: Maybe ResolvedAttributes
resolvedAttributes = Maybe ResolvedAttributes
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_httpStatus :: Lens.Lens' DescribeAutoMLJobResponse Prelude.Int
describeAutoMLJobResponse_httpStatus :: Lens' DescribeAutoMLJobResponse Int
describeAutoMLJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Int
a -> DescribeAutoMLJobResponse
s {$sel:httpStatus:DescribeAutoMLJobResponse' :: Int
httpStatus = Int
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_autoMLJobName :: Lens.Lens' DescribeAutoMLJobResponse Prelude.Text
describeAutoMLJobResponse_autoMLJobName :: Lens' DescribeAutoMLJobResponse Text
describeAutoMLJobResponse_autoMLJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Text
autoMLJobName :: Text
$sel:autoMLJobName:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Text
autoMLJobName} -> Text
autoMLJobName) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Text
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobName:DescribeAutoMLJobResponse' :: Text
autoMLJobName = Text
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_autoMLJobArn :: Lens.Lens' DescribeAutoMLJobResponse Prelude.Text
describeAutoMLJobResponse_autoMLJobArn :: Lens' DescribeAutoMLJobResponse Text
describeAutoMLJobResponse_autoMLJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Text
autoMLJobArn :: Text
$sel:autoMLJobArn:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Text
autoMLJobArn} -> Text
autoMLJobArn) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Text
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobArn:DescribeAutoMLJobResponse' :: Text
autoMLJobArn = Text
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_inputDataConfig :: Lens.Lens' DescribeAutoMLJobResponse (Prelude.NonEmpty AutoMLChannel)
describeAutoMLJobResponse_inputDataConfig :: Lens' DescribeAutoMLJobResponse (NonEmpty AutoMLChannel)
describeAutoMLJobResponse_inputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {NonEmpty AutoMLChannel
inputDataConfig :: NonEmpty AutoMLChannel
$sel:inputDataConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> NonEmpty AutoMLChannel
inputDataConfig} -> NonEmpty AutoMLChannel
inputDataConfig) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} NonEmpty AutoMLChannel
a -> DescribeAutoMLJobResponse
s {$sel:inputDataConfig:DescribeAutoMLJobResponse' :: NonEmpty AutoMLChannel
inputDataConfig = NonEmpty AutoMLChannel
a} :: DescribeAutoMLJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
describeAutoMLJobResponse_outputDataConfig :: Lens.Lens' DescribeAutoMLJobResponse AutoMLOutputDataConfig
describeAutoMLJobResponse_outputDataConfig :: Lens' DescribeAutoMLJobResponse AutoMLOutputDataConfig
describeAutoMLJobResponse_outputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {AutoMLOutputDataConfig
outputDataConfig :: AutoMLOutputDataConfig
$sel:outputDataConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> AutoMLOutputDataConfig
outputDataConfig} -> AutoMLOutputDataConfig
outputDataConfig) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} AutoMLOutputDataConfig
a -> DescribeAutoMLJobResponse
s {$sel:outputDataConfig:DescribeAutoMLJobResponse' :: AutoMLOutputDataConfig
outputDataConfig = AutoMLOutputDataConfig
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_roleArn :: Lens.Lens' DescribeAutoMLJobResponse Prelude.Text
describeAutoMLJobResponse_roleArn :: Lens' DescribeAutoMLJobResponse Text
describeAutoMLJobResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {Text
roleArn :: Text
$sel:roleArn:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Text
roleArn} -> Text
roleArn) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} Text
a -> DescribeAutoMLJobResponse
s {$sel:roleArn:DescribeAutoMLJobResponse' :: Text
roleArn = Text
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_creationTime :: Lens.Lens' DescribeAutoMLJobResponse Prelude.UTCTime
describeAutoMLJobResponse_creationTime :: Lens' DescribeAutoMLJobResponse UTCTime
describeAutoMLJobResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} POSIX
a -> DescribeAutoMLJobResponse
s {$sel:creationTime:DescribeAutoMLJobResponse' :: POSIX
creationTime = POSIX
a} :: DescribeAutoMLJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
describeAutoMLJobResponse_lastModifiedTime :: Lens.Lens' DescribeAutoMLJobResponse Prelude.UTCTime
describeAutoMLJobResponse_lastModifiedTime :: Lens' DescribeAutoMLJobResponse UTCTime
describeAutoMLJobResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} POSIX
a -> DescribeAutoMLJobResponse
s {$sel:lastModifiedTime:DescribeAutoMLJobResponse' :: POSIX
lastModifiedTime = POSIX
a} :: DescribeAutoMLJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
describeAutoMLJobResponse_autoMLJobStatus :: Lens.Lens' DescribeAutoMLJobResponse AutoMLJobStatus
describeAutoMLJobResponse_autoMLJobStatus :: Lens' DescribeAutoMLJobResponse AutoMLJobStatus
describeAutoMLJobResponse_autoMLJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {AutoMLJobStatus
autoMLJobStatus :: AutoMLJobStatus
$sel:autoMLJobStatus:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> AutoMLJobStatus
autoMLJobStatus} -> AutoMLJobStatus
autoMLJobStatus) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} AutoMLJobStatus
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobStatus:DescribeAutoMLJobResponse' :: AutoMLJobStatus
autoMLJobStatus = AutoMLJobStatus
a} :: DescribeAutoMLJobResponse)
describeAutoMLJobResponse_autoMLJobSecondaryStatus :: Lens.Lens' DescribeAutoMLJobResponse AutoMLJobSecondaryStatus
describeAutoMLJobResponse_autoMLJobSecondaryStatus :: Lens' DescribeAutoMLJobResponse AutoMLJobSecondaryStatus
describeAutoMLJobResponse_autoMLJobSecondaryStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoMLJobResponse' {AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus
$sel:autoMLJobSecondaryStatus:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus} -> AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus) (\s :: DescribeAutoMLJobResponse
s@DescribeAutoMLJobResponse' {} AutoMLJobSecondaryStatus
a -> DescribeAutoMLJobResponse
s {$sel:autoMLJobSecondaryStatus:DescribeAutoMLJobResponse' :: AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus = AutoMLJobSecondaryStatus
a} :: DescribeAutoMLJobResponse)
instance Prelude.NFData DescribeAutoMLJobResponse where
  rnf :: DescribeAutoMLJobResponse -> ()
rnf DescribeAutoMLJobResponse' {Int
Maybe Bool
Maybe (NonEmpty AutoMLPartialFailureReason)
Maybe Text
Maybe POSIX
Maybe AutoMLJobArtifacts
Maybe AutoMLJobObjective
Maybe ModelDeployConfig
Maybe ModelDeployResult
Maybe AutoMLCandidate
Maybe ProblemType
Maybe ResolvedAttributes
Maybe AutoMLJobConfig
NonEmpty AutoMLChannel
Text
POSIX
AutoMLJobSecondaryStatus
AutoMLJobStatus
AutoMLOutputDataConfig
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus
autoMLJobStatus :: AutoMLJobStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
roleArn :: Text
outputDataConfig :: AutoMLOutputDataConfig
inputDataConfig :: NonEmpty AutoMLChannel
autoMLJobArn :: Text
autoMLJobName :: Text
httpStatus :: Int
resolvedAttributes :: Maybe ResolvedAttributes
problemType :: Maybe ProblemType
partialFailureReasons :: Maybe (NonEmpty AutoMLPartialFailureReason)
modelDeployResult :: Maybe ModelDeployResult
modelDeployConfig :: Maybe ModelDeployConfig
generateCandidateDefinitionsOnly :: Maybe Bool
failureReason :: Maybe Text
endTime :: Maybe POSIX
bestCandidate :: Maybe AutoMLCandidate
autoMLJobObjective :: Maybe AutoMLJobObjective
autoMLJobConfig :: Maybe AutoMLJobConfig
autoMLJobArtifacts :: Maybe AutoMLJobArtifacts
$sel:autoMLJobSecondaryStatus:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> AutoMLJobSecondaryStatus
$sel:autoMLJobStatus:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> AutoMLJobStatus
$sel:lastModifiedTime:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> POSIX
$sel:creationTime:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> POSIX
$sel:roleArn:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Text
$sel:outputDataConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> AutoMLOutputDataConfig
$sel:inputDataConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> NonEmpty AutoMLChannel
$sel:autoMLJobArn:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Text
$sel:autoMLJobName:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Text
$sel:httpStatus:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Int
$sel:resolvedAttributes:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ResolvedAttributes
$sel:problemType:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ProblemType
$sel:partialFailureReasons:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse
-> Maybe (NonEmpty AutoMLPartialFailureReason)
$sel:modelDeployResult:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ModelDeployResult
$sel:modelDeployConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe ModelDeployConfig
$sel:generateCandidateDefinitionsOnly:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe Bool
$sel:failureReason:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe Text
$sel:endTime:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe POSIX
$sel:bestCandidate:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLCandidate
$sel:autoMLJobObjective:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLJobObjective
$sel:autoMLJobConfig:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLJobConfig
$sel:autoMLJobArtifacts:DescribeAutoMLJobResponse' :: DescribeAutoMLJobResponse -> Maybe AutoMLJobArtifacts
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoMLJobArtifacts
autoMLJobArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutoMLJobConfig
autoMLJobConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 AutoMLCandidate
bestCandidate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      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 Bool
generateCandidateDefinitionsOnly
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelDeployConfig
modelDeployConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelDeployResult
modelDeployResult
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProblemType
problemType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResolvedAttributes
resolvedAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoMLJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoMLJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty AutoMLChannel
inputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AutoMLOutputDataConfig
outputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AutoMLJobStatus
autoMLJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus