{-# 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.Glue.Types.FindMatchesMetrics
-- 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.Glue.Types.FindMatchesMetrics where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types.ColumnImportance
import Amazonka.Glue.Types.ConfusionMatrix
import qualified Amazonka.Prelude as Prelude

-- | The evaluation metrics for the find matches algorithm. The quality of
-- your machine learning transform is measured by getting your transform to
-- predict some matches and comparing the results to known matches from the
-- same dataset. The quality metrics are based on a subset of your data, so
-- they are not precise.
--
-- /See:/ 'newFindMatchesMetrics' smart constructor.
data FindMatchesMetrics = FindMatchesMetrics'
  { -- | The area under the precision\/recall curve (AUPRC) is a single number
    -- measuring the overall quality of the transform, that is independent of
    -- the choice made for precision vs. recall. Higher values indicate that
    -- you have a more attractive precision vs. recall tradeoff.
    --
    -- For more information, see
    -- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
    -- in Wikipedia.
    FindMatchesMetrics -> Maybe Double
areaUnderPRCurve :: Prelude.Maybe Prelude.Double,
    -- | A list of @ColumnImportance@ structures containing column importance
    -- metrics, sorted in order of descending importance.
    FindMatchesMetrics -> Maybe [ColumnImportance]
columnImportances :: Prelude.Maybe [ColumnImportance],
    -- | The confusion matrix shows you what your transform is predicting
    -- accurately and what types of errors it is making.
    --
    -- For more information, see
    -- <https://en.wikipedia.org/wiki/Confusion_matrix Confusion matrix> in
    -- Wikipedia.
    FindMatchesMetrics -> Maybe ConfusionMatrix
confusionMatrix :: Prelude.Maybe ConfusionMatrix,
    -- | The maximum F1 metric indicates the transform\'s accuracy between 0 and
    -- 1, where 1 is the best accuracy.
    --
    -- For more information, see
    -- <https://en.wikipedia.org/wiki/F1_score F1 score> in Wikipedia.
    FindMatchesMetrics -> Maybe Double
f1 :: Prelude.Maybe Prelude.Double,
    -- | The precision metric indicates when often your transform is correct when
    -- it predicts a match. Specifically, it measures how well the transform
    -- finds true positives from the total true positives possible.
    --
    -- For more information, see
    -- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
    -- in Wikipedia.
    FindMatchesMetrics -> Maybe Double
precision :: Prelude.Maybe Prelude.Double,
    -- | The recall metric indicates that for an actual match, how often your
    -- transform predicts the match. Specifically, it measures how well the
    -- transform finds true positives from the total records in the source
    -- data.
    --
    -- For more information, see
    -- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
    -- in Wikipedia.
    FindMatchesMetrics -> Maybe Double
recall :: Prelude.Maybe Prelude.Double
  }
  deriving (FindMatchesMetrics -> FindMatchesMetrics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FindMatchesMetrics -> FindMatchesMetrics -> Bool
$c/= :: FindMatchesMetrics -> FindMatchesMetrics -> Bool
== :: FindMatchesMetrics -> FindMatchesMetrics -> Bool
$c== :: FindMatchesMetrics -> FindMatchesMetrics -> Bool
Prelude.Eq, ReadPrec [FindMatchesMetrics]
ReadPrec FindMatchesMetrics
Int -> ReadS FindMatchesMetrics
ReadS [FindMatchesMetrics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FindMatchesMetrics]
$creadListPrec :: ReadPrec [FindMatchesMetrics]
readPrec :: ReadPrec FindMatchesMetrics
$creadPrec :: ReadPrec FindMatchesMetrics
readList :: ReadS [FindMatchesMetrics]
$creadList :: ReadS [FindMatchesMetrics]
readsPrec :: Int -> ReadS FindMatchesMetrics
$creadsPrec :: Int -> ReadS FindMatchesMetrics
Prelude.Read, Int -> FindMatchesMetrics -> ShowS
[FindMatchesMetrics] -> ShowS
FindMatchesMetrics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FindMatchesMetrics] -> ShowS
$cshowList :: [FindMatchesMetrics] -> ShowS
show :: FindMatchesMetrics -> String
$cshow :: FindMatchesMetrics -> String
showsPrec :: Int -> FindMatchesMetrics -> ShowS
$cshowsPrec :: Int -> FindMatchesMetrics -> ShowS
Prelude.Show, forall x. Rep FindMatchesMetrics x -> FindMatchesMetrics
forall x. FindMatchesMetrics -> Rep FindMatchesMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FindMatchesMetrics x -> FindMatchesMetrics
$cfrom :: forall x. FindMatchesMetrics -> Rep FindMatchesMetrics x
Prelude.Generic)

