{-# 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.Trust
-- 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.Trust 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.SelectiveAuth
import Amazonka.DirectoryService.Types.TrustDirection
import Amazonka.DirectoryService.Types.TrustState
import Amazonka.DirectoryService.Types.TrustType
import qualified Amazonka.Prelude as Prelude

-- | Describes a trust relationship between an Managed Microsoft AD directory
-- and an external domain.
--
-- /See:/ 'newTrust' smart constructor.
data Trust = Trust'
  { -- | The date and time that the trust relationship was created.
    Trust -> Maybe POSIX
createdDateTime :: Prelude.Maybe Data.POSIX,
    -- | The Directory ID of the Amazon Web Services directory involved in the
    -- trust relationship.
    Trust -> Maybe Text
directoryId :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the trust relationship was last updated.
    Trust -> Maybe POSIX
lastUpdatedDateTime :: Prelude.Maybe Data.POSIX,
    -- | The Fully Qualified Domain Name (FQDN) of the external domain involved
    -- in the trust relationship.
    Trust -> Maybe Text
remoteDomainName :: Prelude.Maybe Prelude.Text,
    -- | Current state of selective authentication for the trust.
    Trust -> Maybe SelectiveAuth
selectiveAuth :: Prelude.Maybe SelectiveAuth,
    -- | The date and time that the TrustState was last updated.
    Trust -> Maybe POSIX
stateLastUpdatedDateTime :: Prelude.Maybe Data.POSIX,
    -- | The trust relationship direction.
    Trust -> Maybe TrustDirection
trustDirection :: Prelude.Maybe TrustDirection,
    -- | The unique ID of the trust relationship.
    Trust -> Maybe Text
trustId :: Prelude.Maybe Prelude.Text,
    -- | The trust relationship state.
    Trust -> Maybe TrustState
trustState :: Prelude.Maybe TrustState,
    -- | The reason for the TrustState.
    Trust -> Maybe Text
trustStateReason :: Prelude.Maybe Prelude.Text,
    -- | The trust relationship type. @Forest@ is the default.
    Trust -> Maybe TrustType
trustType :: Prelude.Maybe TrustType
  }
  deriving (Trust -> Trust -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Trust -> Trust -> Bool
$c/= :: Trust -> Trust -> Bool
== :: Trust -> Trust -> Bool
$c== :: Trust -> Trust -> Bool
Prelude.Eq, ReadPrec [Trust]
ReadPrec Trust
Int -> ReadS Trust
ReadS [Trust]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Trust]
$creadListPrec :: ReadPrec [Trust]
readPrec :: ReadPrec Trust
$creadPrec :: ReadPrec Trust
readList :: ReadS [Trust]
$creadList :: ReadS [Trust]
readsPrec :: Int -> ReadS Trust
$creadsPrec :: Int -> ReadS Trust
Prelude.Read, Int -> Trust -> ShowS
[Trust] -> ShowS
Trust -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Trust] -> ShowS
$cshowList :: [Trust] -> ShowS
show :: Trust -> String
$cshow :: Trust -> String
showsPrec :: Int -> Trust -> ShowS
$cshowsPrec :: Int -> Trust -> ShowS
Prelude.Show, forall x. Rep Trust x -> Trust
forall x. Trust -> Rep Trust x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Trust x -> Trust
$cfrom :: forall x. Trust -> Rep Trust x
Prelude.Generic)

-- |
-- Create a value of 'Trust' 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', 'trust_createdDateTime' - The date and time that the trust relationship was created.
--
-- 'directoryId', 'trust_directoryId' - The Directory ID of the Amazon Web Services directory involved in the
-- trust relationship.
--
-- 'lastUpdatedDateTime', 'trust_lastUpdatedDateTime' - The date and time that the trust relationship was last updated.
--
-- 'remoteDomainName', 'trust_remoteDomainName' - The Fully Qualified Domain Name (FQDN) of the external domain involved
-- in the trust relationship.
--
-- 'selectiveAuth', 'trust_selectiveAuth' - Current state of selective authentication for the trust.
--
-- 'stateLastUpdatedDateTime', 'trust_stateLastUpdatedDateTime' - The date and time that the TrustState was last updated.
--
-- 'trustDirection', 'trust_trustDirection' - The trust relationship direction.
--
-- 'trustId', 'trust_trustId' - The unique ID of the trust relationship.
--
-- 'trustState', 'trust_trustState' - The trust relationship state.
--
-- 'trustStateReason', 'trust_trustStateReason' - The reason for the TrustState.
--
-- 'trustType', 'trust_trustType' - The trust relationship type. @Forest@ is the default.
newTrust ::
  Trust
