{-# 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.Forecast.DescribeAutoPredictor
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Describes a predictor created using the CreateAutoPredictor operation.
module Amazonka.Forecast.DescribeAutoPredictor
  ( -- * Creating a Request
    DescribeAutoPredictor (..),
    newDescribeAutoPredictor,

    -- * Request Lenses
    describeAutoPredictor_predictorArn,

    -- * Destructuring the Response
    DescribeAutoPredictorResponse (..),
    newDescribeAutoPredictorResponse,

    -- * Response Lenses
    describeAutoPredictorResponse_creationTime,
    describeAutoPredictorResponse_dataConfig,
    describeAutoPredictorResponse_datasetImportJobArns,
    describeAutoPredictorResponse_encryptionConfig,
    describeAutoPredictorResponse_estimatedTimeRemainingInMinutes,
    describeAutoPredictorResponse_explainabilityInfo,
    describeAutoPredictorResponse_forecastDimensions,
    describeAutoPredictorResponse_forecastFrequency,
    describeAutoPredictorResponse_forecastHorizon,
    describeAutoPredictorResponse_forecastTypes,
    describeAutoPredictorResponse_lastModificationTime,
    describeAutoPredictorResponse_message,
    describeAutoPredictorResponse_monitorInfo,
    describeAutoPredictorResponse_optimizationMetric,
    describeAutoPredictorResponse_predictorArn,
    describeAutoPredictorResponse_predictorName,
    describeAutoPredictorResponse_referencePredictorSummary,
    describeAutoPredictorResponse_status,
    describeAutoPredictorResponse_timeAlignmentBoundary,
    describeAutoPredictorResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDescribeAutoPredictor' smart constructor.
data DescribeAutoPredictor = DescribeAutoPredictor'
  { -- | The Amazon Resource Name (ARN) of the predictor.
    DescribeAutoPredictor -> Text
predictorArn :: Prelude.Text
  }
  deriving (DescribeAutoPredictor -> DescribeAutoPredictor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAutoPredictor -> DescribeAutoPredictor -> Bool
$c/= :: DescribeAutoPredictor -> DescribeAutoPredictor -> Bool
== :: DescribeAutoPredictor -> DescribeAutoPredictor -> Bool
$c== :: DescribeAutoPredictor -> DescribeAutoPredictor -> Bool
Prelude.Eq, ReadPrec [DescribeAutoPredictor]
ReadPrec DescribeAutoPredictor
Int -> ReadS DescribeAutoPredictor
ReadS [DescribeAutoPredictor]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAutoPredictor]
$creadListPrec :: ReadPrec [DescribeAutoPredictor]
readPrec :: ReadPrec DescribeAutoPredictor
$creadPrec :: ReadPrec DescribeAutoPredictor
readList :: ReadS [DescribeAutoPredictor]
$creadList :: ReadS [DescribeAutoPredictor]
readsPrec :: Int -> ReadS DescribeAutoPredictor
$creadsPrec :: Int -> ReadS DescribeAutoPredictor
Prelude.Read, Int -> DescribeAutoPredictor -> ShowS
[DescribeAutoPredictor] -> ShowS
DescribeAutoPredictor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAutoPredictor] -> ShowS
$cshowList :: [DescribeAutoPredictor] -> ShowS
show :: DescribeAutoPredictor -> String
$cshow :: DescribeAutoPredictor -> String
showsPrec :: Int -> DescribeAutoPredictor -> ShowS
$cshowsPrec :: Int -> DescribeAutoPredictor -> ShowS
Prelude.Show, forall x. Rep DescribeAutoPredictor x -> DescribeAutoPredictor
forall x. DescribeAutoPredictor -> Rep DescribeAutoPredictor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeAutoPredictor x -> DescribeAutoPredictor
$cfrom :: forall x. DescribeAutoPredictor -> Rep DescribeAutoPredictor x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAutoPredictor' 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:
--
-- 'predictorArn', 'describeAutoPredictor_predictorArn' - The Amazon Resource Name (ARN) of the predictor.
newDescribeAutoPredictor ::
  -- | 'predictorArn'
  Prelude.Text ->
  DescribeAutoPredictor
newDescribeAutoPredictor :: Text -> DescribeAutoPredictor
newDescribeAutoPredictor Text
pPredictorArn_ =
  DescribeAutoPredictor'
    { $sel:predictorArn:DescribeAutoPredictor' :: Text
predictorArn =
        Text
pPredictorArn_
    }

-- | The Amazon Resource Name (ARN) of the predictor.
describeAutoPredictor_predictorArn :: Lens.Lens' DescribeAutoPredictor Prelude.Text
describeAutoPredictor_predictorArn :: Lens' DescribeAutoPredictor Text
describeAutoPredictor_predictorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictor' {Text
predictorArn :: Text
$sel:predictorArn:DescribeAutoPredictor' :: DescribeAutoPredictor -> Text
predictorArn} -> Text
predictorArn) (\s :: DescribeAutoPredictor
s@DescribeAutoPredictor' {} Text
a -> DescribeAutoPredictor
s {$sel:predictorArn:DescribeAutoPredictor' :: Text
predictorArn = Text
a} :: DescribeAutoPredictor)

