{-# 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.IoTAnalytics.Types.Datastore
-- 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.IoTAnalytics.Types.Datastore where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTAnalytics.Types.DatastorePartitions
import Amazonka.IoTAnalytics.Types.DatastoreStatus
import Amazonka.IoTAnalytics.Types.DatastoreStorage
import Amazonka.IoTAnalytics.Types.FileFormatConfiguration
import Amazonka.IoTAnalytics.Types.RetentionPeriod
import qualified Amazonka.Prelude as Prelude

-- | Information about a data store.
--
-- /See:/ 'newDatastore' smart constructor.
data Datastore = Datastore'
  { -- | The ARN of the data store.
    Datastore -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | When the data store was created.
    Datastore -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | Contains information about the partition dimensions in a data store.
    Datastore -> Maybe DatastorePartitions
datastorePartitions :: Prelude.Maybe DatastorePartitions,
    -- | Contains the configuration information of file formats. IoT Analytics
    -- data stores support JSON and <https://parquet.apache.org/ Parquet>.
    --
    -- The default file format is JSON. You can specify only one format.
    --
    -- You can\'t change the file format after you create the data store.
    Datastore -> Maybe FileFormatConfiguration
fileFormatConfiguration :: Prelude.Maybe FileFormatConfiguration,
    -- | The last time when a new message arrived in the data store.
    --
    -- IoT Analytics updates this value at most once per minute for Amazon
    -- Simple Storage Service one data store. Hence, the
    -- @lastMessageArrivalTime@ value is an approximation.
    --
    -- This feature only applies to messages that arrived in the data store
    -- after October 23, 2020.
    Datastore -> Maybe POSIX
lastMessageArrivalTime :: Prelude.Maybe Data.POSIX,
    -- | The last time the data store was updated.
    Datastore -> Maybe POSIX
lastUpdateTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the data store.
    Datastore -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | How long, in days, message data is kept for the data store. When
    -- @customerManagedS3@ storage is selected, this parameter is ignored.
    Datastore -> Maybe RetentionPeriod
retentionPeriod :: Prelude.Maybe RetentionPeriod,
    -- | The status of a data store:
    --
    -- [CREATING]
    --     The data store is being created.
    --
    -- [ACTIVE]
    --     The data store has been created and can be used.
    --
    -- [DELETING]
    --     The data store is being deleted.
    Datastore -> Maybe DatastoreStatus
status :: Prelude.Maybe DatastoreStatus,
    -- | Where data in a data store is stored.. You can choose @serviceManagedS3@
    -- storage, @customerManagedS3@ storage, or @iotSiteWiseMultiLayerStorage@
    -- storage. The default is @serviceManagedS3@. You can\'t change the choice
    -- of Amazon S3 storage after your data store is created.
    Datastore -> Maybe DatastoreStorage
storage :: Prelude.Maybe DatastoreStorage
  }
  deriving (Datastore -> Datastore -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Datastore -> Datastore -> Bool
$c/= :: Datastore -> Datastore -> Bool
== :: Datastore -> Datastore -> Bool
$c== :: Datastore -> Datastore -> Bool
Prelude.Eq, ReadPrec [Datastore]
ReadPrec Datastore
Int -> ReadS Datastore
ReadS [Datastore]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Datastore]
$creadListPrec :: ReadPrec [Datastore]
readPrec :: ReadPrec Datastore
$creadPrec :: ReadPrec Datastore
readList :: ReadS [Datastore]
$creadList :: ReadS [Datastore]
readsPrec :: Int -> ReadS Datastore
$creadsPrec :: Int -> ReadS Datastore
Prelude.Read, Int -> Datastore -> ShowS
[Datastore] -> ShowS
Datastore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Datastore] -> ShowS
$cshowList :: [Datastore] -> ShowS
show :: Datastore -> String
$cshow :: Datastore -> String
showsPrec :: Int -> Datastore -> ShowS
$cshowsPrec :: Int -> Datastore -> ShowS
Prelude.Show, forall x. Rep Datastore x -> Datastore
forall x. Datastore -> Rep Datastore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Datastore x -> Datastore
$cfrom :: forall x. Datastore -> Rep Datastore x
Prelude.Generic)

