{-# 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.QLDB.Types.JournalS3ExportDescription
-- 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.QLDB.Types.JournalS3ExportDescription 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.QLDB.Types.ExportStatus
import Amazonka.QLDB.Types.OutputFormat
import Amazonka.QLDB.Types.S3ExportConfiguration

-- | Information about a journal export job, including the ledger name,
-- export ID, creation time, current status, and the parameters of the
-- original export creation request.
--
-- /See:/ 'newJournalS3ExportDescription' smart constructor.
data JournalS3ExportDescription = JournalS3ExportDescription'
  { -- | The output format of the exported journal data.
    JournalS3ExportDescription -> Maybe OutputFormat
outputFormat :: Prelude.Maybe OutputFormat,
    -- | The name of the ledger.
    JournalS3ExportDescription -> Text
ledgerName :: Prelude.Text,
    -- | The UUID (represented in Base62-encoded text) of the journal export job.
    JournalS3ExportDescription -> Text
exportId :: Prelude.Text,
    -- | The date and time, in epoch time format, when the export job was
    -- created. (Epoch time format is the number of seconds elapsed since
    -- 12:00:00 AM January 1, 1970 UTC.)
    JournalS3ExportDescription -> POSIX
exportCreationTime :: Data.POSIX,
    -- | The current state of the journal export job.
    JournalS3ExportDescription -> ExportStatus
status :: ExportStatus,
    -- | The inclusive start date and time for the range of journal contents that
    -- was specified in the original export request.
    JournalS3ExportDescription -> POSIX
inclusiveStartTime :: Data.POSIX,
    -- | The exclusive end date and time for the range of journal contents that
    -- was specified in the original export request.
    JournalS3ExportDescription -> POSIX
exclusiveEndTime :: Data.POSIX,
    JournalS3ExportDescription -> S3ExportConfiguration
s3ExportConfiguration :: S3ExportConfiguration,
    -- | The Amazon Resource Name (ARN) of the IAM role that grants QLDB
    -- permissions for a journal export job to do the following:
    --
    -- -   Write objects into your Amazon Simple Storage Service (Amazon S3)
    --     bucket.
    --
    -- -   (Optional) Use your customer managed key in Key Management Service
    --     (KMS) for server-side encryption of your exported data.
    JournalS3ExportDescription -> Text
roleArn :: Prelude.Text
  }
  deriving (JournalS3ExportDescription -> JournalS3ExportDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JournalS3ExportDescription -> JournalS3ExportDescription -> Bool
$c/= :: JournalS3ExportDescription -> JournalS3ExportDescription -> Bool
== :: JournalS3ExportDescription -> JournalS3ExportDescription -> Bool
$c== :: JournalS3ExportDescription -> JournalS3ExportDescription -> Bool
Prelude.Eq, ReadPrec [JournalS3ExportDescription]
ReadPrec JournalS3ExportDescription
Int -> ReadS JournalS3ExportDescription
ReadS [JournalS3ExportDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JournalS3ExportDescription]
$creadListPrec :: ReadPrec [JournalS3ExportDescription]
readPrec :: ReadPrec JournalS3ExportDescription
$creadPrec :: ReadPrec JournalS3ExportDescription
readList :: ReadS [JournalS3ExportDescription]
$creadList :: ReadS [JournalS3ExportDescription]
readsPrec :: Int -> ReadS JournalS3ExportDescription
$creadsPrec :: Int -> ReadS JournalS3ExportDescription
Prelude.Read, Int -> JournalS3ExportDescription -> ShowS
[JournalS3ExportDescription] -> ShowS
JournalS3ExportDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JournalS3ExportDescription] -> ShowS
$cshowList :: [JournalS3ExportDescription] -> ShowS
show :: JournalS3ExportDescription -> String
$cshow :: JournalS3ExportDescription -> String
showsPrec :: Int -> JournalS3ExportDescription -> ShowS
$cshowsPrec :: Int -> JournalS3ExportDescription -> ShowS
Prelude.Show, forall x.
Rep JournalS3ExportDescription x -> JournalS3ExportDescription
forall x.
JournalS3ExportDescription -> Rep JournalS3ExportDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep JournalS3ExportDescription x -> JournalS3ExportDescription
$cfrom :: forall x.
JournalS3ExportDescription -> Rep JournalS3ExportDescription x
Prelude.Generic)