instance Core.AWSRequest DescribeAutoPredictor where
  type
    AWSResponse DescribeAutoPredictor =
      DescribeAutoPredictorResponse
  request :: (Service -> Service)
-> DescribeAutoPredictor -> Request DescribeAutoPredictor
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 DescribeAutoPredictor
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeAutoPredictor)))
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 POSIX
-> Maybe DataConfig
-> Maybe [Text]
-> Maybe EncryptionConfig
-> Maybe Integer
-> Maybe ExplainabilityInfo
-> Maybe (NonEmpty Text)
-> Maybe Text
-> Maybe Int
-> Maybe (NonEmpty Text)
-> Maybe POSIX
-> Maybe Text
-> Maybe MonitorInfo
-> Maybe OptimizationMetric
-> Maybe Text
-> Maybe Text
-> Maybe ReferencePredictorSummary
-> Maybe Text
-> Maybe TimeAlignmentBoundary
-> Int
-> DescribeAutoPredictorResponse
DescribeAutoPredictorResponse'
            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
"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 (Maybe a)
Data..?> Key
"DataConfig")
            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
"DatasetImportJobArns"
                            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
"EncryptionConfig")
            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
"EstimatedTimeRemainingInMinutes")
            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
"ExplainabilityInfo")
            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
"ForecastDimensions")
            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
"ForecastFrequency")
            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
"ForecastHorizon")
            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
"ForecastTypes")
            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
"LastModificationTime")
            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
"Message")
            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
"MonitorInfo")
            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
"OptimizationMetric")
            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
"PredictorArn")
            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
"PredictorName")
            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
"ReferencePredictorSummary")
            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
"TimeAlignmentBoundary")
            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 DescribeAutoPredictor where
  hashWithSalt :: Int -> DescribeAutoPredictor -> Int
hashWithSalt Int
_salt DescribeAutoPredictor' {Text
predictorArn :: Text
$sel:predictorArn:DescribeAutoPredictor' :: DescribeAutoPredictor -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
predictorArn

instance Prelude.NFData DescribeAutoPredictor where
  rnf :: DescribeAutoPredictor -> ()
rnf DescribeAutoPredictor' {Text
predictorArn :: Text
$sel:predictorArn:DescribeAutoPredictor' :: DescribeAutoPredictor -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
predictorArn

instance Data.ToHeaders DescribeAutoPredictor where
  toHeaders :: DescribeAutoPredictor -> 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
"AmazonForecast.DescribeAutoPredictor" ::
                          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 DescribeAutoPredictor where
  toJSON :: DescribeAutoPredictor -> Value
toJSON DescribeAutoPredictor' {Text
predictorArn :: Text
$sel:predictorArn:DescribeAutoPredictor' :: DescribeAutoPredictor -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"PredictorArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
predictorArn)]
      )

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

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

