{-# 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.GuardDuty.Types.Scan
-- 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.GuardDuty.Types.Scan where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GuardDuty.Types.ResourceDetails
import Amazonka.GuardDuty.Types.ScanResultDetails
import Amazonka.GuardDuty.Types.ScanStatus
import Amazonka.GuardDuty.Types.TriggerDetails
import Amazonka.GuardDuty.Types.VolumeDetail
import qualified Amazonka.Prelude as Prelude

-- | Contains information about a malware scan.
--
-- /See:/ 'newScan' smart constructor.
data Scan = Scan'
  { -- | The ID for the account that belongs to the scan.
    Scan -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | The unique detector ID of the administrator account that the request is
    -- associated with. Note that this value will be the same as the one used
    -- for @DetectorId@ if the account is an administrator.
    Scan -> Maybe Text
adminDetectorId :: Prelude.Maybe Prelude.Text,
    -- | List of volumes that were attached to the original instance to be
    -- scanned.
    Scan -> Maybe [VolumeDetail]
attachedVolumes :: Prelude.Maybe [VolumeDetail],
    -- | The unique ID of the detector that the request is associated with.
    Scan -> Maybe Text
detectorId :: Prelude.Maybe Prelude.Text,
    -- | Represents the reason for FAILED scan status.
    Scan -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | Represents the number of files that were scanned.
    Scan -> Maybe Natural
fileCount :: Prelude.Maybe Prelude.Natural,
    -- | Represents the resources that were scanned in the scan entry.
    Scan -> Maybe ResourceDetails
resourceDetails :: Prelude.Maybe ResourceDetails,
    -- | The timestamp of when the scan was finished.
    Scan -> Maybe POSIX
scanEndTime :: Prelude.Maybe Data.POSIX,
    -- | The unique scan ID associated with a scan entry.
    Scan -> Maybe Text
scanId :: Prelude.Maybe Prelude.Text,
    -- | Represents the result of the scan.
    Scan -> Maybe ScanResultDetails
scanResultDetails :: Prelude.Maybe ScanResultDetails,
    -- | The timestamp of when the scan was triggered.
    Scan -> Maybe POSIX
scanStartTime :: Prelude.Maybe Data.POSIX,
    -- | An enum value representing possible scan statuses.
    Scan -> Maybe ScanStatus
scanStatus :: Prelude.Maybe ScanStatus,
    -- | Represents total bytes that were scanned.
    Scan -> Maybe Natural
totalBytes :: Prelude.Maybe Prelude.Natural,
    -- | Specifies the reason why the scan was initiated.
    Scan -> Maybe TriggerDetails
triggerDetails :: Prelude.Maybe TriggerDetails
  }
  deriving (Scan -> Scan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Scan -> Scan -> Bool
$c/= :: Scan -> Scan -> Bool
== :: Scan -> Scan -> Bool
$c== :: Scan -> Scan -> Bool
Prelude.Eq, ReadPrec [Scan]
ReadPrec Scan
Int -> ReadS Scan
ReadS [Scan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Scan]
$creadListPrec :: ReadPrec [Scan]
readPrec :: ReadPrec Scan
$creadPrec :: ReadPrec Scan
readList :: ReadS [Scan]
$creadList :: ReadS [Scan]
readsPrec :: Int -> ReadS Scan
$creadsPrec :: Int -> ReadS Scan
Prelude.Read, Int -> Scan -> ShowS
[Scan] -> ShowS
Scan -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Scan] -> ShowS
$cshowList :: [Scan] -> ShowS
show :: Scan -> String
$cshow :: Scan -> String
showsPrec :: Int -> Scan -> ShowS
$cshowsPrec :: Int -> Scan -> ShowS
Prelude.Show, forall x. Rep Scan x -> Scan
forall x. Scan -> Rep Scan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Scan x -> Scan
$cfrom :: forall x. Scan -> Rep Scan x
Prelude.Generic)