-- |
-- Create a value of 'JournalS3ExportDescription' 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:
--
-- 'outputFormat', 'journalS3ExportDescription_outputFormat' - The output format of the exported journal data.
--
-- 'ledgerName', 'journalS3ExportDescription_ledgerName' - The name of the ledger.
--
-- 'exportId', 'journalS3ExportDescription_exportId' - The UUID (represented in Base62-encoded text) of the journal export job.
--
-- 'exportCreationTime', 'journalS3ExportDescription_exportCreationTime' - The date and time, in epoch time format, when the export job was
-- created. (Epoch time format is the number of seconds elapsed since
-- 12:00:00 AM January 1, 1970 UTC.)
--
-- 'status', 'journalS3ExportDescription_status' - The current state of the journal export job.
--
-- 'inclusiveStartTime', 'journalS3ExportDescription_inclusiveStartTime' - The inclusive start date and time for the range of journal contents that
-- was specified in the original export request.
--
-- 'exclusiveEndTime', 'journalS3ExportDescription_exclusiveEndTime' - The exclusive end date and time for the range of journal contents that
-- was specified in the original export request.
--
-- 's3ExportConfiguration', 'journalS3ExportDescription_s3ExportConfiguration' - Undocumented member.
--
-- 'roleArn', 'journalS3ExportDescription_roleArn' - The Amazon Resource Name (ARN) of the IAM role that grants QLDB
-- permissions for a journal export job to do the following:
--
-- -   Write objects into your Amazon Simple Storage Service (Amazon S3)
--     bucket.
--
-- -   (Optional) Use your customer managed key in Key Management Service
--     (KMS) for server-side encryption of your exported data.
newJournalS3ExportDescription ::
  -- | 'ledgerName'
  Prelude.Text ->
  -- | 'exportId'
  Prelude.Text ->
  -- | 'exportCreationTime'
  Prelude.UTCTime ->
  -- | 'status'
  ExportStatus ->
  -- | 'inclusiveStartTime'
  Prelude.UTCTime ->
  -- | 'exclusiveEndTime'
  Prelude.UTCTime ->
  -- | 's3ExportConfiguration'
  S3ExportConfiguration ->
  -- | 'roleArn'
  Prelude.Text ->
  JournalS3ExportDescription
newJournalS3ExportDescription :: Text
-> Text
-> UTCTime
-> ExportStatus
-> UTCTime
-> UTCTime
-> S3ExportConfiguration
-> Text
-> JournalS3ExportDescription
newJournalS3ExportDescription
  Text
pLedgerName_
  Text
pExportId_
  UTCTime
pExportCreationTime_
  ExportStatus
pStatus_
  UTCTime
pInclusiveStartTime_
  UTCTime
pExclusiveEndTime_
  S3ExportConfiguration
pS3ExportConfiguration_
  Text
pRoleArn_ =
    JournalS3ExportDescription'
      { $sel:outputFormat:JournalS3ExportDescription' :: Maybe OutputFormat
outputFormat =
          forall a. Maybe a
Prelude.Nothing,
        $sel:ledgerName:JournalS3ExportDescription' :: Text
ledgerName = Text
pLedgerName_,
        $sel:exportId:JournalS3ExportDescription' :: Text
exportId = Text
pExportId_,
        $sel:exportCreationTime:JournalS3ExportDescription' :: POSIX
exportCreationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pExportCreationTime_,
        $sel:status:JournalS3ExportDescription' :: ExportStatus
status = ExportStatus
pStatus_,
        $sel:inclusiveStartTime:JournalS3ExportDescription' :: POSIX
inclusiveStartTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pInclusiveStartTime_,
        $sel:exclusiveEndTime:JournalS3ExportDescription' :: POSIX
exclusiveEndTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pExclusiveEndTime_,
        $sel:s3ExportConfiguration:JournalS3ExportDescription' :: S3ExportConfiguration
s3ExportConfiguration = S3ExportConfiguration
pS3ExportConfiguration_,
        $sel:roleArn:JournalS3ExportDescription' :: Text
roleArn = Text
pRoleArn_
      }

-- | The output format of the exported journal data.
journalS3ExportDescription_outputFormat :: Lens.Lens' JournalS3ExportDescription (Prelude.Maybe OutputFormat)
journalS3ExportDescription_outputFormat :: Lens' JournalS3ExportDescription (Maybe OutputFormat)
journalS3ExportDescription_outputFormat = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {Maybe OutputFormat
outputFormat :: Maybe OutputFormat
$sel:outputFormat:JournalS3ExportDescription' :: JournalS3ExportDescription -> Maybe OutputFormat
outputFormat} -> Maybe OutputFormat
outputFormat) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} Maybe OutputFormat
a -> JournalS3ExportDescription
s {$sel:outputFormat:JournalS3ExportDescription' :: Maybe OutputFormat
outputFormat = Maybe OutputFormat
a} :: JournalS3ExportDescription)