-- | /See:/ 'newDescribeAutoPredictorResponse' smart constructor.
data DescribeAutoPredictorResponse = DescribeAutoPredictorResponse'
  { -- | The timestamp of the CreateAutoPredictor request.
    DescribeAutoPredictorResponse -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | The data configuration for your dataset group and any additional
    -- datasets.
    DescribeAutoPredictorResponse -> Maybe DataConfig
dataConfig :: Prelude.Maybe DataConfig,
    -- | An array of the ARNs of the dataset import jobs used to import training
    -- data for the predictor.
    DescribeAutoPredictorResponse -> Maybe [Text]
datasetImportJobArns :: Prelude.Maybe [Prelude.Text],
    DescribeAutoPredictorResponse -> Maybe EncryptionConfig
encryptionConfig :: Prelude.Maybe EncryptionConfig,
    -- | The estimated time remaining in minutes for the predictor training job
    -- to complete.
    DescribeAutoPredictorResponse -> Maybe Integer
estimatedTimeRemainingInMinutes :: Prelude.Maybe Prelude.Integer,
    -- | Provides the status and ARN of the Predictor Explainability.
    DescribeAutoPredictorResponse -> Maybe ExplainabilityInfo
explainabilityInfo :: Prelude.Maybe ExplainabilityInfo,
    -- | An array of dimension (field) names that specify the attributes used to
    -- group your time series.
    DescribeAutoPredictorResponse -> Maybe (NonEmpty Text)
forecastDimensions :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The frequency of predictions in a forecast.
    --
    -- Valid intervals are Y (Year), M (Month), W (Week), D (Day), H (Hour),
    -- 30min (30 minutes), 15min (15 minutes), 10min (10 minutes), 5min (5
    -- minutes), and 1min (1 minute). For example, \"Y\" indicates every year
    -- and \"5min\" indicates every five minutes.
    DescribeAutoPredictorResponse -> Maybe Text
forecastFrequency :: Prelude.Maybe Prelude.Text,
    -- | The number of time-steps that the model predicts. The forecast horizon
    -- is also called the prediction length.
    DescribeAutoPredictorResponse -> Maybe Int
forecastHorizon :: Prelude.Maybe Prelude.Int,
    -- | The forecast types used during predictor training. Default value is
    -- [\"0.1\",\"0.5\",\"0.9\"].
    DescribeAutoPredictorResponse -> Maybe (NonEmpty Text)
forecastTypes :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | The last time the resource was modified. The timestamp depends on the
    -- status of the job:
    --
    -- -   @CREATE_PENDING@ - The @CreationTime@.
    --
    -- -   @CREATE_IN_PROGRESS@ - The current timestamp.
    --
    -- -   @CREATE_STOPPING@ - The current timestamp.
    --
    -- -   @CREATE_STOPPED@ - When the job stopped.
    --
    -- -   @ACTIVE@ or @CREATE_FAILED@ - When the job finished or failed.
    DescribeAutoPredictorResponse -> Maybe POSIX
lastModificationTime :: Prelude.Maybe Data.POSIX,
    -- | In the event of an error, a message detailing the cause of the error.
    DescribeAutoPredictorResponse -> Maybe Text
message :: Prelude.Maybe Prelude.Text,
    -- | A object with the Amazon Resource Name (ARN) and status of the monitor
    -- resource.
    DescribeAutoPredictorResponse -> Maybe MonitorInfo
monitorInfo :: Prelude.Maybe MonitorInfo,
    -- | The accuracy metric used to optimize the predictor.
    DescribeAutoPredictorResponse -> Maybe OptimizationMetric
optimizationMetric :: Prelude.Maybe OptimizationMetric,
    -- | The Amazon Resource Name (ARN) of the predictor
    DescribeAutoPredictorResponse -> Maybe Text
predictorArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the predictor.
    DescribeAutoPredictorResponse -> Maybe Text
predictorName :: Prelude.Maybe Prelude.Text,
    -- | The ARN and state of the reference predictor. This parameter is only
    -- valid for retrained or upgraded predictors.
    DescribeAutoPredictorResponse -> Maybe ReferencePredictorSummary
referencePredictorSummary :: Prelude.Maybe ReferencePredictorSummary,
    -- | The status of the predictor. States include:
    --
    -- -   @ACTIVE@
    --
    -- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
    --
    -- -   @CREATE_STOPPING@, @CREATE_STOPPED@
    --
    -- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
    DescribeAutoPredictorResponse -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | The time boundary Forecast uses when aggregating data.
    DescribeAutoPredictorResponse -> Maybe TimeAlignmentBoundary
timeAlignmentBoundary :: Prelude.Maybe TimeAlignmentBoundary,
    -- | The response's http status code.
    DescribeAutoPredictorResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeAutoPredictorResponse
-> DescribeAutoPredictorResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeAutoPredictorResponse
-> DescribeAutoPredictorResponse -> Bool
$c/= :: DescribeAutoPredictorResponse
-> DescribeAutoPredictorResponse -> Bool
== :: DescribeAutoPredictorResponse
-> DescribeAutoPredictorResponse -> Bool
$c== :: DescribeAutoPredictorResponse
-> DescribeAutoPredictorResponse -> Bool
Prelude.Eq, ReadPrec [DescribeAutoPredictorResponse]
ReadPrec DescribeAutoPredictorResponse
Int -> ReadS DescribeAutoPredictorResponse
ReadS [DescribeAutoPredictorResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeAutoPredictorResponse]
$creadListPrec :: ReadPrec [DescribeAutoPredictorResponse]
readPrec :: ReadPrec DescribeAutoPredictorResponse
$creadPrec :: ReadPrec DescribeAutoPredictorResponse
readList :: ReadS [DescribeAutoPredictorResponse]
$creadList :: ReadS [DescribeAutoPredictorResponse]
readsPrec :: Int -> ReadS DescribeAutoPredictorResponse
$creadsPrec :: Int -> ReadS DescribeAutoPredictorResponse
Prelude.Read, Int -> DescribeAutoPredictorResponse -> ShowS
[DescribeAutoPredictorResponse] -> ShowS
DescribeAutoPredictorResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeAutoPredictorResponse] -> ShowS
$cshowList :: [DescribeAutoPredictorResponse] -> ShowS
show :: DescribeAutoPredictorResponse -> String
$cshow :: DescribeAutoPredictorResponse -> String
showsPrec :: Int -> DescribeAutoPredictorResponse -> ShowS
$cshowsPrec :: Int -> DescribeAutoPredictorResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeAutoPredictorResponse x
-> DescribeAutoPredictorResponse
forall x.
DescribeAutoPredictorResponse
-> Rep DescribeAutoPredictorResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeAutoPredictorResponse x
-> DescribeAutoPredictorResponse
$cfrom :: forall x.
DescribeAutoPredictorResponse
-> Rep DescribeAutoPredictorResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeAutoPredictorResponse' 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:
--
-- 'creationTime', 'describeAutoPredictorResponse_creationTime' - The timestamp of the CreateAutoPredictor request.
--
-- 'dataConfig', 'describeAutoPredictorResponse_dataConfig' - The data configuration for your dataset group and any additional
-- datasets.
--
-- 'datasetImportJobArns', 'describeAutoPredictorResponse_datasetImportJobArns' - An array of the ARNs of the dataset import jobs used to import training
-- data for the predictor.
--
-- 'encryptionConfig', 'describeAutoPredictorResponse_encryptionConfig' - Undocumented member.
--
-- 'estimatedTimeRemainingInMinutes', 'describeAutoPredictorResponse_estimatedTimeRemainingInMinutes' - The estimated time remaining in minutes for the predictor training job
-- to complete.
--
-- 'explainabilityInfo', 'describeAutoPredictorResponse_explainabilityInfo' - Provides the status and ARN of the Predictor Explainability.
--
-- 'forecastDimensions', 'describeAutoPredictorResponse_forecastDimensions' - An array of dimension (field) names that specify the attributes used to
-- group your time series.
--
-- 'forecastFrequency', 'describeAutoPredictorResponse_forecastFrequency' - The frequency of predictions in a forecast.
--
-- Valid intervals are Y (Year), M (Month), W (Week), D (Day), H (Hour),
-- 30min (30 minutes), 15min (15 minutes), 10min (10 minutes), 5min (5
-- minutes), and 1min (1 minute). For example, \"Y\" indicates every year
-- and \"5min\" indicates every five minutes.
--
-- 'forecastHorizon', 'describeAutoPredictorResponse_forecastHorizon' - The number of time-steps that the model predicts. The forecast horizon
-- is also called the prediction length.
--
-- 'forecastTypes', 'describeAutoPredictorResponse_forecastTypes' - The forecast types used during predictor training. Default value is
-- [\"0.1\",\"0.5\",\"0.9\"].
--
-- 'lastModificationTime', 'describeAutoPredictorResponse_lastModificationTime' - The last time the resource was modified. The timestamp depends on the
-- status of the job:
--
-- -   @CREATE_PENDING@ - The @CreationTime@.
--
-- -   @CREATE_IN_PROGRESS@ - The current timestamp.
--
-- -   @CREATE_STOPPING@ - The current timestamp.
--
-- -   @CREATE_STOPPED@ - When the job stopped.
--
-- -   @ACTIVE@ or @CREATE_FAILED@ - When the job finished or failed.
--
-- 'message', 'describeAutoPredictorResponse_message' - In the event of an error, a message detailing the cause of the error.
--
-- 'monitorInfo', 'describeAutoPredictorResponse_monitorInfo' - A object with the Amazon Resource Name (ARN) and status of the monitor
-- resource.
--
-- 'optimizationMetric', 'describeAutoPredictorResponse_optimizationMetric' - The accuracy metric used to optimize the predictor.
--
-- 'predictorArn', 'describeAutoPredictorResponse_predictorArn' - The Amazon Resource Name (ARN) of the predictor
--
-- 'predictorName', 'describeAutoPredictorResponse_predictorName' - The name of the predictor.
--
-- 'referencePredictorSummary', 'describeAutoPredictorResponse_referencePredictorSummary' - The ARN and state of the reference predictor. This parameter is only
-- valid for retrained or upgraded predictors.
--
-- 'status', 'describeAutoPredictorResponse_status' - The status of the predictor. States include:
--
-- -   @ACTIVE@
--
-- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
--
-- -   @CREATE_STOPPING@, @CREATE_STOPPED@
--
-- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
--
-- 'timeAlignmentBoundary', 'describeAutoPredictorResponse_timeAlignmentBoundary' - The time boundary Forecast uses when aggregating data.
--
-- 'httpStatus', 'describeAutoPredictorResponse_httpStatus' - The response's http status code.
newDescribeAutoPredictorResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeAutoPredictorResponse
newDescribeAutoPredictorResponse :: Int -> DescribeAutoPredictorResponse
newDescribeAutoPredictorResponse Int
pHttpStatus_ =
  DescribeAutoPredictorResponse'
    { $sel:creationTime:DescribeAutoPredictorResponse' :: Maybe POSIX
creationTime =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dataConfig:DescribeAutoPredictorResponse' :: Maybe DataConfig
dataConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetImportJobArns:DescribeAutoPredictorResponse' :: Maybe [Text]
datasetImportJobArns = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionConfig:DescribeAutoPredictorResponse' :: Maybe EncryptionConfig
encryptionConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:estimatedTimeRemainingInMinutes:DescribeAutoPredictorResponse' :: Maybe Integer
estimatedTimeRemainingInMinutes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:explainabilityInfo:DescribeAutoPredictorResponse' :: Maybe ExplainabilityInfo
explainabilityInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:forecastDimensions:DescribeAutoPredictorResponse' :: Maybe (NonEmpty Text)
forecastDimensions = forall a. Maybe a
Prelude.Nothing,
      $sel:forecastFrequency:DescribeAutoPredictorResponse' :: Maybe Text
forecastFrequency = forall a. Maybe a
Prelude.Nothing,
      $sel:forecastHorizon:DescribeAutoPredictorResponse' :: Maybe Int
forecastHorizon = forall a. Maybe a
Prelude.Nothing,
      $sel:forecastTypes:DescribeAutoPredictorResponse' :: Maybe (NonEmpty Text)
forecastTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModificationTime:DescribeAutoPredictorResponse' :: Maybe POSIX
lastModificationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:message:DescribeAutoPredictorResponse' :: Maybe Text
message = forall a. Maybe a
Prelude.Nothing,
      $sel:monitorInfo:DescribeAutoPredictorResponse' :: Maybe MonitorInfo
monitorInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:optimizationMetric:DescribeAutoPredictorResponse' :: Maybe OptimizationMetric
optimizationMetric = forall a. Maybe a
Prelude.Nothing,
      $sel:predictorArn:DescribeAutoPredictorResponse' :: Maybe Text
predictorArn = forall a. Maybe a
Prelude.Nothing,
      $sel:predictorName:DescribeAutoPredictorResponse' :: Maybe Text
predictorName = forall a. Maybe a
Prelude.Nothing,
      $sel:referencePredictorSummary:DescribeAutoPredictorResponse' :: Maybe ReferencePredictorSummary
referencePredictorSummary = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeAutoPredictorResponse' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:timeAlignmentBoundary:DescribeAutoPredictorResponse' :: Maybe TimeAlignmentBoundary
timeAlignmentBoundary = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeAutoPredictorResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The timestamp of the CreateAutoPredictor request.
describeAutoPredictorResponse_creationTime :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.UTCTime)
describeAutoPredictorResponse_creationTime :: Lens' DescribeAutoPredictorResponse (Maybe UTCTime)
describeAutoPredictorResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe POSIX
a -> DescribeAutoPredictorResponse
s {$sel:creationTime:DescribeAutoPredictorResponse' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: DescribeAutoPredictorResponse) 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 data configuration for your dataset group and any additional
-- datasets.
describeAutoPredictorResponse_dataConfig :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe DataConfig)
describeAutoPredictorResponse_dataConfig :: Lens' DescribeAutoPredictorResponse (Maybe DataConfig)
describeAutoPredictorResponse_dataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe DataConfig
dataConfig :: Maybe DataConfig
$sel:dataConfig:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe DataConfig
dataConfig} -> Maybe DataConfig
dataConfig) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe DataConfig
a -> DescribeAutoPredictorResponse
s {$sel:dataConfig:DescribeAutoPredictorResponse' :: Maybe DataConfig
dataConfig = Maybe DataConfig
a} :: DescribeAutoPredictorResponse)

