{-# 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.QuickSight.Types.Ingestion
-- 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.QuickSight.Types.Ingestion 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
import Amazonka.QuickSight.Types.ErrorInfo
import Amazonka.QuickSight.Types.IngestionRequestSource
import Amazonka.QuickSight.Types.IngestionRequestType
import Amazonka.QuickSight.Types.IngestionStatus
import Amazonka.QuickSight.Types.QueueInfo
import Amazonka.QuickSight.Types.RowInfo

-- | Information about the SPICE ingestion for a dataset.
--
-- /See:/ 'newIngestion' smart constructor.
data Ingestion = Ingestion'
  { -- | Error information for this ingestion.
    Ingestion -> Maybe ErrorInfo
errorInfo :: Prelude.Maybe ErrorInfo,
    -- | Ingestion ID.
    Ingestion -> Maybe Text
ingestionId :: Prelude.Maybe Prelude.Text,
    -- | The size of the data ingested, in bytes.
    Ingestion -> Maybe Integer
ingestionSizeInBytes :: Prelude.Maybe Prelude.Integer,
    -- | The time that this ingestion took, measured in seconds.
    Ingestion -> Maybe Integer
ingestionTimeInSeconds :: Prelude.Maybe Prelude.Integer,
    Ingestion -> Maybe QueueInfo
queueInfo :: Prelude.Maybe QueueInfo,
    -- | Event source for this ingestion.
    Ingestion -> Maybe IngestionRequestSource
requestSource :: Prelude.Maybe IngestionRequestSource,
    -- | Type of this ingestion.
    Ingestion -> Maybe IngestionRequestType
requestType :: Prelude.Maybe IngestionRequestType,
    Ingestion -> Maybe RowInfo
rowInfo :: Prelude.Maybe RowInfo,
    -- | The Amazon Resource Name (ARN) of the resource.
    Ingestion -> Text
arn :: Prelude.Text,
    -- | Ingestion status.
    Ingestion -> IngestionStatus
ingestionStatus :: IngestionStatus,
    -- | The time that this ingestion started.
    Ingestion -> POSIX
createdTime :: Data.POSIX
  }
  deriving (Ingestion -> Ingestion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ingestion -> Ingestion -> Bool
$c/= :: Ingestion -> Ingestion -> Bool
== :: Ingestion -> Ingestion -> Bool
$c== :: Ingestion -> Ingestion -> Bool
Prelude.Eq, ReadPrec [Ingestion]
ReadPrec Ingestion
Int -> ReadS Ingestion
ReadS [Ingestion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Ingestion]
$creadListPrec :: ReadPrec [Ingestion]
readPrec :: ReadPrec Ingestion
$creadPrec :: ReadPrec Ingestion
readList :: ReadS [Ingestion]
$creadList :: ReadS [Ingestion]
readsPrec :: Int -> ReadS Ingestion
$creadsPrec :: Int -> ReadS Ingestion
Prelude.Read, Int -> Ingestion -> ShowS
[Ingestion] -> ShowS
Ingestion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ingestion] -> ShowS
$cshowList :: [Ingestion] -> ShowS
show :: Ingestion -> String
$cshow :: Ingestion -> String
showsPrec :: Int -> Ingestion -> ShowS
$cshowsPrec :: Int -> Ingestion -> ShowS
Prelude.Show, forall x. Rep Ingestion x -> Ingestion
forall x. Ingestion -> Rep Ingestion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Ingestion x -> Ingestion
$cfrom :: forall x. Ingestion -> Rep Ingestion x
Prelude.Generic)

-- |
-- Create a value of 'Ingestion' 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:
--
-- 'errorInfo', 'ingestion_errorInfo' - Error information for this ingestion.
--
-- 'ingestionId', 'ingestion_ingestionId' - Ingestion ID.
--
-- 'ingestionSizeInBytes', 'ingestion_ingestionSizeInBytes' - The size of the data ingested, in bytes.
--
-- 'ingestionTimeInSeconds', 'ingestion_ingestionTimeInSeconds' - The time that this ingestion took, measured in seconds.
--
-- 'queueInfo', 'ingestion_queueInfo' - Undocumented member.
--
-- 'requestSource', 'ingestion_requestSource' - Event source for this ingestion.
--
-- 'requestType', 'ingestion_requestType' - Type of this ingestion.
--
-- 'rowInfo', 'ingestion_rowInfo' - Undocumented member.
--
-- 'arn', 'ingestion_arn' - The Amazon Resource Name (ARN) of the resource.
--
-- 'ingestionStatus', 'ingestion_ingestionStatus' - Ingestion status.
--
-- 'createdTime', 'ingestion_createdTime' - The time that this ingestion started.
newIngestion ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'ingestionStatus'
  IngestionStatus ->
  -- | 'createdTime'
  Prelude.UTCTime ->
  Ingestion