newTrust :: Trust
newTrust =
  Trust'
    { $sel:createdDateTime:Trust' :: Maybe POSIX
createdDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:directoryId:Trust' :: Maybe Text
directoryId = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedDateTime:Trust' :: Maybe POSIX
lastUpdatedDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:remoteDomainName:Trust' :: Maybe Text
remoteDomainName = forall a. Maybe a
Prelude.Nothing,
      $sel:selectiveAuth:Trust' :: Maybe SelectiveAuth
selectiveAuth = forall a. Maybe a
Prelude.Nothing,
      $sel:stateLastUpdatedDateTime:Trust' :: Maybe POSIX
stateLastUpdatedDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:trustDirection:Trust' :: Maybe TrustDirection
trustDirection = forall a. Maybe a
Prelude.Nothing,
      $sel:trustId:Trust' :: Maybe Text
trustId = forall a. Maybe a
Prelude.Nothing,
      $sel:trustState:Trust' :: Maybe TrustState
trustState = forall a. Maybe a
Prelude.Nothing,
      $sel:trustStateReason:Trust' :: Maybe Text
trustStateReason = forall a. Maybe a
Prelude.Nothing,
      $sel:trustType:Trust' :: Maybe TrustType
trustType = forall a. Maybe a
Prelude.Nothing
    }

-- | The date and time that the trust relationship was created.
trust_createdDateTime :: Lens.Lens' Trust (Prelude.Maybe Prelude.UTCTime)
trust_createdDateTime :: Lens' Trust (Maybe UTCTime)
trust_createdDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe POSIX
createdDateTime :: Maybe POSIX
$sel:createdDateTime:Trust' :: Trust -> Maybe POSIX
createdDateTime} -> Maybe POSIX
createdDateTime) (\s :: Trust
s@Trust' {} Maybe POSIX
a -> Trust
s {$sel:createdDateTime:Trust' :: Maybe POSIX
createdDateTime = Maybe POSIX
a} :: Trust) 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 Directory ID of the Amazon Web Services directory involved in the
-- trust relationship.
trust_directoryId :: Lens.Lens' Trust (Prelude.Maybe Prelude.Text)
trust_directoryId :: Lens' Trust (Maybe Text)
trust_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe Text
directoryId :: Maybe Text
$sel:directoryId:Trust' :: Trust -> Maybe Text
directoryId} -> Maybe Text
directoryId) (\s :: Trust
s@Trust' {} Maybe Text
a -> Trust
s {$sel:directoryId:Trust' :: Maybe Text
directoryId = Maybe Text
a} :: Trust)

-- | The date and time that the trust relationship was last updated.
trust_lastUpdatedDateTime :: Lens.Lens' Trust (Prelude.Maybe Prelude.UTCTime)
trust_lastUpdatedDateTime :: Lens' Trust (Maybe UTCTime)
trust_lastUpdatedDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe POSIX
lastUpdatedDateTime :: Maybe POSIX
$sel:lastUpdatedDateTime:Trust' :: Trust -> Maybe POSIX
lastUpdatedDateTime} -> Maybe POSIX
lastUpdatedDateTime) (\s :: Trust
s@Trust' {} Maybe POSIX
a -> Trust
s {$sel:lastUpdatedDateTime:Trust' :: Maybe POSIX
lastUpdatedDateTime = Maybe POSIX
a} :: Trust) 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 Fully Qualified Domain Name (FQDN) of the external domain involved
-- in the trust relationship.
trust_remoteDomainName :: Lens.Lens' Trust (Prelude.Maybe Prelude.Text)
trust_remoteDomainName :: Lens' Trust (Maybe Text)
trust_remoteDomainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe Text
remoteDomainName :: Maybe Text
$sel:remoteDomainName:Trust' :: Trust -> Maybe Text
remoteDomainName} -> Maybe Text
remoteDomainName) (\s :: Trust
s@Trust' {} Maybe Text
a -> Trust
s {$sel:remoteDomainName:Trust' :: Maybe Text
remoteDomainName = Maybe Text
a} :: Trust)