-- | The name of the ledger.
journalS3ExportDescription_ledgerName :: Lens.Lens' JournalS3ExportDescription Prelude.Text
journalS3ExportDescription_ledgerName :: Lens' JournalS3ExportDescription Text
journalS3ExportDescription_ledgerName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {Text
ledgerName :: Text
$sel:ledgerName:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
ledgerName} -> Text
ledgerName) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} Text
a -> JournalS3ExportDescription
s {$sel:ledgerName:JournalS3ExportDescription' :: Text
ledgerName = Text
a} :: JournalS3ExportDescription)

-- | The UUID (represented in Base62-encoded text) of the journal export job.
journalS3ExportDescription_exportId :: Lens.Lens' JournalS3ExportDescription Prelude.Text
journalS3ExportDescription_exportId :: Lens' JournalS3ExportDescription Text
journalS3ExportDescription_exportId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {Text
exportId :: Text
$sel:exportId:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
exportId} -> Text
exportId) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} Text
a -> JournalS3ExportDescription
s {$sel:exportId:JournalS3ExportDescription' :: Text
exportId = Text
a} :: JournalS3ExportDescription)

-- | The date and time, in epoch time format, when the export job was
-- created. (Epoch time format is the number of seconds elapsed since
-- 12:00:00 AM January 1, 1970 UTC.)
journalS3ExportDescription_exportCreationTime :: Lens.Lens' JournalS3ExportDescription Prelude.UTCTime
journalS3ExportDescription_exportCreationTime :: Lens' JournalS3ExportDescription UTCTime
journalS3ExportDescription_exportCreationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {POSIX
exportCreationTime :: POSIX
$sel:exportCreationTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
exportCreationTime} -> POSIX
exportCreationTime) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} POSIX
a -> JournalS3ExportDescription
s {$sel:exportCreationTime:JournalS3ExportDescription' :: POSIX
exportCreationTime = POSIX
a} :: JournalS3ExportDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current state of the journal export job.
journalS3ExportDescription_status :: Lens.Lens' JournalS3ExportDescription ExportStatus
journalS3ExportDescription_status :: Lens' JournalS3ExportDescription ExportStatus
journalS3ExportDescription_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {ExportStatus
status :: ExportStatus
$sel:status:JournalS3ExportDescription' :: JournalS3ExportDescription -> ExportStatus
status} -> ExportStatus
status) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} ExportStatus
a -> JournalS3ExportDescription
s {$sel:status:JournalS3ExportDescription' :: ExportStatus
status = ExportStatus
a} :: JournalS3ExportDescription)

-- | The inclusive start date and time for the range of journal contents that
-- was specified in the original export request.
journalS3ExportDescription_inclusiveStartTime :: Lens.Lens' JournalS3ExportDescription Prelude.UTCTime
journalS3ExportDescription_inclusiveStartTime :: Lens' JournalS3ExportDescription UTCTime
journalS3ExportDescription_inclusiveStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {POSIX
inclusiveStartTime :: POSIX
$sel:inclusiveStartTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
inclusiveStartTime} -> POSIX
inclusiveStartTime) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} POSIX
a -> JournalS3ExportDescription
s {$sel:inclusiveStartTime:JournalS3ExportDescription' :: POSIX
inclusiveStartTime = POSIX
a} :: JournalS3ExportDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The exclusive end date and time for the range of journal contents that
-- was specified in the original export request.
journalS3ExportDescription_exclusiveEndTime :: Lens.Lens' JournalS3ExportDescription Prelude.UTCTime
journalS3ExportDescription_exclusiveEndTime :: Lens' JournalS3ExportDescription UTCTime
journalS3ExportDescription_exclusiveEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {POSIX
exclusiveEndTime :: POSIX
$sel:exclusiveEndTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
exclusiveEndTime} -> POSIX
exclusiveEndTime) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} POSIX
a -> JournalS3ExportDescription
s {$sel:exclusiveEndTime:JournalS3ExportDescription' :: POSIX
exclusiveEndTime = POSIX
a} :: JournalS3ExportDescription) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Undocumented member.
journalS3ExportDescription_s3ExportConfiguration :: Lens.Lens' JournalS3ExportDescription S3ExportConfiguration
journalS3ExportDescription_s3ExportConfiguration :: Lens' JournalS3ExportDescription S3ExportConfiguration
journalS3ExportDescription_s3ExportConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {S3ExportConfiguration
s3ExportConfiguration :: S3ExportConfiguration
$sel:s3ExportConfiguration:JournalS3ExportDescription' :: JournalS3ExportDescription -> S3ExportConfiguration
s3ExportConfiguration} -> S3ExportConfiguration
s3ExportConfiguration) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} S3ExportConfiguration
a -> JournalS3ExportDescription
s {$sel:s3ExportConfiguration:JournalS3ExportDescription' :: S3ExportConfiguration
s3ExportConfiguration = S3ExportConfiguration
a} :: JournalS3ExportDescription)