-- |
-- Create a value of 'FindMatchesMetrics' 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:
--
-- 'areaUnderPRCurve', 'findMatchesMetrics_areaUnderPRCurve' - The area under the precision\/recall curve (AUPRC) is a single number
-- measuring the overall quality of the transform, that is independent of
-- the choice made for precision vs. recall. Higher values indicate that
-- you have a more attractive precision vs. recall tradeoff.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
-- in Wikipedia.
--
-- 'columnImportances', 'findMatchesMetrics_columnImportances' - A list of @ColumnImportance@ structures containing column importance
-- metrics, sorted in order of descending importance.
--
-- 'confusionMatrix', 'findMatchesMetrics_confusionMatrix' - The confusion matrix shows you what your transform is predicting
-- accurately and what types of errors it is making.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Confusion_matrix Confusion matrix> in
-- Wikipedia.
--
-- 'f1', 'findMatchesMetrics_f1' - The maximum F1 metric indicates the transform\'s accuracy between 0 and
-- 1, where 1 is the best accuracy.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/F1_score F1 score> in Wikipedia.
--
-- 'precision', 'findMatchesMetrics_precision' - The precision metric indicates when often your transform is correct when
-- it predicts a match. Specifically, it measures how well the transform
-- finds true positives from the total true positives possible.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
-- in Wikipedia.
--
-- 'recall', 'findMatchesMetrics_recall' - The recall metric indicates that for an actual match, how often your
-- transform predicts the match. Specifically, it measures how well the
-- transform finds true positives from the total records in the source
-- data.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
-- in Wikipedia.
newFindMatchesMetrics ::
  FindMatchesMetrics
newFindMatchesMetrics :: FindMatchesMetrics
newFindMatchesMetrics =
  FindMatchesMetrics'
    { $sel:areaUnderPRCurve:FindMatchesMetrics' :: Maybe Double
areaUnderPRCurve =
        forall a. Maybe a
Prelude.Nothing,
      $sel:columnImportances:FindMatchesMetrics' :: Maybe [ColumnImportance]
columnImportances = forall a. Maybe a
Prelude.Nothing,
      $sel:confusionMatrix:FindMatchesMetrics' :: Maybe ConfusionMatrix
confusionMatrix = forall a. Maybe a
Prelude.Nothing,
      $sel:f1:FindMatchesMetrics' :: Maybe Double
f1 = forall a. Maybe a
Prelude.Nothing,
      $sel:precision:FindMatchesMetrics' :: Maybe Double
precision = forall a. Maybe a
Prelude.Nothing,
      $sel:recall:FindMatchesMetrics' :: Maybe Double
recall = forall a. Maybe a
Prelude.Nothing
    }