-- | An array of the ARNs of the dataset import jobs used to import training
-- data for the predictor.
describeAutoPredictorResponse_datasetImportJobArns :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe [Prelude.Text])
describeAutoPredictorResponse_datasetImportJobArns :: Lens' DescribeAutoPredictorResponse (Maybe [Text])
describeAutoPredictorResponse_datasetImportJobArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe [Text]
datasetImportJobArns :: Maybe [Text]
$sel:datasetImportJobArns:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe [Text]
datasetImportJobArns} -> Maybe [Text]
datasetImportJobArns) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe [Text]
a -> DescribeAutoPredictorResponse
s {$sel:datasetImportJobArns:DescribeAutoPredictorResponse' :: Maybe [Text]
datasetImportJobArns = Maybe [Text]
a} :: DescribeAutoPredictorResponse) 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

-- | Undocumented member.
describeAutoPredictorResponse_encryptionConfig :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe EncryptionConfig)
describeAutoPredictorResponse_encryptionConfig :: Lens' DescribeAutoPredictorResponse (Maybe EncryptionConfig)
describeAutoPredictorResponse_encryptionConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe EncryptionConfig
encryptionConfig :: Maybe EncryptionConfig
$sel:encryptionConfig:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe EncryptionConfig
encryptionConfig} -> Maybe EncryptionConfig
encryptionConfig) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe EncryptionConfig
a -> DescribeAutoPredictorResponse
s {$sel:encryptionConfig:DescribeAutoPredictorResponse' :: Maybe EncryptionConfig
encryptionConfig = Maybe EncryptionConfig
a} :: DescribeAutoPredictorResponse)