newIngestion :: Text -> IngestionStatus -> UTCTime -> Ingestion
newIngestion Text
pArn_ IngestionStatus
pIngestionStatus_ UTCTime
pCreatedTime_ =
  Ingestion'
    { $sel:errorInfo:Ingestion' :: Maybe ErrorInfo
errorInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:ingestionId:Ingestion' :: Maybe Text
ingestionId = forall a. Maybe a
Prelude.Nothing,
      $sel:ingestionSizeInBytes:Ingestion' :: Maybe Integer
ingestionSizeInBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:ingestionTimeInSeconds:Ingestion' :: Maybe Integer
ingestionTimeInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:queueInfo:Ingestion' :: Maybe QueueInfo
queueInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:requestSource:Ingestion' :: Maybe IngestionRequestSource
requestSource = forall a. Maybe a
Prelude.Nothing,
      $sel:requestType:Ingestion' :: Maybe IngestionRequestType
requestType = forall a. Maybe a
Prelude.Nothing,
      $sel:rowInfo:Ingestion' :: Maybe RowInfo
rowInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:Ingestion' :: Text
arn = Text
pArn_,
      $sel:ingestionStatus:Ingestion' :: IngestionStatus
ingestionStatus = IngestionStatus
pIngestionStatus_,
      $sel:createdTime:Ingestion' :: POSIX
createdTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreatedTime_
    }

-- | Error information for this ingestion.
ingestion_errorInfo :: Lens.Lens' Ingestion (Prelude.Maybe ErrorInfo)
ingestion_errorInfo :: Lens' Ingestion (Maybe ErrorInfo)
ingestion_errorInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe ErrorInfo
errorInfo :: Maybe ErrorInfo
$sel:errorInfo:Ingestion' :: Ingestion -> Maybe ErrorInfo
errorInfo} -> Maybe ErrorInfo
errorInfo) (\s :: Ingestion
s@Ingestion' {} Maybe ErrorInfo
a -> Ingestion
s {$sel:errorInfo:Ingestion' :: Maybe ErrorInfo
errorInfo = Maybe ErrorInfo
a} :: Ingestion)

-- | Ingestion ID.
ingestion_ingestionId :: Lens.Lens' Ingestion (Prelude.Maybe Prelude.Text)
ingestion_ingestionId :: Lens' Ingestion (Maybe Text)
ingestion_ingestionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe Text
ingestionId :: Maybe Text
$sel:ingestionId:Ingestion' :: Ingestion -> Maybe Text
ingestionId} -> Maybe Text
ingestionId) (\s :: Ingestion
s@Ingestion' {} Maybe Text
a -> Ingestion
s {$sel:ingestionId:Ingestion' :: Maybe Text
ingestionId = Maybe Text
a} :: Ingestion)

-- | The size of the data ingested, in bytes.
ingestion_ingestionSizeInBytes :: Lens.Lens' Ingestion (Prelude.Maybe Prelude.Integer)
ingestion_ingestionSizeInBytes :: Lens' Ingestion (Maybe Integer)
ingestion_ingestionSizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe Integer
ingestionSizeInBytes :: Maybe Integer
$sel:ingestionSizeInBytes:Ingestion' :: Ingestion -> Maybe Integer
ingestionSizeInBytes} -> Maybe Integer
ingestionSizeInBytes) (\s :: Ingestion
s@Ingestion' {} Maybe Integer
a -> Ingestion
s {$sel:ingestionSizeInBytes:Ingestion' :: Maybe Integer
ingestionSizeInBytes = Maybe Integer
a} :: Ingestion)

-- | The time that this ingestion took, measured in seconds.
ingestion_ingestionTimeInSeconds :: Lens.Lens' Ingestion (Prelude.Maybe Prelude.Integer)
ingestion_ingestionTimeInSeconds :: Lens' Ingestion (Maybe Integer)
ingestion_ingestionTimeInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe Integer
ingestionTimeInSeconds :: Maybe Integer
$sel:ingestionTimeInSeconds:Ingestion' :: Ingestion -> Maybe Integer
ingestionTimeInSeconds} -> Maybe Integer
ingestionTimeInSeconds) (\s :: Ingestion
s@Ingestion' {} Maybe Integer
a -> Ingestion
s {$sel:ingestionTimeInSeconds:Ingestion' :: Maybe Integer
ingestionTimeInSeconds = Maybe Integer
a} :: Ingestion)