-- | Current state of selective authentication for the trust.
trust_selectiveAuth :: Lens.Lens' Trust (Prelude.Maybe SelectiveAuth)
trust_selectiveAuth :: Lens' Trust (Maybe SelectiveAuth)
trust_selectiveAuth = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe SelectiveAuth
selectiveAuth :: Maybe SelectiveAuth
$sel:selectiveAuth:Trust' :: Trust -> Maybe SelectiveAuth
selectiveAuth} -> Maybe SelectiveAuth
selectiveAuth) (\s :: Trust
s@Trust' {} Maybe SelectiveAuth
a -> Trust
s {$sel:selectiveAuth:Trust' :: Maybe SelectiveAuth
selectiveAuth = Maybe SelectiveAuth
a} :: Trust)

-- | The date and time that the TrustState was last updated.
trust_stateLastUpdatedDateTime :: Lens.Lens' Trust (Prelude.Maybe Prelude.UTCTime)
trust_stateLastUpdatedDateTime :: Lens' Trust (Maybe UTCTime)
trust_stateLastUpdatedDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe POSIX
stateLastUpdatedDateTime :: Maybe POSIX
$sel:stateLastUpdatedDateTime:Trust' :: Trust -> Maybe POSIX
stateLastUpdatedDateTime} -> Maybe POSIX
stateLastUpdatedDateTime) (\s :: Trust
s@Trust' {} Maybe POSIX
a -> Trust
s {$sel:stateLastUpdatedDateTime:Trust' :: Maybe POSIX
stateLastUpdatedDateTime = Maybe POSIX
a} :: Trust) 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 trust relationship direction.
trust_trustDirection :: Lens.Lens' Trust (Prelude.Maybe TrustDirection)
trust_trustDirection :: Lens' Trust (Maybe TrustDirection)
trust_trustDirection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe TrustDirection
trustDirection :: Maybe TrustDirection
$sel:trustDirection:Trust' :: Trust -> Maybe TrustDirection
trustDirection} -> Maybe TrustDirection
trustDirection) (\s :: Trust
s@Trust' {} Maybe TrustDirection
a -> Trust
s {$sel:trustDirection:Trust' :: Maybe TrustDirection
trustDirection = Maybe TrustDirection
a} :: Trust)

-- | The unique ID of the trust relationship.
trust_trustId :: Lens.Lens' Trust (Prelude.Maybe Prelude.Text)
trust_trustId :: Lens' Trust (Maybe Text)
trust_trustId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe Text
trustId :: Maybe Text
$sel:trustId:Trust' :: Trust -> Maybe Text
trustId} -> Maybe Text
trustId) (\s :: Trust
s@Trust' {} Maybe Text
a -> Trust
s {$sel:trustId:Trust' :: Maybe Text
trustId = Maybe Text
a} :: Trust)

-- | The trust relationship state.
trust_trustState :: Lens.Lens' Trust (Prelude.Maybe TrustState)
trust_trustState :: Lens' Trust (Maybe TrustState)
trust_trustState = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe TrustState
trustState :: Maybe TrustState
$sel:trustState:Trust' :: Trust -> Maybe TrustState
trustState} -> Maybe TrustState
trustState) (\s :: Trust
s@Trust' {} Maybe TrustState
a -> Trust
s {$sel:trustState:Trust' :: Maybe TrustState
trustState = Maybe TrustState
a} :: Trust)

-- | The reason for the TrustState.
trust_trustStateReason :: Lens.Lens' Trust (Prelude.Maybe Prelude.Text)
trust_trustStateReason :: Lens' Trust (Maybe Text)
trust_trustStateReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe Text
trustStateReason :: Maybe Text
$sel:trustStateReason:Trust' :: Trust -> Maybe Text
trustStateReason} -> Maybe Text
trustStateReason) (\s :: Trust
s@Trust' {} Maybe Text
a -> Trust
s {$sel:trustStateReason:Trust' :: Maybe Text
trustStateReason = Maybe Text
a} :: Trust)

-- | The trust relationship type. @Forest@ is the default.
trust_trustType :: Lens.Lens' Trust (Prelude.Maybe TrustType)
trust_trustType :: Lens' Trust (Maybe TrustType)
trust_trustType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Trust' {Maybe TrustType
trustType :: Maybe TrustType
$sel:trustType:Trust' :: Trust -> Maybe TrustType
trustType} -> Maybe TrustType
trustType) (\s :: Trust
s@Trust' {} Maybe TrustType
a -> Trust
s {$sel:trustType:Trust' :: Maybe TrustType
trustType = Maybe TrustType
a} :: Trust)

