{-# 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.MacieV2.Types.ClassificationDetails
-- 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.MacieV2.Types.ClassificationDetails where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MacieV2.Types.ClassificationResult
import Amazonka.MacieV2.Types.OriginType
import qualified Amazonka.Prelude as Prelude

-- | Provides information about a sensitive data finding and the details of
-- the finding.
--
-- /See:/ 'newClassificationDetails' smart constructor.
data ClassificationDetails = ClassificationDetails'
  { -- | The path to the folder or file in Amazon S3 that contains the
    -- corresponding sensitive data discovery result for the finding. If a
    -- finding applies to a large archive or compressed file, this value is the
    -- path to a folder. Otherwise, this value is the path to a file.
    ClassificationDetails -> Maybe Text
detailedResultsLocation :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the classification job that produced
    -- the finding. This value is null if the origin of the finding
    -- (originType) is AUTOMATED_SENSITIVE_DATA_DISCOVERY.
    ClassificationDetails -> Maybe Text
jobArn :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the classification job that produced the
    -- finding. This value is null if the origin of the finding (originType) is
    -- AUTOMATED_SENSITIVE_DATA_DISCOVERY.
    ClassificationDetails -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | Specifies how Amazon Macie found the sensitive data that produced the
    -- finding. Possible values are: SENSITIVE_DATA_DISCOVERY_JOB, for a
    -- classification job; and, AUTOMATED_SENSITIVE_DATA_DISCOVERY, for
    -- automated sensitive data discovery.
    ClassificationDetails -> Maybe OriginType
originType :: Prelude.Maybe OriginType,
    -- | The status and other details of the finding.
    ClassificationDetails -> Maybe ClassificationResult
result :: Prelude.Maybe ClassificationResult
  }
  deriving (ClassificationDetails -> ClassificationDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassificationDetails -> ClassificationDetails -> Bool
$c/= :: ClassificationDetails -> ClassificationDetails -> Bool
== :: ClassificationDetails -> ClassificationDetails -> Bool
$c== :: ClassificationDetails -> ClassificationDetails -> Bool
Prelude.Eq, ReadPrec [ClassificationDetails]
ReadPrec ClassificationDetails
Int -> ReadS ClassificationDetails
ReadS [ClassificationDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassificationDetails]
$creadListPrec :: ReadPrec [ClassificationDetails]
readPrec :: ReadPrec ClassificationDetails
$creadPrec :: ReadPrec ClassificationDetails
readList :: ReadS [ClassificationDetails]
$creadList :: ReadS [ClassificationDetails]
readsPrec :: Int -> ReadS ClassificationDetails
$creadsPrec :: Int -> ReadS ClassificationDetails
Prelude.Read, Int -> ClassificationDetails -> ShowS
[ClassificationDetails] -> ShowS
ClassificationDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClassificationDetails] -> ShowS
$cshowList :: [ClassificationDetails] -> ShowS
show :: ClassificationDetails -> String
$cshow :: ClassificationDetails -> String
showsPrec :: Int -> ClassificationDetails -> ShowS
$cshowsPrec :: Int -> ClassificationDetails -> ShowS
Prelude.Show, forall x. Rep ClassificationDetails x -> ClassificationDetails
forall x. ClassificationDetails -> Rep ClassificationDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClassificationDetails x -> ClassificationDetails
$cfrom :: forall x. ClassificationDetails -> Rep ClassificationDetails x
Prelude.Generic)

-- |
-- Create a value of 'ClassificationDetails' 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:
--
-- 'detailedResultsLocation', 'classificationDetails_detailedResultsLocation' - The path to the folder or file in Amazon S3 that contains the
-- corresponding sensitive data discovery result for the finding. If a
-- finding applies to a large archive or compressed file, this value is the
-- path to a folder. Otherwise, this value is the path to a file.
--
-- 'jobArn', 'classificationDetails_jobArn' - The Amazon Resource Name (ARN) of the classification job that produced
-- the finding. This value is null if the origin of the finding
-- (originType) is AUTOMATED_SENSITIVE_DATA_DISCOVERY.
--
-- 'jobId', 'classificationDetails_jobId' - The unique identifier for the classification job that produced the
-- finding. This value is null if the origin of the finding (originType) is
-- AUTOMATED_SENSITIVE_DATA_DISCOVERY.
--
-- 'originType', 'classificationDetails_originType' - Specifies how Amazon Macie found the sensitive data that produced the
-- finding. Possible values are: SENSITIVE_DATA_DISCOVERY_JOB, for a
-- classification job; and, AUTOMATED_SENSITIVE_DATA_DISCOVERY, for
-- automated sensitive data discovery.
--
-- 'result', 'classificationDetails_result' - The status and other details of the finding.
newClassificationDetails ::
  ClassificationDetails
newClassificationDetails :: ClassificationDetails
newClassificationDetails =
  ClassificationDetails'
    { $sel:detailedResultsLocation:ClassificationDetails' :: Maybe Text
detailedResultsLocation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:jobArn:ClassificationDetails' :: Maybe Text
jobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:ClassificationDetails' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:originType:ClassificationDetails' :: Maybe OriginType
originType = forall a. Maybe a
Prelude.Nothing,
      $sel:result:ClassificationDetails' :: Maybe ClassificationResult
result = forall a. Maybe a
Prelude.Nothing
    }

-- | The path to the folder or file in Amazon S3 that contains the
-- corresponding sensitive data discovery result for the finding. If a
-- finding applies to a large archive or compressed file, this value is the
-- path to a folder. Otherwise, this value is the path to a file.
classificationDetails_detailedResultsLocation :: Lens.Lens' ClassificationDetails (Prelude.Maybe Prelude.Text)
classificationDetails_detailedResultsLocation :: Lens' ClassificationDetails (Maybe Text)
classificationDetails_detailedResultsLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassificationDetails' {Maybe Text
detailedResultsLocation :: Maybe Text
$sel:detailedResultsLocation:ClassificationDetails' :: ClassificationDetails -> Maybe Text
detailedResultsLocation} -> Maybe Text
detailedResultsLocation) (\s :: ClassificationDetails
s@ClassificationDetails' {} Maybe Text
a -> ClassificationDetails
s {$sel:detailedResultsLocation:ClassificationDetails' :: Maybe Text
detailedResultsLocation = Maybe Text
a} :: ClassificationDetails)

-- | The Amazon Resource Name (ARN) of the classification job that produced
-- the finding. This value is null if the origin of the finding
-- (originType) is AUTOMATED_SENSITIVE_DATA_DISCOVERY.
classificationDetails_jobArn :: Lens.Lens' ClassificationDetails (Prelude.Maybe Prelude.Text)
classificationDetails_jobArn :: Lens' ClassificationDetails (Maybe Text)
classificationDetails_jobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassificationDetails' {Maybe Text
jobArn :: Maybe Text
$sel:jobArn:ClassificationDetails' :: ClassificationDetails -> Maybe Text
jobArn} -> Maybe Text
jobArn) (\s :: ClassificationDetails
s@ClassificationDetails' {} Maybe Text
a -> ClassificationDetails
s {$sel:jobArn:ClassificationDetails' :: Maybe Text
jobArn = Maybe Text
a} :: ClassificationDetails)

-- | The unique identifier for the classification job that produced the
-- finding. This value is null if the origin of the finding (originType) is
-- AUTOMATED_SENSITIVE_DATA_DISCOVERY.
classificationDetails_jobId :: Lens.Lens' ClassificationDetails (Prelude.Maybe Prelude.Text)
classificationDetails_jobId :: Lens' ClassificationDetails (Maybe Text)
classificationDetails_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassificationDetails' {Maybe Text
jobId :: Maybe Text
$sel:jobId:ClassificationDetails' :: ClassificationDetails -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: ClassificationDetails
s@ClassificationDetails' {} Maybe Text
a -> ClassificationDetails
s {$sel:jobId:ClassificationDetails' :: Maybe Text
jobId = Maybe Text
a} :: ClassificationDetails)