-- | Undocumented member.
ingestion_queueInfo :: Lens.Lens' Ingestion (Prelude.Maybe QueueInfo)
ingestion_queueInfo :: Lens' Ingestion (Maybe QueueInfo)
ingestion_queueInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe QueueInfo
queueInfo :: Maybe QueueInfo
$sel:queueInfo:Ingestion' :: Ingestion -> Maybe QueueInfo
queueInfo} -> Maybe QueueInfo
queueInfo) (\s :: Ingestion
s@Ingestion' {} Maybe QueueInfo
a -> Ingestion
s {$sel:queueInfo:Ingestion' :: Maybe QueueInfo
queueInfo = Maybe QueueInfo
a} :: Ingestion)

-- | Event source for this ingestion.
ingestion_requestSource :: Lens.Lens' Ingestion (Prelude.Maybe IngestionRequestSource)
ingestion_requestSource :: Lens' Ingestion (Maybe IngestionRequestSource)
ingestion_requestSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe IngestionRequestSource
requestSource :: Maybe IngestionRequestSource
$sel:requestSource:Ingestion' :: Ingestion -> Maybe IngestionRequestSource
requestSource} -> Maybe IngestionRequestSource
requestSource) (\s :: Ingestion
s@Ingestion' {} Maybe IngestionRequestSource
a -> Ingestion
s {$sel:requestSource:Ingestion' :: Maybe IngestionRequestSource
requestSource = Maybe IngestionRequestSource
a} :: Ingestion)

-- | Type of this ingestion.
ingestion_requestType :: Lens.Lens' Ingestion (Prelude.Maybe IngestionRequestType)
ingestion_requestType :: Lens' Ingestion (Maybe IngestionRequestType)
ingestion_requestType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe IngestionRequestType
requestType :: Maybe IngestionRequestType
$sel:requestType:Ingestion' :: Ingestion -> Maybe IngestionRequestType
requestType} -> Maybe IngestionRequestType
requestType) (\s :: Ingestion
s@Ingestion' {} Maybe IngestionRequestType
a -> Ingestion
s {$sel:requestType:Ingestion' :: Maybe IngestionRequestType
requestType = Maybe IngestionRequestType
a} :: Ingestion)

-- | Undocumented member.
ingestion_rowInfo :: Lens.Lens' Ingestion (Prelude.Maybe RowInfo)
ingestion_rowInfo :: Lens' Ingestion (Maybe RowInfo)
ingestion_rowInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Maybe RowInfo
rowInfo :: Maybe RowInfo
$sel:rowInfo:Ingestion' :: Ingestion -> Maybe RowInfo
rowInfo} -> Maybe RowInfo
rowInfo) (\s :: Ingestion
s@Ingestion' {} Maybe RowInfo
a -> Ingestion
s {$sel:rowInfo:Ingestion' :: Maybe RowInfo
rowInfo = Maybe RowInfo
a} :: Ingestion)

-- | The Amazon Resource Name (ARN) of the resource.
ingestion_arn :: Lens.Lens' Ingestion Prelude.Text
ingestion_arn :: Lens' Ingestion Text
ingestion_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {Text
arn :: Text
$sel:arn:Ingestion' :: Ingestion -> Text
arn} -> Text
arn) (\s :: Ingestion
s@Ingestion' {} Text
a -> Ingestion
s {$sel:arn:Ingestion' :: Text
arn = Text
a} :: Ingestion)

-- | Ingestion status.
ingestion_ingestionStatus :: Lens.Lens' Ingestion IngestionStatus
ingestion_ingestionStatus :: Lens' Ingestion IngestionStatus
ingestion_ingestionStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {IngestionStatus
ingestionStatus :: IngestionStatus
$sel:ingestionStatus:Ingestion' :: Ingestion -> IngestionStatus
ingestionStatus} -> IngestionStatus
ingestionStatus) (\s :: Ingestion
s@Ingestion' {} IngestionStatus
a -> Ingestion
s {$sel:ingestionStatus:Ingestion' :: IngestionStatus
ingestionStatus = IngestionStatus
a} :: Ingestion)

-- | The time that this ingestion started.
ingestion_createdTime :: Lens.Lens' Ingestion Prelude.UTCTime
ingestion_createdTime :: Lens' Ingestion UTCTime
ingestion_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Ingestion' {POSIX
createdTime :: POSIX
$sel:createdTime:Ingestion' :: Ingestion -> POSIX
createdTime} -> POSIX
createdTime) (\s :: Ingestion
s@Ingestion' {} POSIX
a -> Ingestion
s {$sel:createdTime:Ingestion' :: POSIX
createdTime = POSIX
a} :: Ingestion) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON Ingestion where
  parseJSON :: Value -> Parser Ingestion
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Ingestion"
      ( \Object
x ->
          Maybe ErrorInfo
-> Maybe Text
-> Maybe Integer
-> Maybe Integer
-> Maybe QueueInfo
-> Maybe IngestionRequestSource
-> Maybe IngestionRequestType
-> Maybe RowInfo
-> Text
-> IngestionStatus
-> POSIX
-> Ingestion
Ingestion'
            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
"ErrorInfo")
            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