-- | The Amazon Resource Name (ARN) of the IAM role that grants QLDB
-- permissions for a journal export job to do the following:
--
-- -   Write objects into your Amazon Simple Storage Service (Amazon S3)
--     bucket.
--
-- -   (Optional) Use your customer managed key in Key Management Service
--     (KMS) for server-side encryption of your exported data.
journalS3ExportDescription_roleArn :: Lens.Lens' JournalS3ExportDescription Prelude.Text
journalS3ExportDescription_roleArn :: Lens' JournalS3ExportDescription Text
journalS3ExportDescription_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JournalS3ExportDescription' {Text
roleArn :: Text
$sel:roleArn:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
roleArn} -> Text
roleArn) (\s :: JournalS3ExportDescription
s@JournalS3ExportDescription' {} Text
a -> JournalS3ExportDescription
s {$sel:roleArn:JournalS3ExportDescription' :: Text
roleArn = Text
a} :: JournalS3ExportDescription)

instance Data.FromJSON JournalS3ExportDescription where
  parseJSON :: Value -> Parser JournalS3ExportDescription
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JournalS3ExportDescription"
      ( \Object
x ->
          Maybe OutputFormat
-> Text
-> Text
-> POSIX
-> ExportStatus
-> POSIX
-> POSIX
-> S3ExportConfiguration
-> Text
-> JournalS3ExportDescription
JournalS3ExportDescription'
            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
"OutputFormat")
            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
"LedgerName")
            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
"ExportId")
            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
"ExportCreationTime")
            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
"Status")
            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
"InclusiveStartTime")
            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
"ExclusiveEndTime")
            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
"S3ExportConfiguration")
            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
"RoleArn")
      )

instance Prelude.Hashable JournalS3ExportDescription where
  hashWithSalt :: Int -> JournalS3ExportDescription -> Int
hashWithSalt Int
_salt JournalS3ExportDescription' {Maybe OutputFormat
Text
POSIX
ExportStatus
S3ExportConfiguration
roleArn :: Text
s3ExportConfiguration :: S3ExportConfiguration
exclusiveEndTime :: POSIX
inclusiveStartTime :: POSIX
status :: ExportStatus
exportCreationTime :: POSIX
exportId :: Text
ledgerName :: Text
outputFormat :: Maybe OutputFormat
$sel:roleArn:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
$sel:s3ExportConfiguration:JournalS3ExportDescription' :: JournalS3ExportDescription -> S3ExportConfiguration
$sel:exclusiveEndTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
$sel:inclusiveStartTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
$sel:status:JournalS3ExportDescription' :: JournalS3ExportDescription -> ExportStatus
$sel:exportCreationTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
$sel:exportId:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
$sel:ledgerName:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
$sel:outputFormat:JournalS3ExportDescription' :: JournalS3ExportDescription -> Maybe OutputFormat
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutputFormat
outputFormat
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ledgerName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
exportId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
exportCreationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ExportStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
inclusiveStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
exclusiveEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` S3ExportConfiguration
s3ExportConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData JournalS3ExportDescription where
  rnf :: JournalS3ExportDescription -> ()
rnf JournalS3ExportDescription' {Maybe OutputFormat
Text
POSIX
ExportStatus
S3ExportConfiguration
roleArn :: Text
s3ExportConfiguration :: S3ExportConfiguration
exclusiveEndTime :: POSIX
inclusiveStartTime :: POSIX
status :: ExportStatus
exportCreationTime :: POSIX
exportId :: Text
ledgerName :: Text
outputFormat :: Maybe OutputFormat
$sel:roleArn:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
$sel:s3ExportConfiguration:JournalS3ExportDescription' :: JournalS3ExportDescription -> S3ExportConfiguration
$sel:exclusiveEndTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
$sel:inclusiveStartTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
$sel:status:JournalS3ExportDescription' :: JournalS3ExportDescription -> ExportStatus
$sel:exportCreationTime:JournalS3ExportDescription' :: JournalS3ExportDescription -> POSIX
$sel:exportId:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
$sel:ledgerName:JournalS3ExportDescription' :: JournalS3ExportDescription -> Text
$sel:outputFormat:JournalS3ExportDescription' :: JournalS3ExportDescription -> Maybe OutputFormat
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe OutputFormat
outputFormat
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ledgerName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
exportId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
exportCreationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ExportStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
inclusiveStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
exclusiveEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf S3ExportConfiguration
s3ExportConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn