{-# 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.CloudTrail.Types.ImportStatistics
-- 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.CloudTrail.Types.ImportStatistics 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

-- | Provides statistics for the specified @ImportID@. CloudTrail does not
-- update import statistics in real-time. Returned values for parameters
-- such as @EventsCompleted@ may be lower than the actual value, because
-- CloudTrail updates statistics incrementally over the course of the
-- import.
--
-- /See:/ 'newImportStatistics' smart constructor.
data ImportStatistics = ImportStatistics'
  { -- | The number of trail events imported into the event data store.
    ImportStatistics -> Maybe Integer
eventsCompleted :: Prelude.Maybe Prelude.Integer,
    -- | The number of failed entries.
    ImportStatistics -> Maybe Integer
failedEntries :: Prelude.Maybe Prelude.Integer,
    -- | The number of log files that completed import.
    ImportStatistics -> Maybe Integer
filesCompleted :: Prelude.Maybe Prelude.Integer,
    -- | The number of S3 prefixes that completed import.
    ImportStatistics -> Maybe Integer
prefixesCompleted :: Prelude.Maybe Prelude.Integer,
    -- | The number of S3 prefixes found for the import.
    ImportStatistics -> Maybe Integer
prefixesFound :: Prelude.Maybe Prelude.Integer
  }
  deriving (ImportStatistics -> ImportStatistics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportStatistics -> ImportStatistics -> Bool
$c/= :: ImportStatistics -> ImportStatistics -> Bool
== :: ImportStatistics -> ImportStatistics -> Bool
$c== :: ImportStatistics -> ImportStatistics -> Bool
Prelude.Eq, ReadPrec [ImportStatistics]
ReadPrec ImportStatistics
Int -> ReadS ImportStatistics
ReadS [ImportStatistics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportStatistics]
$creadListPrec :: ReadPrec [ImportStatistics]
readPrec :: ReadPrec ImportStatistics
$creadPrec :: ReadPrec ImportStatistics
readList :: ReadS [ImportStatistics]
$creadList :: ReadS [ImportStatistics]
readsPrec :: Int -> ReadS ImportStatistics
$creadsPrec :: Int -> ReadS ImportStatistics
Prelude.Read, Int -> ImportStatistics -> ShowS
[ImportStatistics] -> ShowS
ImportStatistics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportStatistics] -> ShowS
$cshowList :: [ImportStatistics] -> ShowS
show :: ImportStatistics -> String
$cshow :: ImportStatistics -> String
showsPrec :: Int -> ImportStatistics -> ShowS
$cshowsPrec :: Int -> ImportStatistics -> ShowS
Prelude.Show, forall x. Rep ImportStatistics x -> ImportStatistics
forall x. ImportStatistics -> Rep ImportStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportStatistics x -> ImportStatistics
$cfrom :: forall x. ImportStatistics -> Rep ImportStatistics x
Prelude.Generic)

-- |
-- Create a value of 'ImportStatistics' 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:
--
-- 'eventsCompleted', 'importStatistics_eventsCompleted' - The number of trail events imported into the event data store.
--
-- 'failedEntries', 'importStatistics_failedEntries' - The number of failed entries.
--
-- 'filesCompleted', 'importStatistics_filesCompleted' - The number of log files that completed import.
--
-- 'prefixesCompleted', 'importStatistics_prefixesCompleted' - The number of S3 prefixes that completed import.
--
-- 'prefixesFound', 'importStatistics_prefixesFound' - The number of S3 prefixes found for the import.
newImportStatistics ::
  ImportStatistics
newImportStatistics :: ImportStatistics
newImportStatistics =
  ImportStatistics'
    { $sel:eventsCompleted:ImportStatistics' :: Maybe Integer
eventsCompleted =
        forall a. Maybe a
Prelude.Nothing,
      $sel:failedEntries:ImportStatistics' :: Maybe Integer
failedEntries = forall a. Maybe a
Prelude.Nothing,
      $sel:filesCompleted:ImportStatistics' :: Maybe Integer
filesCompleted = forall a. Maybe a
Prelude.Nothing,
      $sel:prefixesCompleted:ImportStatistics' :: Maybe Integer
prefixesCompleted = forall a. Maybe a
Prelude.Nothing,
      $sel:prefixesFound:ImportStatistics' :: Maybe Integer
prefixesFound = forall a. Maybe a
Prelude.Nothing
    }

-- | The number of trail events imported into the event data store.
importStatistics_eventsCompleted :: Lens.Lens' ImportStatistics (Prelude.Maybe Prelude.Integer)
importStatistics_eventsCompleted :: Lens' ImportStatistics (Maybe Integer)
importStatistics_eventsCompleted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportStatistics' {Maybe Integer
eventsCompleted :: Maybe Integer
$sel:eventsCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
eventsCompleted} -> Maybe Integer
eventsCompleted) (\s :: ImportStatistics
s@ImportStatistics' {} Maybe Integer
a -> ImportStatistics
s {$sel:eventsCompleted:ImportStatistics' :: Maybe Integer
eventsCompleted = Maybe Integer
a} :: ImportStatistics)