-- |
-- Create a value of 'Datastore' 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:
--
-- 'arn', 'datastore_arn' - The ARN of the data store.
--
-- 'creationTime', 'datastore_creationTime' - When the data store was created.
--
-- 'datastorePartitions', 'datastore_datastorePartitions' - Contains information about the partition dimensions in a data store.
--
-- 'fileFormatConfiguration', 'datastore_fileFormatConfiguration' - Contains the configuration information of file formats. IoT Analytics
-- data stores support JSON and <https://parquet.apache.org/ Parquet>.
--
-- The default file format is JSON. You can specify only one format.
--
-- You can\'t change the file format after you create the data store.
--
-- 'lastMessageArrivalTime', 'datastore_lastMessageArrivalTime' - The last time when a new message arrived in the data store.
--
-- IoT Analytics updates this value at most once per minute for Amazon
-- Simple Storage Service one data store. Hence, the
-- @lastMessageArrivalTime@ value is an approximation.
--
-- This feature only applies to messages that arrived in the data store
-- after October 23, 2020.
--
-- 'lastUpdateTime', 'datastore_lastUpdateTime' - The last time the data store was updated.
--
-- 'name', 'datastore_name' - The name of the data store.
--
-- 'retentionPeriod', 'datastore_retentionPeriod' - How long, in days, message data is kept for the data store. When
-- @customerManagedS3@ storage is selected, this parameter is ignored.
--
-- 'status', 'datastore_status' - The status of a data store:
--
-- [CREATING]
--     The data store is being created.
--
-- [ACTIVE]
--     The data store has been created and can be used.
--
-- [DELETING]
--     The data store is being deleted.
--
-- 'storage', 'datastore_storage' - Where data in a data store is stored.. You can choose @serviceManagedS3@
-- storage, @customerManagedS3@ storage, or @iotSiteWiseMultiLayerStorage@
-- storage. The default is @serviceManagedS3@. You can\'t change the choice
-- of Amazon S3 storage after your data store is created.
newDatastore ::
  Datastore
newDatastore :: Datastore
newDatastore =
  Datastore'
    { $sel:arn:Datastore' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:Datastore' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:datastorePartitions:Datastore' :: Maybe DatastorePartitions
datastorePartitions = forall a. Maybe a
Prelude.Nothing,
      $sel:fileFormatConfiguration:Datastore' :: Maybe FileFormatConfiguration
fileFormatConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:lastMessageArrivalTime:Datastore' :: Maybe POSIX
lastMessageArrivalTime = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdateTime:Datastore' :: Maybe POSIX
lastUpdateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Datastore' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:retentionPeriod:Datastore' :: Maybe RetentionPeriod
retentionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Datastore' :: Maybe DatastoreStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:storage:Datastore' :: Maybe DatastoreStorage
storage = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the data store.
datastore_arn :: Lens.Lens' Datastore (Prelude.Maybe Prelude.Text)
datastore_arn :: Lens' Datastore (Maybe Text)
datastore_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe Text
arn :: Maybe Text
$sel:arn:Datastore' :: Datastore -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Datastore
s@Datastore' {} Maybe Text
a -> Datastore
s {$sel:arn:Datastore' :: Maybe Text
arn = Maybe Text
a} :: Datastore)

-- | When the data store was created.
datastore_creationTime :: Lens.Lens' Datastore (Prelude.Maybe Prelude.UTCTime)
datastore_creationTime :: Lens' Datastore (Maybe UTCTime)
datastore_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:Datastore' :: Datastore -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: Datastore
s@Datastore' {} Maybe POSIX
a -> Datastore
s {$sel:creationTime:Datastore' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: Datastore) 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

-- | Contains information about the partition dimensions in a data store.
datastore_datastorePartitions :: Lens.Lens' Datastore (Prelude.Maybe DatastorePartitions)
datastore_datastorePartitions :: Lens' Datastore (Maybe DatastorePartitions)
datastore_datastorePartitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe DatastorePartitions
datastorePartitions :: Maybe DatastorePartitions
$sel:datastorePartitions:Datastore' :: Datastore -> Maybe DatastorePartitions
datastorePartitions} -> Maybe DatastorePartitions
datastorePartitions) (\s :: Datastore
s@Datastore' {} Maybe DatastorePartitions
a -> Datastore
s {$sel:datastorePartitions:Datastore' :: Maybe DatastorePartitions
datastorePartitions = Maybe DatastorePartitions
a} :: Datastore)

-- | Contains the configuration information of file formats. IoT Analytics
-- data stores support JSON and <https://parquet.apache.org/ Parquet>.
--
-- The default file format is JSON. You can specify only one format.
--
-- You can\'t change the file format after you create the data store.
datastore_fileFormatConfiguration :: Lens.Lens' Datastore (Prelude.Maybe FileFormatConfiguration)
datastore_fileFormatConfiguration :: Lens' Datastore (Maybe FileFormatConfiguration)
datastore_fileFormatConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe FileFormatConfiguration
fileFormatConfiguration :: Maybe FileFormatConfiguration
$sel:fileFormatConfiguration:Datastore' :: Datastore -> Maybe FileFormatConfiguration
fileFormatConfiguration} -> Maybe FileFormatConfiguration
fileFormatConfiguration) (\s :: Datastore
s@Datastore' {} Maybe FileFormatConfiguration
a -> Datastore
s {$sel:fileFormatConfiguration:Datastore' :: Maybe FileFormatConfiguration
fileFormatConfiguration = Maybe FileFormatConfiguration
a} :: Datastore)

