{-# 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.DirectoryService.Types.SharedDirectory
-- 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.DirectoryService.Types.SharedDirectory where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DirectoryService.Types.ShareMethod
import Amazonka.DirectoryService.Types.ShareStatus
import qualified Amazonka.Prelude as Prelude

-- | Details about the shared directory in the directory owner account for
-- which the share request in the directory consumer account has been
-- accepted.
--
-- /See:/ 'newSharedDirectory' smart constructor.
data SharedDirectory = SharedDirectory'
  { -- | The date and time that the shared directory was created.
    SharedDirectory -> Maybe POSIX
createdDateTime :: Prelude.Maybe Data.POSIX,
    -- | The date and time that the shared directory was last updated.
    SharedDirectory -> Maybe POSIX
lastUpdatedDateTime :: Prelude.Maybe Data.POSIX,
    -- | Identifier of the directory owner account, which contains the directory
    -- that has been shared to the consumer account.
    SharedDirectory -> Maybe Text
ownerAccountId :: Prelude.Maybe Prelude.Text,
    -- | Identifier of the directory in the directory owner account.
    SharedDirectory -> Maybe Text
ownerDirectoryId :: Prelude.Maybe Prelude.Text,
    -- | The method used when sharing a directory to determine whether the
    -- directory should be shared within your Amazon Web Services organization
    -- (@ORGANIZATIONS@) or with any Amazon Web Services account by sending a
    -- shared directory request (@HANDSHAKE@).
    SharedDirectory -> Maybe ShareMethod
shareMethod :: Prelude.Maybe ShareMethod,
    -- | A directory share request that is sent by the directory owner to the
    -- directory consumer. The request includes a typed message to help the
    -- directory consumer administrator determine whether to approve or reject
    -- the share invitation.
    SharedDirectory -> Maybe (Sensitive Text)
shareNotes :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | Current directory status of the shared Managed Microsoft AD directory.
    SharedDirectory -> Maybe ShareStatus
shareStatus :: Prelude.Maybe ShareStatus,
    -- | Identifier of the directory consumer account that has access to the
    -- shared directory (@OwnerDirectoryId@) in the directory owner account.
    SharedDirectory -> Maybe Text
sharedAccountId :: Prelude.Maybe Prelude.Text,
    -- | Identifier of the shared directory in the directory consumer account.
    -- This identifier is different for each directory owner account.
    SharedDirectory -> Maybe Text
sharedDirectoryId :: Prelude.Maybe Prelude.Text
  }
  deriving (SharedDirectory -> SharedDirectory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SharedDirectory -> SharedDirectory -> Bool
$c/= :: SharedDirectory -> SharedDirectory -> Bool
== :: SharedDirectory -> SharedDirectory -> Bool
$c== :: SharedDirectory -> SharedDirectory -> Bool
Prelude.Eq, Int -> SharedDirectory -> ShowS
[SharedDirectory] -> ShowS
SharedDirectory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SharedDirectory] -> ShowS
$cshowList :: [SharedDirectory] -> ShowS
show :: SharedDirectory -> String
$cshow :: SharedDirectory -> String
showsPrec :: Int -> SharedDirectory -> ShowS
$cshowsPrec :: Int -> SharedDirectory -> ShowS
Prelude.Show, forall x. Rep SharedDirectory x -> SharedDirectory
forall x. SharedDirectory -> Rep SharedDirectory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SharedDirectory x -> SharedDirectory
$cfrom :: forall x. SharedDirectory -> Rep SharedDirectory x
Prelude.Generic)