-- | The number of failed entries.
importStatistics_failedEntries :: Lens.Lens' ImportStatistics (Prelude.Maybe Prelude.Integer)
importStatistics_failedEntries :: Lens' ImportStatistics (Maybe Integer)
importStatistics_failedEntries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportStatistics' {Maybe Integer
failedEntries :: Maybe Integer
$sel:failedEntries:ImportStatistics' :: ImportStatistics -> Maybe Integer
failedEntries} -> Maybe Integer
failedEntries) (\s :: ImportStatistics
s@ImportStatistics' {} Maybe Integer
a -> ImportStatistics
s {$sel:failedEntries:ImportStatistics' :: Maybe Integer
failedEntries = Maybe Integer
a} :: ImportStatistics)

-- | The number of log files that completed import.
importStatistics_filesCompleted :: Lens.Lens' ImportStatistics (Prelude.Maybe Prelude.Integer)
importStatistics_filesCompleted :: Lens' ImportStatistics (Maybe Integer)
importStatistics_filesCompleted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportStatistics' {Maybe Integer
filesCompleted :: Maybe Integer
$sel:filesCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
filesCompleted} -> Maybe Integer
filesCompleted) (\s :: ImportStatistics
s@ImportStatistics' {} Maybe Integer
a -> ImportStatistics
s {$sel:filesCompleted:ImportStatistics' :: Maybe Integer
filesCompleted = Maybe Integer
a} :: ImportStatistics)

-- | The number of S3 prefixes that completed import.
importStatistics_prefixesCompleted :: Lens.Lens' ImportStatistics (Prelude.Maybe Prelude.Integer)
importStatistics_prefixesCompleted :: Lens' ImportStatistics (Maybe Integer)
importStatistics_prefixesCompleted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportStatistics' {Maybe Integer
prefixesCompleted :: Maybe Integer
$sel:prefixesCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
prefixesCompleted} -> Maybe Integer
prefixesCompleted) (\s :: ImportStatistics
s@ImportStatistics' {} Maybe Integer
a -> ImportStatistics
s {$sel:prefixesCompleted:ImportStatistics' :: Maybe Integer
prefixesCompleted = Maybe Integer
a} :: ImportStatistics)

-- | The number of S3 prefixes found for the import.
importStatistics_prefixesFound :: Lens.Lens' ImportStatistics (Prelude.Maybe Prelude.Integer)
importStatistics_prefixesFound :: Lens' ImportStatistics (Maybe Integer)
importStatistics_prefixesFound = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportStatistics' {Maybe Integer
prefixesFound :: Maybe Integer
$sel:prefixesFound:ImportStatistics' :: ImportStatistics -> Maybe Integer
prefixesFound} -> Maybe Integer
prefixesFound) (\s :: ImportStatistics
s@ImportStatistics' {} Maybe Integer
a -> ImportStatistics
s {$sel:prefixesFound:ImportStatistics' :: Maybe Integer
prefixesFound = Maybe Integer
a} :: ImportStatistics)

instance Data.FromJSON ImportStatistics where
  parseJSON :: Value -> Parser ImportStatistics
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ImportStatistics"
      ( \Object
x ->
          Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> ImportStatistics
ImportStatistics'
            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
"EventsCompleted")
            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
"FailedEntries")
            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
"FilesCompleted")
            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
"PrefixesCompleted")
            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
"PrefixesFound")
      )

instance Prelude.Hashable ImportStatistics where
  hashWithSalt :: Int -> ImportStatistics -> Int
hashWithSalt Int
_salt ImportStatistics' {Maybe Integer
prefixesFound :: Maybe Integer
prefixesCompleted :: Maybe Integer
filesCompleted :: Maybe Integer
failedEntries :: Maybe Integer
eventsCompleted :: Maybe Integer
$sel:prefixesFound:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:prefixesCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:filesCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:failedEntries:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:eventsCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
eventsCompleted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
failedEntries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
filesCompleted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
prefixesCompleted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
prefixesFound

instance Prelude.NFData ImportStatistics where
  rnf :: ImportStatistics -> ()
rnf ImportStatistics' {Maybe Integer
prefixesFound :: Maybe Integer
prefixesCompleted :: Maybe Integer
filesCompleted :: Maybe Integer
failedEntries :: Maybe Integer
eventsCompleted :: Maybe Integer
$sel:prefixesFound:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:prefixesCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:filesCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:failedEntries:ImportStatistics' :: ImportStatistics -> Maybe Integer
$sel:eventsCompleted:ImportStatistics' :: ImportStatistics -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
eventsCompleted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
failedEntries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
filesCompleted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
prefixesCompleted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
prefixesFound