instance Data.FromJSON Trust where
  parseJSON :: Value -> Parser Trust
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Trust"
      ( \Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe SelectiveAuth
-> Maybe POSIX
-> Maybe TrustDirection
-> Maybe Text
-> Maybe TrustState
-> Maybe Text
-> Maybe TrustType
-> Trust
Trust'
            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
"DirectoryId")
            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
"RemoteDomainName")
            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
"SelectiveAuth")
            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
"StateLastUpdatedDateTime")
            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
"TrustDirection")
            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
"TrustId")
            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
"TrustState")
            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
"TrustStateReason")
            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
"TrustType")
      )

instance Prelude.Hashable Trust where
  hashWithSalt :: Int -> Trust -> Int
hashWithSalt Int
_salt Trust' {Maybe Text
Maybe POSIX
Maybe SelectiveAuth
Maybe TrustDirection
Maybe TrustState
Maybe TrustType
trustType :: Maybe TrustType
trustStateReason :: Maybe Text
trustState :: Maybe TrustState
trustId :: Maybe Text
trustDirection :: Maybe TrustDirection
stateLastUpdatedDateTime :: Maybe POSIX
selectiveAuth :: Maybe SelectiveAuth
remoteDomainName :: Maybe Text
lastUpdatedDateTime :: Maybe POSIX
directoryId :: Maybe Text
createdDateTime :: Maybe POSIX
$sel:trustType:Trust' :: Trust -> Maybe TrustType
$sel:trustStateReason:Trust' :: Trust -> Maybe Text
$sel:trustState:Trust' :: Trust -> Maybe TrustState
$sel:trustId:Trust' :: Trust -> Maybe Text
$sel:trustDirection:Trust' :: Trust -> Maybe TrustDirection
$sel:stateLastUpdatedDateTime:Trust' :: Trust -> Maybe POSIX
$sel:selectiveAuth:Trust' :: Trust -> Maybe SelectiveAuth
$sel:remoteDomainName:Trust' :: Trust -> Maybe Text
$sel:lastUpdatedDateTime:Trust' :: Trust -> Maybe POSIX
$sel:directoryId:Trust' :: Trust -> Maybe Text
$sel:createdDateTime:Trust' :: Trust -> 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 Text
directoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
remoteDomainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SelectiveAuth
selectiveAuth
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
stateLastUpdatedDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrustDirection
trustDirection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
trustId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrustState
trustState
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
trustStateReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrustType
trustType

instance Prelude.NFData Trust where
  rnf :: Trust -> ()
rnf Trust' {Maybe Text
Maybe POSIX
Maybe SelectiveAuth
Maybe TrustDirection
Maybe TrustState
Maybe TrustType
trustType :: Maybe TrustType
trustStateReason :: Maybe Text
trustState :: Maybe TrustState
trustId :: Maybe Text
trustDirection :: Maybe TrustDirection
stateLastUpdatedDateTime :: Maybe POSIX
selectiveAuth :: Maybe SelectiveAuth
remoteDomainName :: Maybe Text
lastUpdatedDateTime :: Maybe POSIX
directoryId :: Maybe Text
createdDateTime :: Maybe POSIX
$sel:trustType:Trust' :: Trust -> Maybe TrustType
$sel:trustStateReason:Trust' :: Trust -> Maybe Text
$sel:trustState:Trust' :: Trust -> Maybe TrustState
$sel:trustId:Trust' :: Trust -> Maybe Text
$sel:trustDirection:Trust' :: Trust -> Maybe TrustDirection
$sel:stateLastUpdatedDateTime:Trust' :: Trust -> Maybe POSIX
$sel:selectiveAuth:Trust' :: Trust -> Maybe SelectiveAuth
$sel:remoteDomainName:Trust' :: Trust -> Maybe Text
$sel:lastUpdatedDateTime:Trust' :: Trust -> Maybe POSIX
$sel:directoryId:Trust' :: Trust -> Maybe Text
$sel:createdDateTime:Trust' :: Trust -> 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 Text
directoryId
      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
remoteDomainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SelectiveAuth
selectiveAuth
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
stateLastUpdatedDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrustDirection
trustDirection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
trustId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrustState
trustState
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
trustStateReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TrustType
trustType