-- | Specifies how Amazon Macie found the sensitive data that produced the
-- finding. Possible values are: SENSITIVE_DATA_DISCOVERY_JOB, for a
-- classification job; and, AUTOMATED_SENSITIVE_DATA_DISCOVERY, for
-- automated sensitive data discovery.
classificationDetails_originType :: Lens.Lens' ClassificationDetails (Prelude.Maybe OriginType)
classificationDetails_originType :: Lens' ClassificationDetails (Maybe OriginType)
classificationDetails_originType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassificationDetails' {Maybe OriginType
originType :: Maybe OriginType
$sel:originType:ClassificationDetails' :: ClassificationDetails -> Maybe OriginType
originType} -> Maybe OriginType
originType) (\s :: ClassificationDetails
s@ClassificationDetails' {} Maybe OriginType
a -> ClassificationDetails
s {$sel:originType:ClassificationDetails' :: Maybe OriginType
originType = Maybe OriginType
a} :: ClassificationDetails)

-- | The status and other details of the finding.
classificationDetails_result :: Lens.Lens' ClassificationDetails (Prelude.Maybe ClassificationResult)
classificationDetails_result :: Lens' ClassificationDetails (Maybe ClassificationResult)
classificationDetails_result = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClassificationDetails' {Maybe ClassificationResult
result :: Maybe ClassificationResult
$sel:result:ClassificationDetails' :: ClassificationDetails -> Maybe ClassificationResult
result} -> Maybe ClassificationResult
result) (\s :: ClassificationDetails
s@ClassificationDetails' {} Maybe ClassificationResult
a -> ClassificationDetails
s {$sel:result:ClassificationDetails' :: Maybe ClassificationResult
result = Maybe ClassificationResult
a} :: ClassificationDetails)

instance Data.FromJSON ClassificationDetails where
  parseJSON :: Value -> Parser ClassificationDetails
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ClassificationDetails"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe OriginType
-> Maybe ClassificationResult
-> ClassificationDetails
ClassificationDetails'
            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
"detailedResultsLocation")
            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
"jobArn")
            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
"jobId")
            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
"originType")
            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
"result")
      )

instance Prelude.Hashable ClassificationDetails where
  hashWithSalt :: Int -> ClassificationDetails -> Int
hashWithSalt Int
_salt ClassificationDetails' {Maybe Text
Maybe OriginType
Maybe ClassificationResult
result :: Maybe ClassificationResult
originType :: Maybe OriginType
jobId :: Maybe Text
jobArn :: Maybe Text
detailedResultsLocation :: Maybe Text
$sel:result:ClassificationDetails' :: ClassificationDetails -> Maybe ClassificationResult
$sel:originType:ClassificationDetails' :: ClassificationDetails -> Maybe OriginType
$sel:jobId:ClassificationDetails' :: ClassificationDetails -> Maybe Text
$sel:jobArn:ClassificationDetails' :: ClassificationDetails -> Maybe Text
$sel:detailedResultsLocation:ClassificationDetails' :: ClassificationDetails -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
detailedResultsLocation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OriginType
originType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClassificationResult
result

instance Prelude.NFData ClassificationDetails where
  rnf :: ClassificationDetails -> ()
rnf ClassificationDetails' {Maybe Text
Maybe OriginType
Maybe ClassificationResult
result :: Maybe ClassificationResult
originType :: Maybe OriginType
jobId :: Maybe Text
jobArn :: Maybe Text
detailedResultsLocation :: Maybe Text
$sel:result:ClassificationDetails' :: ClassificationDetails -> Maybe ClassificationResult
$sel:originType:ClassificationDetails' :: ClassificationDetails -> Maybe OriginType
$sel:jobId:ClassificationDetails' :: ClassificationDetails -> Maybe Text
$sel:jobArn:ClassificationDetails' :: ClassificationDetails -> Maybe Text
$sel:detailedResultsLocation:ClassificationDetails' :: ClassificationDetails -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
detailedResultsLocation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OriginType
originType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClassificationResult
result