-- |
-- Create a value of 'Scan' 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:
--
-- 'accountId', 'scan_accountId' - The ID for the account that belongs to the scan.
--
-- 'adminDetectorId', 'scan_adminDetectorId' - The unique detector ID of the administrator account that the request is
-- associated with. Note that this value will be the same as the one used
-- for @DetectorId@ if the account is an administrator.
--
-- 'attachedVolumes', 'scan_attachedVolumes' - List of volumes that were attached to the original instance to be
-- scanned.
--
-- 'detectorId', 'scan_detectorId' - The unique ID of the detector that the request is associated with.
--
-- 'failureReason', 'scan_failureReason' - Represents the reason for FAILED scan status.
--
-- 'fileCount', 'scan_fileCount' - Represents the number of files that were scanned.
--
-- 'resourceDetails', 'scan_resourceDetails' - Represents the resources that were scanned in the scan entry.
--
-- 'scanEndTime', 'scan_scanEndTime' - The timestamp of when the scan was finished.
--
-- 'scanId', 'scan_scanId' - The unique scan ID associated with a scan entry.
--
-- 'scanResultDetails', 'scan_scanResultDetails' - Represents the result of the scan.
--
-- 'scanStartTime', 'scan_scanStartTime' - The timestamp of when the scan was triggered.
--
-- 'scanStatus', 'scan_scanStatus' - An enum value representing possible scan statuses.
--
-- 'totalBytes', 'scan_totalBytes' - Represents total bytes that were scanned.
--
-- 'triggerDetails', 'scan_triggerDetails' - Specifies the reason why the scan was initiated.
newScan ::
  Scan
newScan :: Scan
newScan =
  Scan'
    { $sel:accountId:Scan' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:adminDetectorId:Scan' :: Maybe Text
adminDetectorId = forall a. Maybe a
Prelude.Nothing,
      $sel:attachedVolumes:Scan' :: Maybe [VolumeDetail]
attachedVolumes = forall a. Maybe a
Prelude.Nothing,
      $sel:detectorId:Scan' :: Maybe Text
detectorId = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:Scan' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:fileCount:Scan' :: Maybe Natural
fileCount = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceDetails:Scan' :: Maybe ResourceDetails
resourceDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:scanEndTime:Scan' :: Maybe POSIX
scanEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:scanId:Scan' :: Maybe Text
scanId = forall a. Maybe a
Prelude.Nothing,
      $sel:scanResultDetails:Scan' :: Maybe ScanResultDetails
scanResultDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:scanStartTime:Scan' :: Maybe POSIX
scanStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:scanStatus:Scan' :: Maybe ScanStatus
scanStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:totalBytes:Scan' :: Maybe Natural
totalBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:triggerDetails:Scan' :: Maybe TriggerDetails
triggerDetails = forall a. Maybe a
Prelude.Nothing
    }

-- | The ID for the account that belongs to the scan.
scan_accountId :: Lens.Lens' Scan (Prelude.Maybe Prelude.Text)
scan_accountId :: Lens' Scan (Maybe Text)
scan_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Text
accountId :: Maybe Text
$sel:accountId:Scan' :: Scan -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: Scan
s@Scan' {} Maybe Text
a -> Scan
s {$sel:accountId:Scan' :: Maybe Text
accountId = Maybe Text
a} :: Scan)

-- | The unique detector ID of the administrator account that the request is
-- associated with. Note that this value will be the same as the one used
-- for @DetectorId@ if the account is an administrator.
scan_adminDetectorId :: Lens.Lens' Scan (Prelude.Maybe Prelude.Text)
scan_adminDetectorId :: Lens' Scan (Maybe Text)
scan_adminDetectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Text
adminDetectorId :: Maybe Text
$sel:adminDetectorId:Scan' :: Scan -> Maybe Text
adminDetectorId} -> Maybe Text
adminDetectorId) (\s :: Scan
s@Scan' {} Maybe Text
a -> Scan
s {$sel:adminDetectorId:Scan' :: Maybe Text
adminDetectorId = Maybe Text
a} :: Scan)