-- | The last time when a new message arrived in the data store.
--
-- IoT Analytics updates this value at most once per minute for Amazon
-- Simple Storage Service one data store. Hence, the
-- @lastMessageArrivalTime@ value is an approximation.
--
-- This feature only applies to messages that arrived in the data store
-- after October 23, 2020.
datastore_lastMessageArrivalTime :: Lens.Lens' Datastore (Prelude.Maybe Prelude.UTCTime)
datastore_lastMessageArrivalTime :: Lens' Datastore (Maybe UTCTime)
datastore_lastMessageArrivalTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe POSIX
lastMessageArrivalTime :: Maybe POSIX
$sel:lastMessageArrivalTime:Datastore' :: Datastore -> Maybe POSIX
lastMessageArrivalTime} -> Maybe POSIX
lastMessageArrivalTime) (\s :: Datastore
s@Datastore' {} Maybe POSIX
a -> Datastore
s {$sel:lastMessageArrivalTime:Datastore' :: Maybe POSIX
lastMessageArrivalTime = Maybe POSIX
a} :: Datastore) 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 last time the data store was updated.
datastore_lastUpdateTime :: Lens.Lens' Datastore (Prelude.Maybe Prelude.UTCTime)
datastore_lastUpdateTime :: Lens' Datastore (Maybe UTCTime)
datastore_lastUpdateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe POSIX
lastUpdateTime :: Maybe POSIX
$sel:lastUpdateTime:Datastore' :: Datastore -> Maybe POSIX
lastUpdateTime} -> Maybe POSIX
lastUpdateTime) (\s :: Datastore
s@Datastore' {} Maybe POSIX
a -> Datastore
s {$sel:lastUpdateTime:Datastore' :: Maybe POSIX
lastUpdateTime = Maybe POSIX
a} :: Datastore) 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 name of the data store.
datastore_name :: Lens.Lens' Datastore (Prelude.Maybe Prelude.Text)
datastore_name :: Lens' Datastore (Maybe Text)
datastore_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe Text
name :: Maybe Text
$sel:name:Datastore' :: Datastore -> Maybe Text
name} -> Maybe Text
name) (\s :: Datastore
s@Datastore' {} Maybe Text
a -> Datastore
s {$sel:name:Datastore' :: Maybe Text
name = Maybe Text
a} :: Datastore)

-- | How long, in days, message data is kept for the data store. When
-- @customerManagedS3@ storage is selected, this parameter is ignored.
datastore_retentionPeriod :: Lens.Lens' Datastore (Prelude.Maybe RetentionPeriod)
datastore_retentionPeriod :: Lens' Datastore (Maybe RetentionPeriod)
datastore_retentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe RetentionPeriod
retentionPeriod :: Maybe RetentionPeriod
$sel:retentionPeriod:Datastore' :: Datastore -> Maybe RetentionPeriod
retentionPeriod} -> Maybe RetentionPeriod
retentionPeriod) (\s :: Datastore
s@Datastore' {} Maybe RetentionPeriod
a -> Datastore
s {$sel:retentionPeriod:Datastore' :: Maybe RetentionPeriod
retentionPeriod = Maybe RetentionPeriod
a} :: Datastore)

-- | The status of a data store:
--
-- [CREATING]
--     The data store is being created.
--
-- [ACTIVE]
--     The data store has been created and can be used.
--
-- [DELETING]
--     The data store is being deleted.
datastore_status :: Lens.Lens' Datastore (Prelude.Maybe DatastoreStatus)
datastore_status :: Lens' Datastore (Maybe DatastoreStatus)
datastore_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe DatastoreStatus
status :: Maybe DatastoreStatus
$sel:status:Datastore' :: Datastore -> Maybe DatastoreStatus
status} -> Maybe DatastoreStatus
status) (\s :: Datastore
s@Datastore' {} Maybe DatastoreStatus
a -> Datastore
s {$sel:status:Datastore' :: Maybe DatastoreStatus
status = Maybe DatastoreStatus
a} :: Datastore)