-- |
-- Create a value of 'SharedDirectory' 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:
--
-- 'createdDateTime', 'sharedDirectory_createdDateTime' - The date and time that the shared directory was created.
--
-- 'lastUpdatedDateTime', 'sharedDirectory_lastUpdatedDateTime' - The date and time that the shared directory was last updated.
--
-- 'ownerAccountId', 'sharedDirectory_ownerAccountId' - Identifier of the directory owner account, which contains the directory
-- that has been shared to the consumer account.
--
-- 'ownerDirectoryId', 'sharedDirectory_ownerDirectoryId' - Identifier of the directory in the directory owner account.
--
-- 'shareMethod', 'sharedDirectory_shareMethod' - The method used when sharing a directory to determine whether the
-- directory should be shared within your Amazon Web Services organization
-- (@ORGANIZATIONS@) or with any Amazon Web Services account by sending a
-- shared directory request (@HANDSHAKE@).
--
-- 'shareNotes', 'sharedDirectory_shareNotes' - A directory share request that is sent by the directory owner to the
-- directory consumer. The request includes a typed message to help the
-- directory consumer administrator determine whether to approve or reject
-- the share invitation.
--
-- 'shareStatus', 'sharedDirectory_shareStatus' - Current directory status of the shared Managed Microsoft AD directory.
--
-- 'sharedAccountId', 'sharedDirectory_sharedAccountId' - Identifier of the directory consumer account that has access to the
-- shared directory (@OwnerDirectoryId@) in the directory owner account.
--
-- 'sharedDirectoryId', 'sharedDirectory_sharedDirectoryId' - Identifier of the shared directory in the directory consumer account.
-- This identifier is different for each directory owner account.
newSharedDirectory ::
  SharedDirectory
newSharedDirectory :: SharedDirectory
newSharedDirectory =
  SharedDirectory'
    { $sel:createdDateTime:SharedDirectory' :: Maybe POSIX
createdDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedDateTime:SharedDirectory' :: Maybe POSIX
lastUpdatedDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerAccountId:SharedDirectory' :: Maybe Text
ownerAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:ownerDirectoryId:SharedDirectory' :: Maybe Text
ownerDirectoryId = forall a. Maybe a
Prelude.Nothing,
      $sel:shareMethod:SharedDirectory' :: Maybe ShareMethod
shareMethod = forall a. Maybe a
Prelude.Nothing,
      $sel:shareNotes:SharedDirectory' :: Maybe (Sensitive Text)
shareNotes = forall a. Maybe a
Prelude.Nothing,
      $sel:shareStatus:SharedDirectory' :: Maybe ShareStatus
shareStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:sharedAccountId:SharedDirectory' :: Maybe Text
sharedAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:sharedDirectoryId:SharedDirectory' :: Maybe Text
sharedDirectoryId = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time that the shared directory was created.
sharedDirectory_createdDateTime :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.UTCTime)
sharedDirectory_createdDateTime :: Lens' SharedDirectory (Maybe UTCTime)
sharedDirectory_createdDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe POSIX
createdDateTime :: Maybe POSIX
$sel:createdDateTime:SharedDirectory' :: SharedDirectory -> Maybe POSIX
createdDateTime} -> Maybe POSIX
createdDateTime) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe POSIX
a -> SharedDirectory
s {$sel:createdDateTime:SharedDirectory' :: Maybe POSIX
createdDateTime = Maybe POSIX
a} :: SharedDirectory) 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 date and time that the shared directory was last updated.
sharedDirectory_lastUpdatedDateTime :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.UTCTime)
sharedDirectory_lastUpdatedDateTime :: Lens' SharedDirectory (Maybe UTCTime)
sharedDirectory_lastUpdatedDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe POSIX
lastUpdatedDateTime :: Maybe POSIX
$sel:lastUpdatedDateTime:SharedDirectory' :: SharedDirectory -> Maybe POSIX
lastUpdatedDateTime} -> Maybe POSIX
lastUpdatedDateTime) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe POSIX
a -> SharedDirectory
s {$sel:lastUpdatedDateTime:SharedDirectory' :: Maybe POSIX
lastUpdatedDateTime = Maybe POSIX
a} :: SharedDirectory) 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

-- | Identifier of the directory owner account, which contains the directory
-- that has been shared to the consumer account.
sharedDirectory_ownerAccountId :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.Text)
sharedDirectory_ownerAccountId :: Lens' SharedDirectory (Maybe Text)
sharedDirectory_ownerAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe Text
ownerAccountId :: Maybe Text
$sel:ownerAccountId:SharedDirectory' :: SharedDirectory -> Maybe Text
ownerAccountId} -> Maybe Text
ownerAccountId) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe Text
a -> SharedDirectory
s {$sel:ownerAccountId:SharedDirectory' :: Maybe Text
ownerAccountId = Maybe Text
a} :: SharedDirectory)