-- | List of volumes that were attached to the original instance to be
-- scanned.
scan_attachedVolumes :: Lens.Lens' Scan (Prelude.Maybe [VolumeDetail])
scan_attachedVolumes :: Lens' Scan (Maybe [VolumeDetail])
scan_attachedVolumes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe [VolumeDetail]
attachedVolumes :: Maybe [VolumeDetail]
$sel:attachedVolumes:Scan' :: Scan -> Maybe [VolumeDetail]
attachedVolumes} -> Maybe [VolumeDetail]
attachedVolumes) (\s :: Scan
s@Scan' {} Maybe [VolumeDetail]
a -> Scan
s {$sel:attachedVolumes:Scan' :: Maybe [VolumeDetail]
attachedVolumes = Maybe [VolumeDetail]
a} :: Scan) 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 unique ID of the detector that the request is associated with.
scan_detectorId :: Lens.Lens' Scan (Prelude.Maybe Prelude.Text)
scan_detectorId :: Lens' Scan (Maybe Text)
scan_detectorId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Text
detectorId :: Maybe Text
$sel:detectorId:Scan' :: Scan -> Maybe Text
detectorId} -> Maybe Text
detectorId) (\s :: Scan
s@Scan' {} Maybe Text
a -> Scan
s {$sel:detectorId:Scan' :: Maybe Text
detectorId = Maybe Text
a} :: Scan)

-- | Represents the reason for FAILED scan status.
scan_failureReason :: Lens.Lens' Scan (Prelude.Maybe Prelude.Text)
scan_failureReason :: Lens' Scan (Maybe Text)
scan_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:Scan' :: Scan -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: Scan
s@Scan' {} Maybe Text
a -> Scan
s {$sel:failureReason:Scan' :: Maybe Text
failureReason = Maybe Text
a} :: Scan)

-- | Represents the number of files that were scanned.
scan_fileCount :: Lens.Lens' Scan (Prelude.Maybe Prelude.Natural)
scan_fileCount :: Lens' Scan (Maybe Natural)
scan_fileCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Natural
fileCount :: Maybe Natural
$sel:fileCount:Scan' :: Scan -> Maybe Natural
fileCount} -> Maybe Natural
fileCount) (\s :: Scan
s@Scan' {} Maybe Natural
a -> Scan
s {$sel:fileCount:Scan' :: Maybe Natural
fileCount = Maybe Natural
a} :: Scan)

-- | Represents the resources that were scanned in the scan entry.
scan_resourceDetails :: Lens.Lens' Scan (Prelude.Maybe ResourceDetails)
scan_resourceDetails :: Lens' Scan (Maybe ResourceDetails)
scan_resourceDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe ResourceDetails
resourceDetails :: Maybe ResourceDetails
$sel:resourceDetails:Scan' :: Scan -> Maybe ResourceDetails
resourceDetails} -> Maybe ResourceDetails
resourceDetails) (\s :: Scan
s@Scan' {} Maybe ResourceDetails
a -> Scan
s {$sel:resourceDetails:Scan' :: Maybe ResourceDetails
resourceDetails = Maybe ResourceDetails
a} :: Scan)

-- | The timestamp of when the scan was finished.
scan_scanEndTime :: Lens.Lens' Scan (Prelude.Maybe Prelude.UTCTime)
scan_scanEndTime :: Lens' Scan (Maybe UTCTime)
scan_scanEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe POSIX
scanEndTime :: Maybe POSIX
$sel:scanEndTime:Scan' :: Scan -> Maybe POSIX
scanEndTime} -> Maybe POSIX
scanEndTime) (\s :: Scan
s@Scan' {} Maybe POSIX
a -> Scan
s {$sel:scanEndTime:Scan' :: Maybe POSIX
scanEndTime = Maybe POSIX
a} :: Scan) 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 unique scan ID associated with a scan entry.
scan_scanId :: Lens.Lens' Scan (Prelude.Maybe Prelude.Text)
scan_scanId :: Lens' Scan (Maybe Text)
scan_scanId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Text
scanId :: Maybe Text
$sel:scanId:Scan' :: Scan -> Maybe Text
scanId} -> Maybe Text
scanId) (\s :: Scan
s@Scan' {} Maybe Text
a -> Scan
s {$sel:scanId:Scan' :: Maybe Text
scanId = Maybe Text
a} :: Scan)