-- | The estimated time remaining in minutes for the predictor training job
-- to complete.
describeAutoPredictorResponse_estimatedTimeRemainingInMinutes :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Integer)
describeAutoPredictorResponse_estimatedTimeRemainingInMinutes :: Lens' DescribeAutoPredictorResponse (Maybe Integer)
describeAutoPredictorResponse_estimatedTimeRemainingInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Integer
estimatedTimeRemainingInMinutes :: Maybe Integer
$sel:estimatedTimeRemainingInMinutes:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Integer
estimatedTimeRemainingInMinutes} -> Maybe Integer
estimatedTimeRemainingInMinutes) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Integer
a -> DescribeAutoPredictorResponse
s {$sel:estimatedTimeRemainingInMinutes:DescribeAutoPredictorResponse' :: Maybe Integer
estimatedTimeRemainingInMinutes = Maybe Integer
a} :: DescribeAutoPredictorResponse)

-- | Provides the status and ARN of the Predictor Explainability.
describeAutoPredictorResponse_explainabilityInfo :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe ExplainabilityInfo)
describeAutoPredictorResponse_explainabilityInfo :: Lens' DescribeAutoPredictorResponse (Maybe ExplainabilityInfo)
describeAutoPredictorResponse_explainabilityInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe ExplainabilityInfo
explainabilityInfo :: Maybe ExplainabilityInfo
$sel:explainabilityInfo:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe ExplainabilityInfo
explainabilityInfo} -> Maybe ExplainabilityInfo
explainabilityInfo) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe ExplainabilityInfo
a -> DescribeAutoPredictorResponse
s {$sel:explainabilityInfo:DescribeAutoPredictorResponse' :: Maybe ExplainabilityInfo
explainabilityInfo = Maybe ExplainabilityInfo
a} :: DescribeAutoPredictorResponse)

