{-# 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.IoT.Types.TaskStatistics
-- 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.IoT.Types.TaskStatistics where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Statistics for the checks performed during the audit.
--
-- /See:/ 'newTaskStatistics' smart constructor.
data TaskStatistics = TaskStatistics'
  { -- | The number of checks that did not run because the audit was canceled.
    TaskStatistics -> Maybe Int
canceledChecks :: Prelude.Maybe Prelude.Int,
    -- | The number of checks that found compliant resources.
    TaskStatistics -> Maybe Int
compliantChecks :: Prelude.Maybe Prelude.Int,
    -- | The number of checks.
    TaskStatistics -> Maybe Int
failedChecks :: Prelude.Maybe Prelude.Int,
    -- | The number of checks in progress.
    TaskStatistics -> Maybe Int
inProgressChecks :: Prelude.Maybe Prelude.Int,
    -- | The number of checks that found noncompliant resources.
    TaskStatistics -> Maybe Int
nonCompliantChecks :: Prelude.Maybe Prelude.Int,
    -- | The number of checks in this audit.
    TaskStatistics -> Maybe Int
totalChecks :: Prelude.Maybe Prelude.Int,
    -- | The number of checks waiting for data collection.
    TaskStatistics -> Maybe Int
waitingForDataCollectionChecks :: Prelude.Maybe Prelude.Int
  }
  deriving (TaskStatistics -> TaskStatistics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TaskStatistics -> TaskStatistics -> Bool
$c/= :: TaskStatistics -> TaskStatistics -> Bool
== :: TaskStatistics -> TaskStatistics -> Bool
$c== :: TaskStatistics -> TaskStatistics -> Bool
Prelude.Eq, ReadPrec [TaskStatistics]
ReadPrec TaskStatistics
Int -> ReadS TaskStatistics
ReadS [TaskStatistics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TaskStatistics]
$creadListPrec :: ReadPrec [TaskStatistics]
readPrec :: ReadPrec TaskStatistics
$creadPrec :: ReadPrec TaskStatistics
readList :: ReadS [TaskStatistics]
$creadList :: ReadS [TaskStatistics]
readsPrec :: Int -> ReadS TaskStatistics
$creadsPrec :: Int -> ReadS TaskStatistics
Prelude.Read, Int -> TaskStatistics -> ShowS
[TaskStatistics] -> ShowS
TaskStatistics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TaskStatistics] -> ShowS
$cshowList :: [TaskStatistics] -> ShowS
show :: TaskStatistics -> String
$cshow :: TaskStatistics -> String
showsPrec :: Int -> TaskStatistics -> ShowS
$cshowsPrec :: Int -> TaskStatistics -> ShowS
Prelude.Show, forall x. Rep TaskStatistics x -> TaskStatistics
forall x. TaskStatistics -> Rep TaskStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TaskStatistics x -> TaskStatistics
$cfrom :: forall x. TaskStatistics -> Rep TaskStatistics x
Prelude.Generic)

-- |
-- Create a value of 'TaskStatistics' 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:
--
-- 'canceledChecks', 'taskStatistics_canceledChecks' - The number of checks that did not run because the audit was canceled.
--
-- 'compliantChecks', 'taskStatistics_compliantChecks' - The number of checks that found compliant resources.
--
-- 'failedChecks', 'taskStatistics_failedChecks' - The number of checks.
--
-- 'inProgressChecks', 'taskStatistics_inProgressChecks' - The number of checks in progress.
--
-- 'nonCompliantChecks', 'taskStatistics_nonCompliantChecks' - The number of checks that found noncompliant resources.
--
-- 'totalChecks', 'taskStatistics_totalChecks' - The number of checks in this audit.
--
-- 'waitingForDataCollectionChecks', 'taskStatistics_waitingForDataCollectionChecks' - The number of checks waiting for data collection.
newTaskStatistics ::
  TaskStatistics
newTaskStatistics :: TaskStatistics
newTaskStatistics =
  TaskStatistics'
    { $sel:canceledChecks:TaskStatistics' :: Maybe Int
canceledChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:compliantChecks:TaskStatistics' :: Maybe Int
compliantChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:failedChecks:TaskStatistics' :: Maybe Int
failedChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:inProgressChecks:TaskStatistics' :: Maybe Int
inProgressChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:nonCompliantChecks:TaskStatistics' :: Maybe Int
nonCompliantChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:totalChecks:TaskStatistics' :: Maybe Int
totalChecks = forall a. Maybe a
Prelude.Nothing,
      $sel:waitingForDataCollectionChecks:TaskStatistics' :: Maybe Int
waitingForDataCollectionChecks = forall a. Maybe a
Prelude.Nothing
    }

-- | The number of checks that did not run because the audit was canceled.
taskStatistics_canceledChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_canceledChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_canceledChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
canceledChecks :: Maybe Int
$sel:canceledChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
canceledChecks} -> Maybe Int
canceledChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:canceledChecks:TaskStatistics' :: Maybe Int
canceledChecks = Maybe Int
a} :: TaskStatistics)