"IngestionId")
            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
"IngestionSizeInBytes")
            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
"IngestionTimeInSeconds")
            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
"QueueInfo")
            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
"RequestSource")
            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
"RequestType")
            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
"RowInfo")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"IngestionStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"CreatedTime")
      )

instance Prelude.Hashable Ingestion where
  hashWithSalt :: Int -> Ingestion -> Int
hashWithSalt Int
_salt Ingestion' {Maybe Integer
Maybe Text
Maybe ErrorInfo
Maybe IngestionRequestSource
Maybe IngestionRequestType
Maybe QueueInfo
Maybe RowInfo
Text
POSIX
IngestionStatus
createdTime :: POSIX
ingestionStatus :: IngestionStatus
arn :: Text
rowInfo :: Maybe RowInfo
requestType :: Maybe IngestionRequestType
requestSource :: Maybe IngestionRequestSource
queueInfo :: Maybe QueueInfo
ingestionTimeInSeconds :: Maybe Integer
ingestionSizeInBytes :: Maybe Integer
ingestionId :: Maybe Text
errorInfo :: Maybe ErrorInfo
$sel:createdTime:Ingestion' :: Ingestion -> POSIX
$sel:ingestionStatus:Ingestion' :: Ingestion -> IngestionStatus
$sel:arn:Ingestion' :: Ingestion -> Text
$sel:rowInfo:Ingestion' :: Ingestion -> Maybe RowInfo
$sel:requestType:Ingestion' :: Ingestion -> Maybe IngestionRequestType
$sel:requestSource:Ingestion' :: Ingestion -> Maybe IngestionRequestSource
$sel:queueInfo:Ingestion' :: Ingestion -> Maybe QueueInfo
$sel:ingestionTimeInSeconds:Ingestion' :: Ingestion -> Maybe Integer
$sel:ingestionSizeInBytes:Ingestion' :: Ingestion -> Maybe Integer
$sel:ingestionId:Ingestion' :: Ingestion -> Maybe Text
$sel:errorInfo:Ingestion' :: Ingestion -> Maybe ErrorInfo
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ErrorInfo
errorInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ingestionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
ingestionSizeInBytes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
ingestionTimeInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe QueueInfo
queueInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IngestionRequestSource
requestSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IngestionRequestType
requestType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RowInfo
rowInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` IngestionStatus
ingestionStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
createdTime

instance Prelude.NFData Ingestion where
  rnf :: Ingestion -> ()
rnf Ingestion' {Maybe Integer
Maybe Text
Maybe ErrorInfo
Maybe IngestionRequestSource
Maybe IngestionRequestType
Maybe QueueInfo
Maybe RowInfo
Text
POSIX
IngestionStatus
createdTime :: POSIX
ingestionStatus :: IngestionStatus
arn :: Text
rowInfo :: Maybe RowInfo
requestType :: Maybe IngestionRequestType
requestSource :: Maybe IngestionRequestSource
queueInfo :: Maybe QueueInfo
ingestionTimeInSeconds :: Maybe Integer
ingestionSizeInBytes :: Maybe Integer
ingestionId :: Maybe Text
errorInfo :: Maybe ErrorInfo
$sel:createdTime:Ingestion' :: Ingestion -> POSIX
$sel:ingestionStatus:Ingestion' :: Ingestion -> IngestionStatus
$sel:arn:Ingestion' :: Ingestion -> Text
$sel:rowInfo:Ingestion' :: Ingestion -> Maybe RowInfo
$sel:requestType:Ingestion' :: Ingestion -> Maybe IngestionRequestType
$sel:requestSource:Ingestion' :: Ingestion -> Maybe IngestionRequestSource
$sel:queueInfo:Ingestion' :: Ingestion -> Maybe QueueInfo
$sel:ingestionTimeInSeconds:Ingestion' :: Ingestion -> Maybe Integer
$sel:ingestionSizeInBytes:Ingestion' :: Ingestion -> Maybe Integer
$sel:ingestionId:Ingestion' :: Ingestion -> Maybe Text
$sel:errorInfo:Ingestion' :: Ingestion -> Maybe ErrorInfo
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ErrorInfo
errorInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ingestionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
ingestionSizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
ingestionTimeInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QueueInfo
queueInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IngestionRequestSource
requestSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe IngestionRequestType
requestType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RowInfo
rowInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf IngestionStatus
ingestionStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
createdTime