-- | Represents the result of the scan.
scan_scanResultDetails :: Lens.Lens' Scan (Prelude.Maybe ScanResultDetails)
scan_scanResultDetails :: Lens' Scan (Maybe ScanResultDetails)
scan_scanResultDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe ScanResultDetails
scanResultDetails :: Maybe ScanResultDetails
$sel:scanResultDetails:Scan' :: Scan -> Maybe ScanResultDetails
scanResultDetails} -> Maybe ScanResultDetails
scanResultDetails) (\s :: Scan
s@Scan' {} Maybe ScanResultDetails
a -> Scan
s {$sel:scanResultDetails:Scan' :: Maybe ScanResultDetails
scanResultDetails = Maybe ScanResultDetails
a} :: Scan)

-- | The timestamp of when the scan was triggered.
scan_scanStartTime :: Lens.Lens' Scan (Prelude.Maybe Prelude.UTCTime)
scan_scanStartTime :: Lens' Scan (Maybe UTCTime)
scan_scanStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe POSIX
scanStartTime :: Maybe POSIX
$sel:scanStartTime:Scan' :: Scan -> Maybe POSIX
scanStartTime} -> Maybe POSIX
scanStartTime) (\s :: Scan
s@Scan' {} Maybe POSIX
a -> Scan
s {$sel:scanStartTime:Scan' :: Maybe POSIX
scanStartTime = Maybe POSIX
a} :: Scan) 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

-- | An enum value representing possible scan statuses.
scan_scanStatus :: Lens.Lens' Scan (Prelude.Maybe ScanStatus)
scan_scanStatus :: Lens' Scan (Maybe ScanStatus)
scan_scanStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe ScanStatus
scanStatus :: Maybe ScanStatus
$sel:scanStatus:Scan' :: Scan -> Maybe ScanStatus
scanStatus} -> Maybe ScanStatus
scanStatus) (\s :: Scan
s@Scan' {} Maybe ScanStatus
a -> Scan
s {$sel:scanStatus:Scan' :: Maybe ScanStatus
scanStatus = Maybe ScanStatus
a} :: Scan)

-- | Represents total bytes that were scanned.
scan_totalBytes :: Lens.Lens' Scan (Prelude.Maybe Prelude.Natural)
scan_totalBytes :: Lens' Scan (Maybe Natural)
scan_totalBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe Natural
totalBytes :: Maybe Natural
$sel:totalBytes:Scan' :: Scan -> Maybe Natural
totalBytes} -> Maybe Natural
totalBytes) (\s :: Scan
s@Scan' {} Maybe Natural
a -> Scan
s {$sel:totalBytes:Scan' :: Maybe Natural
totalBytes = Maybe Natural
a} :: Scan)

-- | Specifies the reason why the scan was initiated.
scan_triggerDetails :: Lens.Lens' Scan (Prelude.Maybe TriggerDetails)
scan_triggerDetails :: Lens' Scan (Maybe TriggerDetails)
scan_triggerDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Scan' {Maybe TriggerDetails
triggerDetails :: Maybe TriggerDetails
$sel:triggerDetails:Scan' :: Scan -> Maybe TriggerDetails
triggerDetails} -> Maybe TriggerDetails
triggerDetails) (\s :: Scan
s@Scan' {} Maybe TriggerDetails
a -> Scan
s {$sel:triggerDetails:Scan' :: Maybe TriggerDetails
triggerDetails = Maybe TriggerDetails
a} :: Scan)

instance Data.FromJSON Scan where
  parseJSON :: Value -> Parser Scan
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Scan"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe [VolumeDetail]
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe ResourceDetails
-> Maybe POSIX
-> Maybe Text
-> Maybe ScanResultDetails
-> Maybe POSIX
-> Maybe ScanStatus
-> Maybe Natural
-> Maybe TriggerDetails
-> Scan
Scan'
            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
"accountId")
            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
"adminDetectorId")
            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
"attachedVolumes"
                            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
"detectorId")
            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
"failureReason")
            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
"fileCount")
            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
"resourceDetails")
            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
"scanEndTime")
            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
"scanId")
            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
"scanResultDetails")
            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
"scanStartTime")
            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
"scanStatus")
            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
"totalBytes")
            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
"triggerDetails")
      )

instance Prelude.Hashable Scan where
  hashWithSalt :: Int -> Scan -> Int