-- | An array of dimension (field) names that specify the attributes used to
-- group your time series.
describeAutoPredictorResponse_forecastDimensions :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeAutoPredictorResponse_forecastDimensions :: Lens' DescribeAutoPredictorResponse (Maybe (NonEmpty Text))
describeAutoPredictorResponse_forecastDimensions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe (NonEmpty Text)
forecastDimensions :: Maybe (NonEmpty Text)
$sel:forecastDimensions:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe (NonEmpty Text)
forecastDimensions} -> Maybe (NonEmpty Text)
forecastDimensions) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe (NonEmpty Text)
a -> DescribeAutoPredictorResponse
s {$sel:forecastDimensions:DescribeAutoPredictorResponse' :: Maybe (NonEmpty Text)
forecastDimensions = Maybe (NonEmpty Text)
a} :: DescribeAutoPredictorResponse) 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 frequency of predictions in a forecast.
--
-- Valid intervals are Y (Year), M (Month), W (Week), D (Day), H (Hour),
-- 30min (30 minutes), 15min (15 minutes), 10min (10 minutes), 5min (5
-- minutes), and 1min (1 minute). For example, \"Y\" indicates every year
-- and \"5min\" indicates every five minutes.
describeAutoPredictorResponse_forecastFrequency :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Text)
describeAutoPredictorResponse_forecastFrequency :: Lens' DescribeAutoPredictorResponse (Maybe Text)
describeAutoPredictorResponse_forecastFrequency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Text
forecastFrequency :: Maybe Text
$sel:forecastFrequency:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
forecastFrequency} -> Maybe Text
forecastFrequency) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Text
a -> DescribeAutoPredictorResponse
s {$sel:forecastFrequency:DescribeAutoPredictorResponse' :: Maybe Text
forecastFrequency = Maybe Text
a} :: DescribeAutoPredictorResponse)

-- | The number of time-steps that the model predicts. The forecast horizon
-- is also called the prediction length.
describeAutoPredictorResponse_forecastHorizon :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Int)
describeAutoPredictorResponse_forecastHorizon :: Lens' DescribeAutoPredictorResponse (Maybe Int)
describeAutoPredictorResponse_forecastHorizon = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Int
forecastHorizon :: Maybe Int
$sel:forecastHorizon:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Int
forecastHorizon} -> Maybe Int
forecastHorizon) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Int
a -> DescribeAutoPredictorResponse
s {$sel:forecastHorizon:DescribeAutoPredictorResponse' :: Maybe Int
forecastHorizon = Maybe Int
a} :: DescribeAutoPredictorResponse)

-- | The forecast types used during predictor training. Default value is
-- [\"0.1\",\"0.5\",\"0.9\"].
describeAutoPredictorResponse_forecastTypes :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
describeAutoPredictorResponse_forecastTypes :: Lens' DescribeAutoPredictorResponse (Maybe (NonEmpty Text))
describeAutoPredictorResponse_forecastTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe (NonEmpty Text)
forecastTypes :: Maybe (NonEmpty Text)
$sel:forecastTypes:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe (NonEmpty Text)
forecastTypes} -> Maybe (NonEmpty Text)
forecastTypes) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe (NonEmpty Text)
a -> DescribeAutoPredictorResponse
s {$sel:forecastTypes:DescribeAutoPredictorResponse' :: Maybe (NonEmpty Text)
forecastTypes = Maybe (NonEmpty Text)
a} :: DescribeAutoPredictorResponse) 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 last time the resource was modified. The timestamp depends on the
-- status of the job:
--
-- -   @CREATE_PENDING@ - The @CreationTime@.
--
-- -   @CREATE_IN_PROGRESS@ - The current timestamp.
--
-- -   @CREATE_STOPPING@ - The current timestamp.
--
-- -   @CREATE_STOPPED@ - When the job stopped.
--
-- -   @ACTIVE@ or @CREATE_FAILED@ - When the job finished or failed.
describeAutoPredictorResponse_lastModificationTime :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.UTCTime)
describeAutoPredictorResponse_lastModificationTime :: Lens' DescribeAutoPredictorResponse (Maybe UTCTime)
describeAutoPredictorResponse_lastModificationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe POSIX
lastModificationTime :: Maybe POSIX
$sel:lastModificationTime:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe POSIX
lastModificationTime} -> Maybe POSIX
lastModificationTime) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe POSIX
a -> DescribeAutoPredictorResponse
s {$sel:lastModificationTime:DescribeAutoPredictorResponse' :: Maybe POSIX
lastModificationTime = Maybe POSIX
a} :: DescribeAutoPredictorResponse) 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