-- | The area under the precision\/recall curve (AUPRC) is a single number
-- measuring the overall quality of the transform, that is independent of
-- the choice made for precision vs. recall. Higher values indicate that
-- you have a more attractive precision vs. recall tradeoff.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
-- in Wikipedia.
findMatchesMetrics_areaUnderPRCurve :: Lens.Lens' FindMatchesMetrics (Prelude.Maybe Prelude.Double)
findMatchesMetrics_areaUnderPRCurve :: Lens' FindMatchesMetrics (Maybe Double)
findMatchesMetrics_areaUnderPRCurve = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindMatchesMetrics' {Maybe Double
areaUnderPRCurve :: Maybe Double
$sel:areaUnderPRCurve:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
areaUnderPRCurve} -> Maybe Double
areaUnderPRCurve) (\s :: FindMatchesMetrics
s@FindMatchesMetrics' {} Maybe Double
a -> FindMatchesMetrics
s {$sel:areaUnderPRCurve:FindMatchesMetrics' :: Maybe Double
areaUnderPRCurve = Maybe Double
a} :: FindMatchesMetrics)

-- | A list of @ColumnImportance@ structures containing column importance
-- metrics, sorted in order of descending importance.
findMatchesMetrics_columnImportances :: Lens.Lens' FindMatchesMetrics (Prelude.Maybe [ColumnImportance])
findMatchesMetrics_columnImportances :: Lens' FindMatchesMetrics (Maybe [ColumnImportance])
findMatchesMetrics_columnImportances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindMatchesMetrics' {Maybe [ColumnImportance]
columnImportances :: Maybe [ColumnImportance]
$sel:columnImportances:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe [ColumnImportance]
columnImportances} -> Maybe [ColumnImportance]
columnImportances) (\s :: FindMatchesMetrics
s@FindMatchesMetrics' {} Maybe [ColumnImportance]
a -> FindMatchesMetrics
s {$sel:columnImportances:FindMatchesMetrics' :: Maybe [ColumnImportance]
columnImportances = Maybe [ColumnImportance]
a} :: FindMatchesMetrics) 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 confusion matrix shows you what your transform is predicting
-- accurately and what types of errors it is making.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Confusion_matrix Confusion matrix> in
-- Wikipedia.
findMatchesMetrics_confusionMatrix :: Lens.Lens' FindMatchesMetrics (Prelude.Maybe ConfusionMatrix)
findMatchesMetrics_confusionMatrix :: Lens' FindMatchesMetrics (Maybe ConfusionMatrix)
findMatchesMetrics_confusionMatrix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindMatchesMetrics' {Maybe ConfusionMatrix
confusionMatrix :: Maybe ConfusionMatrix
$sel:confusionMatrix:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe ConfusionMatrix
confusionMatrix} -> Maybe ConfusionMatrix
confusionMatrix) (\s :: FindMatchesMetrics
s@FindMatchesMetrics' {} Maybe ConfusionMatrix
a -> FindMatchesMetrics
s {$sel:confusionMatrix:FindMatchesMetrics' :: Maybe ConfusionMatrix
confusionMatrix = Maybe ConfusionMatrix
a} :: FindMatchesMetrics)

-- | The maximum F1 metric indicates the transform\'s accuracy between 0 and
-- 1, where 1 is the best accuracy.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/F1_score F1 score> in Wikipedia.
findMatchesMetrics_f1 :: Lens.Lens' FindMatchesMetrics (Prelude.Maybe Prelude.Double)
findMatchesMetrics_f1 :: Lens' FindMatchesMetrics (Maybe Double)
findMatchesMetrics_f1 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindMatchesMetrics' {Maybe Double
f1 :: Maybe Double
$sel:f1:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
f1} -> Maybe Double
f1) (\s :: FindMatchesMetrics
s@FindMatchesMetrics' {} Maybe Double
a -> FindMatchesMetrics
s {$sel:f1:FindMatchesMetrics' :: Maybe Double
f1 = Maybe Double
a} :: FindMatchesMetrics)