hashWithSalt Int
_salt Scan' {Maybe Natural
Maybe [VolumeDetail]
Maybe Text
Maybe POSIX
Maybe ResourceDetails
Maybe ScanResultDetails
Maybe ScanStatus
Maybe TriggerDetails
triggerDetails :: Maybe TriggerDetails
totalBytes :: Maybe Natural
scanStatus :: Maybe ScanStatus
scanStartTime :: Maybe POSIX
scanResultDetails :: Maybe ScanResultDetails
scanId :: Maybe Text
scanEndTime :: Maybe POSIX
resourceDetails :: Maybe ResourceDetails
fileCount :: Maybe Natural
failureReason :: Maybe Text
detectorId :: Maybe Text
attachedVolumes :: Maybe [VolumeDetail]
adminDetectorId :: Maybe Text
accountId :: Maybe Text
$sel:triggerDetails:Scan' :: Scan -> Maybe TriggerDetails
$sel:totalBytes:Scan' :: Scan -> Maybe Natural
$sel:scanStatus:Scan' :: Scan -> Maybe ScanStatus
$sel:scanStartTime:Scan' :: Scan -> Maybe POSIX
$sel:scanResultDetails:Scan' :: Scan -> Maybe ScanResultDetails
$sel:scanId:Scan' :: Scan -> Maybe Text
$sel:scanEndTime:Scan' :: Scan -> Maybe POSIX
$sel:resourceDetails:Scan' :: Scan -> Maybe ResourceDetails
$sel:fileCount:Scan' :: Scan -> Maybe Natural
$sel:failureReason:Scan' :: Scan -> Maybe Text
$sel:detectorId:Scan' :: Scan -> Maybe Text
$sel:attachedVolumes:Scan' :: Scan -> Maybe [VolumeDetail]
$sel:adminDetectorId:Scan' :: Scan -> Maybe Text
$sel:accountId:Scan' :: Scan -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
adminDetectorId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [VolumeDetail]
attachedVolumes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
detectorId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
fileCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceDetails
resourceDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
scanEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scanId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ScanResultDetails
scanResultDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
scanStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ScanStatus
scanStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
totalBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TriggerDetails
triggerDetails

instance Prelude.NFData Scan where
  rnf :: Scan -> ()
rnf Scan' {Maybe Natural
Maybe [VolumeDetail]
Maybe Text
Maybe POSIX
Maybe ResourceDetails
Maybe ScanResultDetails
Maybe ScanStatus
Maybe TriggerDetails
triggerDetails :: Maybe TriggerDetails
totalBytes :: Maybe Natural
scanStatus :: Maybe ScanStatus
scanStartTime :: Maybe POSIX
scanResultDetails :: Maybe ScanResultDetails
scanId :: Maybe Text
scanEndTime :: Maybe POSIX
resourceDetails :: Maybe ResourceDetails
fileCount :: Maybe Natural
failureReason :: Maybe Text
detectorId :: Maybe Text
attachedVolumes :: Maybe [VolumeDetail]
adminDetectorId :: Maybe Text
accountId :: Maybe Text
$sel:triggerDetails:Scan' :: Scan -> Maybe TriggerDetails
$sel:totalBytes:Scan' :: Scan -> Maybe Natural
$sel:scanStatus:Scan' :: Scan -> Maybe ScanStatus
$sel:scanStartTime:Scan' :: Scan -> Maybe POSIX
$sel:scanResultDetails:Scan' :: Scan -> Maybe ScanResultDetails
$sel:scanId:Scan' :: Scan -> Maybe Text
$sel:scanEndTime:Scan' :: Scan -> Maybe POSIX
$sel:resourceDetails:Scan' :: Scan -> Maybe ResourceDetails
$sel:fileCount:Scan' :: Scan -> Maybe Natural
$sel:failureReason:Scan' :: Scan -> Maybe Text
$sel:detectorId:Scan' :: Scan -> Maybe Text
$sel:attachedVolumes:Scan' :: Scan -> Maybe [VolumeDetail]
$sel:adminDetectorId:Scan' :: Scan -> Maybe Text
$sel:accountId:Scan' :: Scan -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
adminDetectorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [VolumeDetail]
attachedVolumes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
detectorId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
fileCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceDetails
resourceDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
scanEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
scanId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ScanResultDetails
scanResultDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
scanStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ScanStatus
scanStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
totalBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TriggerDetails
triggerDetails