-- | In the event of an error, a message detailing the cause of the error.
describeAutoPredictorResponse_message :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Text)
describeAutoPredictorResponse_message :: Lens' DescribeAutoPredictorResponse (Maybe Text)
describeAutoPredictorResponse_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Text
message :: Maybe Text
$sel:message:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
message} -> Maybe Text
message) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Text
a -> DescribeAutoPredictorResponse
s {$sel:message:DescribeAutoPredictorResponse' :: Maybe Text
message = Maybe Text
a} :: DescribeAutoPredictorResponse)

-- | A object with the Amazon Resource Name (ARN) and status of the monitor
-- resource.
describeAutoPredictorResponse_monitorInfo :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe MonitorInfo)
describeAutoPredictorResponse_monitorInfo :: Lens' DescribeAutoPredictorResponse (Maybe MonitorInfo)
describeAutoPredictorResponse_monitorInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe MonitorInfo
monitorInfo :: Maybe MonitorInfo
$sel:monitorInfo:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe MonitorInfo
monitorInfo} -> Maybe MonitorInfo
monitorInfo) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe MonitorInfo
a -> DescribeAutoPredictorResponse
s {$sel:monitorInfo:DescribeAutoPredictorResponse' :: Maybe MonitorInfo
monitorInfo = Maybe MonitorInfo
a} :: DescribeAutoPredictorResponse)

-- | The accuracy metric used to optimize the predictor.
describeAutoPredictorResponse_optimizationMetric :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe OptimizationMetric)
describeAutoPredictorResponse_optimizationMetric :: Lens' DescribeAutoPredictorResponse (Maybe OptimizationMetric)
describeAutoPredictorResponse_optimizationMetric = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe OptimizationMetric
optimizationMetric :: Maybe OptimizationMetric
$sel:optimizationMetric:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe OptimizationMetric
optimizationMetric} -> Maybe OptimizationMetric
optimizationMetric) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe OptimizationMetric
a -> DescribeAutoPredictorResponse
s {$sel:optimizationMetric:DescribeAutoPredictorResponse' :: Maybe OptimizationMetric
optimizationMetric = Maybe OptimizationMetric
a} :: DescribeAutoPredictorResponse)

-- | The Amazon Resource Name (ARN) of the predictor
describeAutoPredictorResponse_predictorArn :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Text)
describeAutoPredictorResponse_predictorArn :: Lens' DescribeAutoPredictorResponse (Maybe Text)
describeAutoPredictorResponse_predictorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Text
predictorArn :: Maybe Text
$sel:predictorArn:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
predictorArn} -> Maybe Text
predictorArn) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Text
a -> DescribeAutoPredictorResponse
s {$sel:predictorArn:DescribeAutoPredictorResponse' :: Maybe Text
predictorArn = Maybe Text
a} :: DescribeAutoPredictorResponse)

-- | The name of the predictor.
describeAutoPredictorResponse_predictorName :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Text)
describeAutoPredictorResponse_predictorName :: Lens' DescribeAutoPredictorResponse (Maybe Text)
describeAutoPredictorResponse_predictorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Text
predictorName :: Maybe Text
$sel:predictorName:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
predictorName} -> Maybe Text
predictorName) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Text
a -> DescribeAutoPredictorResponse
s {$sel:predictorName:DescribeAutoPredictorResponse' :: Maybe Text
predictorName = Maybe Text
a} :: DescribeAutoPredictorResponse)

-- | The ARN and state of the reference predictor. This parameter is only
-- valid for retrained or upgraded predictors.
describeAutoPredictorResponse_referencePredictorSummary :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe ReferencePredictorSummary)
describeAutoPredictorResponse_referencePredictorSummary :: Lens'
  DescribeAutoPredictorResponse (Maybe ReferencePredictorSummary)
describeAutoPredictorResponse_referencePredictorSummary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe ReferencePredictorSummary
referencePredictorSummary :: Maybe ReferencePredictorSummary
$sel:referencePredictorSummary:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe ReferencePredictorSummary
referencePredictorSummary} -> Maybe ReferencePredictorSummary
referencePredictorSummary) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe ReferencePredictorSummary
a -> DescribeAutoPredictorResponse
s {$sel:referencePredictorSummary:DescribeAutoPredictorResponse' :: Maybe ReferencePredictorSummary
referencePredictorSummary = Maybe ReferencePredictorSummary
a} :: DescribeAutoPredictorResponse)