-- | Where data in a data store is stored.. You can choose @serviceManagedS3@
-- storage, @customerManagedS3@ storage, or @iotSiteWiseMultiLayerStorage@
-- storage. The default is @serviceManagedS3@. You can\'t change the choice
-- of Amazon S3 storage after your data store is created.
datastore_storage :: Lens.Lens' Datastore (Prelude.Maybe DatastoreStorage)
datastore_storage :: Lens' Datastore (Maybe DatastoreStorage)
datastore_storage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Datastore' {Maybe DatastoreStorage
storage :: Maybe DatastoreStorage
$sel:storage:Datastore' :: Datastore -> Maybe DatastoreStorage
storage} -> Maybe DatastoreStorage
storage) (\s :: Datastore
s@Datastore' {} Maybe DatastoreStorage
a -> Datastore
s {$sel:storage:Datastore' :: Maybe DatastoreStorage
storage = Maybe DatastoreStorage
a} :: Datastore)

instance Data.FromJSON Datastore where
  parseJSON :: Value -> Parser Datastore
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Datastore"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe DatastorePartitions
-> Maybe FileFormatConfiguration
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe RetentionPeriod
-> Maybe DatastoreStatus
-> Maybe DatastoreStorage
-> Datastore
Datastore'
            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
"arn")
            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
"creationTime")
            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
"datastorePartitions")
            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
"fileFormatConfiguration")
            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
"lastMessageArrivalTime")
            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
"lastUpdateTime")
            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
"name")
            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
"retentionPeriod")
            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
"status")
            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
"storage")
      )

instance Prelude.Hashable Datastore where
  hashWithSalt :: Int -> Datastore -> Int
hashWithSalt Int
_salt Datastore' {Maybe Text
Maybe POSIX
Maybe DatastoreStatus
Maybe RetentionPeriod
Maybe FileFormatConfiguration
Maybe DatastoreStorage
Maybe DatastorePartitions
storage :: Maybe DatastoreStorage
status :: Maybe DatastoreStatus
retentionPeriod :: Maybe RetentionPeriod
name :: Maybe Text
lastUpdateTime :: Maybe POSIX
lastMessageArrivalTime :: Maybe POSIX
fileFormatConfiguration :: Maybe FileFormatConfiguration
datastorePartitions :: Maybe DatastorePartitions
creationTime :: Maybe POSIX
arn :: Maybe Text
$sel:storage:Datastore' :: Datastore -> Maybe DatastoreStorage
$sel:status:Datastore' :: Datastore -> Maybe DatastoreStatus
$sel:retentionPeriod:Datastore' :: Datastore -> Maybe RetentionPeriod
$sel:name:Datastore' :: Datastore -> Maybe Text
$sel:lastUpdateTime:Datastore' :: Datastore -> Maybe POSIX
$sel:lastMessageArrivalTime:Datastore' :: Datastore -> Maybe POSIX
$sel:fileFormatConfiguration:Datastore' :: Datastore -> Maybe FileFormatConfiguration
$sel:datastorePartitions:Datastore' :: Datastore -> Maybe DatastorePartitions
$sel:creationTime:Datastore' :: Datastore -> Maybe POSIX
$sel:arn:Datastore' :: Datastore -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DatastorePartitions
datastorePartitions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FileFormatConfiguration
fileFormatConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastMessageArrivalTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RetentionPeriod
retentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DatastoreStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DatastoreStorage
storage

instance Prelude.NFData Datastore where
  rnf :: Datastore -> ()
rnf Datastore' {Maybe Text
Maybe POSIX
Maybe DatastoreStatus
Maybe RetentionPeriod
Maybe FileFormatConfiguration
Maybe DatastoreStorage
Maybe DatastorePartitions
storage :: Maybe DatastoreStorage
status :: Maybe DatastoreStatus
retentionPeriod :: Maybe RetentionPeriod
name :: Maybe Text
lastUpdateTime :: Maybe POSIX
lastMessageArrivalTime :: Maybe POSIX
fileFormatConfiguration :: Maybe FileFormatConfiguration
datastorePartitions :: Maybe DatastorePartitions
creationTime :: Maybe POSIX
arn :: Maybe Text
$sel:storage:Datastore' :: Datastore -> Maybe DatastoreStorage
$sel:status:Datastore' :: Datastore -> Maybe DatastoreStatus
$sel:retentionPeriod:Datastore' :: Datastore -> Maybe RetentionPeriod
$sel:name:Datastore' :: Datastore -> Maybe Text
$sel:lastUpdateTime:Datastore' :: Datastore -> Maybe POSIX
$sel:lastMessageArrivalTime:Datastore' :: Datastore -> Maybe POSIX
$sel:fileFormatConfiguration:Datastore' :: Datastore -> Maybe FileFormatConfiguration
$sel:datastorePartitions:Datastore' :: Datastore -> Maybe DatastorePartitions
$sel:creationTime:Datastore' :: Datastore -> Maybe POSIX
$sel:arn:Datastore' :: Datastore -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DatastorePartitions
datastorePartitions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FileFormatConfiguration
fileFormatConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastMessageArrivalTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RetentionPeriod
retentionPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DatastoreStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DatastoreStorage
storage