{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Forecast.Types.Baseline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Forecast.Types.Baseline 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.PredictorBaseline
import qualified Amazonka.Prelude as Prelude

-- | Metrics you can use as a baseline for comparison purposes. Use these
-- metrics when you interpret monitoring results for an auto predictor.
--
-- /See:/ 'newBaseline' smart constructor.
data Baseline = Baseline'
  { -- | The initial
    -- <https://docs.aws.amazon.com/forecast/latest/dg/metrics.html accuracy metrics>
    -- for the predictor you are monitoring. Use these metrics as a baseline
    -- for comparison purposes as you use your predictor and the metrics
    -- change.
    Baseline -> Maybe PredictorBaseline
predictorBaseline :: Prelude.Maybe PredictorBaseline
  }
  deriving (Baseline -> Baseline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Baseline -> Baseline -> Bool
$c/= :: Baseline -> Baseline -> Bool
== :: Baseline -> Baseline -> Bool
$c== :: Baseline -> Baseline -> Bool
Prelude.Eq, ReadPrec [Baseline]
ReadPrec Baseline
Int -> ReadS Baseline
ReadS [Baseline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Baseline]
$creadListPrec :: ReadPrec [Baseline]
readPrec :: ReadPrec Baseline
$creadPrec :: ReadPrec Baseline
readList :: ReadS [Baseline]
$creadList :: ReadS [Baseline]
readsPrec :: Int -> ReadS Baseline
$creadsPrec :: Int -> ReadS Baseline
Prelude.Read, Int -> Baseline -> ShowS
[Baseline] -> ShowS
Baseline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Baseline] -> ShowS
$cshowList :: [Baseline] -> ShowS
show :: Baseline -> String
$cshow :: Baseline -> String
showsPrec :: Int -> Baseline -> ShowS
$cshowsPrec :: Int -> Baseline -> ShowS
Prelude.Show, forall x. Rep Baseline x -> Baseline
forall x. Baseline -> Rep Baseline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Baseline x -> Baseline
$cfrom :: forall x. Baseline -> Rep Baseline x
Prelude.Generic)

-- |
-- Create a value of 'Baseline' 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:
--
-- 'predictorBaseline', 'baseline_predictorBaseline' - The initial
-- <https://docs.aws.amazon.com/forecast/latest/dg/metrics.html accuracy metrics>
-- for the predictor you are monitoring. Use these metrics as a baseline
-- for comparison purposes as you use your predictor and the metrics
-- change.
newBaseline ::
  Baseline
newBaseline :: Baseline
newBaseline =
  Baseline' {$sel:predictorBaseline:Baseline' :: Maybe PredictorBaseline
predictorBaseline = forall a. Maybe a
Prelude.Nothing}

-- | The initial
-- <https://docs.aws.amazon.com/forecast/latest/dg/metrics.html accuracy metrics>
-- for the predictor you are monitoring. Use these metrics as a baseline
-- for comparison purposes as you use your predictor and the metrics
-- change.
baseline_predictorBaseline :: Lens.Lens' Baseline (Prelude.Maybe PredictorBaseline)
baseline_predictorBaseline :: Lens' Baseline (Maybe PredictorBaseline)
baseline_predictorBaseline = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Baseline' {Maybe PredictorBaseline
predictorBaseline :: Maybe PredictorBaseline
$sel:predictorBaseline:Baseline' :: Baseline -> Maybe PredictorBaseline
predictorBaseline} -> Maybe PredictorBaseline
predictorBaseline) (\s :: Baseline
s@Baseline' {} Maybe PredictorBaseline
a -> Baseline
s {$sel:predictorBaseline:Baseline' :: Maybe PredictorBaseline
predictorBaseline = Maybe PredictorBaseline
a} :: Baseline)

instance Data.FromJSON Baseline where
  parseJSON :: Value -> Parser Baseline
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Baseline"
      ( \Object
x ->
          Maybe PredictorBaseline -> Baseline
Baseline'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PredictorBaseline")
      )

instance Prelude.Hashable Baseline where
  hashWithSalt :: Int -> Baseline -> Int
hashWithSalt Int
_salt Baseline' {Maybe PredictorBaseline
predictorBaseline :: Maybe PredictorBaseline
$sel:predictorBaseline:Baseline' :: Baseline -> Maybe PredictorBaseline
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PredictorBaseline
predictorBaseline

instance Prelude.NFData Baseline where
  rnf :: Baseline -> ()
rnf Baseline' {Maybe PredictorBaseline
predictorBaseline :: Maybe PredictorBaseline
$sel:predictorBaseline:Baseline' :: Baseline -> Maybe PredictorBaseline
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe PredictorBaseline
predictorBaseline