-- | Identifier of the directory in the directory owner account.
sharedDirectory_ownerDirectoryId :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.Text)
sharedDirectory_ownerDirectoryId :: Lens' SharedDirectory (Maybe Text)
sharedDirectory_ownerDirectoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe Text
ownerDirectoryId :: Maybe Text
$sel:ownerDirectoryId:SharedDirectory' :: SharedDirectory -> Maybe Text
ownerDirectoryId} -> Maybe Text
ownerDirectoryId) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe Text
a -> SharedDirectory
s {$sel:ownerDirectoryId:SharedDirectory' :: Maybe Text
ownerDirectoryId = Maybe Text
a} :: SharedDirectory)

-- | The method used when sharing a directory to determine whether the
-- directory should be shared within your Amazon Web Services organization
-- (@ORGANIZATIONS@) or with any Amazon Web Services account by sending a
-- shared directory request (@HANDSHAKE@).
sharedDirectory_shareMethod :: Lens.Lens' SharedDirectory (Prelude.Maybe ShareMethod)
sharedDirectory_shareMethod :: Lens' SharedDirectory (Maybe ShareMethod)
sharedDirectory_shareMethod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe ShareMethod
shareMethod :: Maybe ShareMethod
$sel:shareMethod:SharedDirectory' :: SharedDirectory -> Maybe ShareMethod
shareMethod} -> Maybe ShareMethod
shareMethod) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe ShareMethod
a -> SharedDirectory
s {$sel:shareMethod:SharedDirectory' :: Maybe ShareMethod
shareMethod = Maybe ShareMethod
a} :: SharedDirectory)

-- | A directory share request that is sent by the directory owner to the
-- directory consumer. The request includes a typed message to help the
-- directory consumer administrator determine whether to approve or reject
-- the share invitation.
sharedDirectory_shareNotes :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.Text)
sharedDirectory_shareNotes :: Lens' SharedDirectory (Maybe Text)
sharedDirectory_shareNotes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe (Sensitive Text)
shareNotes :: Maybe (Sensitive Text)
$sel:shareNotes:SharedDirectory' :: SharedDirectory -> Maybe (Sensitive Text)
shareNotes} -> Maybe (Sensitive Text)
shareNotes) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe (Sensitive Text)
a -> SharedDirectory
s {$sel:shareNotes:SharedDirectory' :: Maybe (Sensitive Text)
shareNotes = Maybe (Sensitive Text)
a} :: SharedDirectory) 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. Iso' (Sensitive a) a
Data._Sensitive

-- | Current directory status of the shared Managed Microsoft AD directory.
sharedDirectory_shareStatus :: Lens.Lens' SharedDirectory (Prelude.Maybe ShareStatus)
sharedDirectory_shareStatus :: Lens' SharedDirectory (Maybe ShareStatus)
sharedDirectory_shareStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe ShareStatus
shareStatus :: Maybe ShareStatus
$sel:shareStatus:SharedDirectory' :: SharedDirectory -> Maybe ShareStatus
shareStatus} -> Maybe ShareStatus
shareStatus) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe ShareStatus
a -> SharedDirectory
s {$sel:shareStatus:SharedDirectory' :: Maybe ShareStatus
shareStatus = Maybe ShareStatus
a} :: SharedDirectory)

-- | Identifier of the directory consumer account that has access to the
-- shared directory (@OwnerDirectoryId@) in the directory owner account.
sharedDirectory_sharedAccountId :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.Text)
sharedDirectory_sharedAccountId :: Lens' SharedDirectory (Maybe Text)
sharedDirectory_sharedAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe Text
sharedAccountId :: Maybe Text
$sel:sharedAccountId:SharedDirectory' :: SharedDirectory -> Maybe Text
sharedAccountId} -> Maybe Text
sharedAccountId) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe Text
a -> SharedDirectory
s {$sel:sharedAccountId:SharedDirectory' :: Maybe Text
sharedAccountId = Maybe Text
a} :: SharedDirectory)