-- | The number of checks that found compliant resources.
taskStatistics_compliantChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_compliantChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_compliantChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
compliantChecks :: Maybe Int
$sel:compliantChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
compliantChecks} -> Maybe Int
compliantChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:compliantChecks:TaskStatistics' :: Maybe Int
compliantChecks = Maybe Int
a} :: TaskStatistics)

-- | The number of checks.
taskStatistics_failedChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_failedChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_failedChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
failedChecks :: Maybe Int
$sel:failedChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
failedChecks} -> Maybe Int
failedChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:failedChecks:TaskStatistics' :: Maybe Int
failedChecks = Maybe Int
a} :: TaskStatistics)

-- | The number of checks in progress.
taskStatistics_inProgressChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_inProgressChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_inProgressChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
inProgressChecks :: Maybe Int
$sel:inProgressChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
inProgressChecks} -> Maybe Int
inProgressChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:inProgressChecks:TaskStatistics' :: Maybe Int
inProgressChecks = Maybe Int
a} :: TaskStatistics)

-- | The number of checks that found noncompliant resources.
taskStatistics_nonCompliantChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_nonCompliantChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_nonCompliantChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
nonCompliantChecks :: Maybe Int
$sel:nonCompliantChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
nonCompliantChecks} -> Maybe Int
nonCompliantChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:nonCompliantChecks:TaskStatistics' :: Maybe Int
nonCompliantChecks = Maybe Int
a} :: TaskStatistics)

-- | The number of checks in this audit.
taskStatistics_totalChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_totalChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_totalChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
totalChecks :: Maybe Int
$sel:totalChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
totalChecks} -> Maybe Int
totalChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:totalChecks:TaskStatistics' :: Maybe Int
totalChecks = Maybe Int
a} :: TaskStatistics)

-- | The number of checks waiting for data collection.
taskStatistics_waitingForDataCollectionChecks :: Lens.Lens' TaskStatistics (Prelude.Maybe Prelude.Int)
taskStatistics_waitingForDataCollectionChecks :: Lens' TaskStatistics (Maybe Int)
taskStatistics_waitingForDataCollectionChecks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TaskStatistics' {Maybe Int
waitingForDataCollectionChecks :: Maybe Int
$sel:waitingForDataCollectionChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
waitingForDataCollectionChecks} -> Maybe Int
waitingForDataCollectionChecks) (\s :: TaskStatistics
s@TaskStatistics' {} Maybe Int
a -> TaskStatistics
s {$sel:waitingForDataCollectionChecks:TaskStatistics' :: Maybe Int
waitingForDataCollectionChecks = Maybe Int
a} :: TaskStatistics)

instance Data.FromJSON TaskStatistics where
  parseJSON :: Value -> Parser TaskStatistics
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TaskStatistics"
      ( \Object
x ->
          Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> TaskStatistics
TaskStatistics'
            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
"canceledChecks")
            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
"compliantChecks")
            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
"failedChecks")
            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
"inProgressChecks")
            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
"nonCompliantChecks")
            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
"totalChecks")
            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
"waitingForDataCollectionChecks")
      )

instance Prelude.Hashable TaskStatistics where
  hashWithSalt :: Int -> TaskStatistics -> Int
hashWithSalt Int
_salt TaskStatistics' {Maybe Int
waitingForDataCollectionChecks :: Maybe Int
totalChecks :: Maybe Int
nonCompliantChecks :: Maybe Int
inProgressChecks :: Maybe Int
failedChecks :: Maybe Int
compliantChecks :: Maybe Int
canceledChecks :: Maybe Int
$sel:waitingForDataCollectionChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:totalChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:nonCompliantChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:inProgressChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:failedChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:compliantChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:canceledChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
canceledChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
compliantChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
failedChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
inProgressChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
nonCompliantChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
totalChecks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
waitingForDataCollectionChecks

instance Prelude.NFData TaskStatistics where
  rnf :: TaskStatistics -> ()
rnf TaskStatistics' {Maybe Int
waitingForDataCollectionChecks :: Maybe Int
totalChecks :: Maybe Int
nonCompliantChecks :: Maybe Int
inProgressChecks :: Maybe Int
failedChecks :: Maybe Int
compliantChecks :: Maybe Int
canceledChecks :: Maybe Int
$sel:waitingForDataCollectionChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:totalChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:nonCompliantChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:inProgressChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:failedChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:compliantChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
$sel:canceledChecks:TaskStatistics' :: TaskStatistics -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
canceledChecks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
compliantChecks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
failedChecks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
inProgressChecks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
nonCompliantChecks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
totalChecks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
waitingForDataCollectionChecks