-- | The precision metric indicates when often your transform is correct when
-- it predicts a match. Specifically, it measures how well the transform
-- finds true positives from the total true positives possible.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
-- in Wikipedia.
findMatchesMetrics_precision :: Lens.Lens' FindMatchesMetrics (Prelude.Maybe Prelude.Double)
findMatchesMetrics_precision :: Lens' FindMatchesMetrics (Maybe Double)
findMatchesMetrics_precision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindMatchesMetrics' {Maybe Double
precision :: Maybe Double
$sel:precision:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
precision} -> Maybe Double
precision) (\s :: FindMatchesMetrics
s@FindMatchesMetrics' {} Maybe Double
a -> FindMatchesMetrics
s {$sel:precision:FindMatchesMetrics' :: Maybe Double
precision = Maybe Double
a} :: FindMatchesMetrics)

-- | The recall metric indicates that for an actual match, how often your
-- transform predicts the match. Specifically, it measures how well the
-- transform finds true positives from the total records in the source
-- data.
--
-- For more information, see
-- <https://en.wikipedia.org/wiki/Precision_and_recall Precision and recall>
-- in Wikipedia.
findMatchesMetrics_recall :: Lens.Lens' FindMatchesMetrics (Prelude.Maybe Prelude.Double)
findMatchesMetrics_recall :: Lens' FindMatchesMetrics (Maybe Double)
findMatchesMetrics_recall = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FindMatchesMetrics' {Maybe Double
recall :: Maybe Double
$sel:recall:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
recall} -> Maybe Double
recall) (\s :: FindMatchesMetrics
s@FindMatchesMetrics' {} Maybe Double
a -> FindMatchesMetrics
s {$sel:recall:FindMatchesMetrics' :: Maybe Double
recall = Maybe Double
a} :: FindMatchesMetrics)

instance Data.FromJSON FindMatchesMetrics where
  parseJSON :: Value -> Parser FindMatchesMetrics
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FindMatchesMetrics"
      ( \Object
x ->
          Maybe Double
-> Maybe [ColumnImportance]
-> Maybe ConfusionMatrix
-> Maybe Double
-> Maybe Double
-> Maybe Double
-> FindMatchesMetrics
FindMatchesMetrics'
            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
"AreaUnderPRCurve")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ColumnImportances"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"ConfusionMatrix")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"F1")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Precision")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Recall")
      )

instance Prelude.Hashable FindMatchesMetrics where
  hashWithSalt :: Int -> FindMatchesMetrics -> Int
hashWithSalt Int
_salt FindMatchesMetrics' {Maybe Double
Maybe [ColumnImportance]
Maybe ConfusionMatrix
recall :: Maybe Double
precision :: Maybe Double
f1 :: Maybe Double
confusionMatrix :: Maybe ConfusionMatrix
columnImportances :: Maybe [ColumnImportance]
areaUnderPRCurve :: Maybe Double
$sel:recall:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
$sel:precision:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
$sel:f1:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
$sel:confusionMatrix:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe ConfusionMatrix
$sel:columnImportances:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe [ColumnImportance]
$sel:areaUnderPRCurve:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
areaUnderPRCurve
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ColumnImportance]
columnImportances
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConfusionMatrix
confusionMatrix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
f1
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
precision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
recall

instance Prelude.NFData FindMatchesMetrics where
  rnf :: FindMatchesMetrics -> ()
rnf FindMatchesMetrics' {Maybe Double
Maybe [ColumnImportance]
Maybe ConfusionMatrix
recall :: Maybe Double
precision :: Maybe Double
f1 :: Maybe Double
confusionMatrix :: Maybe ConfusionMatrix
columnImportances :: Maybe [ColumnImportance]
areaUnderPRCurve :: Maybe Double
$sel:recall:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
$sel:precision:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
$sel:f1:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
$sel:confusionMatrix:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe ConfusionMatrix
$sel:columnImportances:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe [ColumnImportance]
$sel:areaUnderPRCurve:FindMatchesMetrics' :: FindMatchesMetrics -> Maybe Double
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
areaUnderPRCurve
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ColumnImportance]
columnImportances
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConfusionMatrix
confusionMatrix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
f1
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
precision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
recall