-- | Identifier of the shared directory in the directory consumer account.
-- This identifier is different for each directory owner account.
sharedDirectory_sharedDirectoryId :: Lens.Lens' SharedDirectory (Prelude.Maybe Prelude.Text)
sharedDirectory_sharedDirectoryId :: Lens' SharedDirectory (Maybe Text)
sharedDirectory_sharedDirectoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SharedDirectory' {Maybe Text
sharedDirectoryId :: Maybe Text
$sel:sharedDirectoryId:SharedDirectory' :: SharedDirectory -> Maybe Text
sharedDirectoryId} -> Maybe Text
sharedDirectoryId) (\s :: SharedDirectory
s@SharedDirectory' {} Maybe Text
a -> SharedDirectory
s {$sel:sharedDirectoryId:SharedDirectory' :: Maybe Text
sharedDirectoryId = Maybe Text
a} :: SharedDirectory)

instance Data.FromJSON SharedDirectory where
  parseJSON :: Value -> Parser SharedDirectory
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"SharedDirectory"
      ( \Object
x ->
          Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe ShareMethod
-> Maybe (Sensitive Text)
-> Maybe ShareStatus
-> Maybe Text
-> Maybe Text
-> SharedDirectory
SharedDirectory'
            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
"CreatedDateTime")
            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
"LastUpdatedDateTime")
            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
"OwnerAccountId")
            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
"OwnerDirectoryId")
            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
"ShareMethod")
            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
"ShareNotes")
            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
"ShareStatus")
            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
"SharedAccountId")
            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
"SharedDirectoryId")
      )

instance Prelude.Hashable SharedDirectory where
  hashWithSalt :: Int -> SharedDirectory -> Int
hashWithSalt Int
_salt SharedDirectory' {Maybe Text
Maybe (Sensitive Text)
Maybe POSIX
Maybe ShareMethod
Maybe ShareStatus
sharedDirectoryId :: Maybe Text
sharedAccountId :: Maybe Text
shareStatus :: Maybe ShareStatus
shareNotes :: Maybe (Sensitive Text)
shareMethod :: Maybe ShareMethod
ownerDirectoryId :: Maybe Text
ownerAccountId :: Maybe Text
lastUpdatedDateTime :: Maybe POSIX
createdDateTime :: Maybe POSIX
$sel:sharedDirectoryId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:sharedAccountId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:shareStatus:SharedDirectory' :: SharedDirectory -> Maybe ShareStatus
$sel:shareNotes:SharedDirectory' :: SharedDirectory -> Maybe (Sensitive Text)
$sel:shareMethod:SharedDirectory' :: SharedDirectory -> Maybe ShareMethod
$sel:ownerDirectoryId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:ownerAccountId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:lastUpdatedDateTime:SharedDirectory' :: SharedDirectory -> Maybe POSIX
$sel:createdDateTime:SharedDirectory' :: SharedDirectory -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ownerDirectoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ShareMethod
shareMethod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
shareNotes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ShareStatus
shareStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sharedAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sharedDirectoryId

instance Prelude.NFData SharedDirectory where
  rnf :: SharedDirectory -> ()
rnf SharedDirectory' {Maybe Text
Maybe (Sensitive Text)
Maybe POSIX
Maybe ShareMethod
Maybe ShareStatus
sharedDirectoryId :: Maybe Text
sharedAccountId :: Maybe Text
shareStatus :: Maybe ShareStatus
shareNotes :: Maybe (Sensitive Text)
shareMethod :: Maybe ShareMethod
ownerDirectoryId :: Maybe Text
ownerAccountId :: Maybe Text
lastUpdatedDateTime :: Maybe POSIX
createdDateTime :: Maybe POSIX
$sel:sharedDirectoryId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:sharedAccountId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:shareStatus:SharedDirectory' :: SharedDirectory -> Maybe ShareStatus
$sel:shareNotes:SharedDirectory' :: SharedDirectory -> Maybe (Sensitive Text)
$sel:shareMethod:SharedDirectory' :: SharedDirectory -> Maybe ShareMethod
$sel:ownerDirectoryId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:ownerAccountId:SharedDirectory' :: SharedDirectory -> Maybe Text
$sel:lastUpdatedDateTime:SharedDirectory' :: SharedDirectory -> Maybe POSIX
$sel:createdDateTime:SharedDirectory' :: SharedDirectory -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ownerDirectoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ShareMethod
shareMethod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
shareNotes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ShareStatus
shareStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sharedAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sharedDirectoryId