-- | The status of the predictor. States include:
--
-- -   @ACTIVE@
--
-- -   @CREATE_PENDING@, @CREATE_IN_PROGRESS@, @CREATE_FAILED@
--
-- -   @CREATE_STOPPING@, @CREATE_STOPPED@
--
-- -   @DELETE_PENDING@, @DELETE_IN_PROGRESS@, @DELETE_FAILED@
describeAutoPredictorResponse_status :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe Prelude.Text)
describeAutoPredictorResponse_status :: Lens' DescribeAutoPredictorResponse (Maybe Text)
describeAutoPredictorResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe Text
status :: Maybe Text
$sel:status:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
status} -> Maybe Text
status) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe Text
a -> DescribeAutoPredictorResponse
s {$sel:status:DescribeAutoPredictorResponse' :: Maybe Text
status = Maybe Text
a} :: DescribeAutoPredictorResponse)

-- | The time boundary Forecast uses when aggregating data.
describeAutoPredictorResponse_timeAlignmentBoundary :: Lens.Lens' DescribeAutoPredictorResponse (Prelude.Maybe TimeAlignmentBoundary)
describeAutoPredictorResponse_timeAlignmentBoundary :: Lens' DescribeAutoPredictorResponse (Maybe TimeAlignmentBoundary)
describeAutoPredictorResponse_timeAlignmentBoundary = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeAutoPredictorResponse' {Maybe TimeAlignmentBoundary
timeAlignmentBoundary :: Maybe TimeAlignmentBoundary
$sel:timeAlignmentBoundary:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe TimeAlignmentBoundary
timeAlignmentBoundary} -> Maybe TimeAlignmentBoundary
timeAlignmentBoundary) (\s :: DescribeAutoPredictorResponse
s@DescribeAutoPredictorResponse' {} Maybe TimeAlignmentBoundary
a -> DescribeAutoPredictorResponse
s {$sel:timeAlignmentBoundary:DescribeAutoPredictorResponse' :: Maybe TimeAlignmentBoundary
timeAlignmentBoundary = Maybe TimeAlignmentBoundary
a} :: DescribeAutoPredictorResponse)

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

instance Prelude.NFData DescribeAutoPredictorResponse where
  rnf :: DescribeAutoPredictorResponse -> ()
rnf DescribeAutoPredictorResponse' {Int
Maybe Int
Maybe Integer
Maybe [Text]
Maybe (NonEmpty Text)
Maybe Text
Maybe POSIX
Maybe DataConfig
Maybe EncryptionConfig
Maybe ExplainabilityInfo
Maybe MonitorInfo
Maybe OptimizationMetric
Maybe ReferencePredictorSummary
Maybe TimeAlignmentBoundary
httpStatus :: Int
timeAlignmentBoundary :: Maybe TimeAlignmentBoundary
status :: Maybe Text
referencePredictorSummary :: Maybe ReferencePredictorSummary
predictorName :: Maybe Text
predictorArn :: Maybe Text
optimizationMetric :: Maybe OptimizationMetric
monitorInfo :: Maybe MonitorInfo
message :: Maybe Text
lastModificationTime :: Maybe POSIX
forecastTypes :: Maybe (NonEmpty Text)
forecastHorizon :: Maybe Int
forecastFrequency :: Maybe Text
forecastDimensions :: Maybe (NonEmpty Text)
explainabilityInfo :: Maybe ExplainabilityInfo
estimatedTimeRemainingInMinutes :: Maybe Integer
encryptionConfig :: Maybe EncryptionConfig
datasetImportJobArns :: Maybe [Text]
dataConfig :: Maybe DataConfig
creationTime :: Maybe POSIX
$sel:httpStatus:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Int
$sel:timeAlignmentBoundary:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe TimeAlignmentBoundary
$sel:status:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
$sel:referencePredictorSummary:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe ReferencePredictorSummary
$sel:predictorName:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
$sel:predictorArn:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
$sel:optimizationMetric:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe OptimizationMetric
$sel:monitorInfo:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe MonitorInfo
$sel:message:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
$sel:lastModificationTime:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe POSIX
$sel:forecastTypes:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe (NonEmpty Text)
$sel:forecastHorizon:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Int
$sel:forecastFrequency:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Text
$sel:forecastDimensions:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe (NonEmpty Text)
$sel:explainabilityInfo:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe ExplainabilityInfo
$sel:estimatedTimeRemainingInMinutes:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe Integer
$sel:encryptionConfig:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe EncryptionConfig
$sel:datasetImportJobArns:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe [Text]
$sel:dataConfig:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe DataConfig
$sel:creationTime:DescribeAutoPredictorResponse' :: DescribeAutoPredictorResponse -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataConfig
dataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
datasetImportJobArns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionConfig
encryptionConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
estimatedTimeRemainingInMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExplainabilityInfo
explainabilityInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
forecastDimensions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
forecastFrequency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
forecastHorizon
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
forecastTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModificationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MonitorInfo
monitorInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OptimizationMetric
optimizationMetric
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
predictorArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
predictorName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ReferencePredictorSummary
referencePredictorSummary
      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 TimeAlignmentBoundary
timeAlignmentBoundary
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus