{-# 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.Connect.Types.Rule
-- 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.Connect.Types.Rule where

import Amazonka.Connect.Types.RuleAction
import Amazonka.Connect.Types.RulePublishStatus
import Amazonka.Connect.Types.RuleTriggerEventSource
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

-- | Information about a rule.
--
-- /See:/ 'newRule' smart constructor.
data Rule = Rule'
  { -- | The tags used to organize, track, or control access for this resource.
    -- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
    Rule -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the rule.
    Rule -> Text
name :: Prelude.Text,
    -- | A unique identifier for the rule.
    Rule -> Text
ruleId :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the rule.
    Rule -> Text
ruleArn :: Prelude.Text,
    -- | The event source to trigger the rule.
    Rule -> RuleTriggerEventSource
triggerEventSource :: RuleTriggerEventSource,
    -- | The conditions of the rule.
    Rule -> Text
function :: Prelude.Text,
    -- | A list of actions to be run when the rule is triggered.
    Rule -> [RuleAction]
actions :: [RuleAction],
    -- | The publish status of the rule.
    Rule -> RulePublishStatus
publishStatus :: RulePublishStatus,
    -- | The timestamp for when the rule was created.
    Rule -> POSIX
createdTime :: Data.POSIX,
    -- | The timestamp for the when the rule was last updated.
    Rule -> POSIX
lastUpdatedTime :: Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the user who last updated the rule.
    Rule -> Text
lastUpdatedBy :: Prelude.Text
  }
  deriving (Rule -> Rule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rule -> Rule -> Bool
$c/= :: Rule -> Rule -> Bool
== :: Rule -> Rule -> Bool
$c== :: Rule -> Rule -> Bool
Prelude.Eq, ReadPrec [Rule]
ReadPrec Rule
Int -> ReadS Rule
ReadS [Rule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Rule]
$creadListPrec :: ReadPrec [Rule]
readPrec :: ReadPrec Rule
$creadPrec :: ReadPrec Rule
readList :: ReadS [Rule]
$creadList :: ReadS [Rule]
readsPrec :: Int -> ReadS Rule
$creadsPrec :: Int -> ReadS Rule
Prelude.Read, Int -> Rule -> ShowS
[Rule] -> ShowS
Rule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Rule] -> ShowS
$cshowList :: [Rule] -> ShowS
show :: Rule -> String
$cshow :: Rule -> String
showsPrec :: Int -> Rule -> ShowS
$cshowsPrec :: Int -> Rule -> ShowS
Prelude.Show, forall x. Rep Rule x -> Rule
forall x. Rule -> Rep Rule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Rule x -> Rule
$cfrom :: forall x. Rule -> Rep Rule x
Prelude.Generic)

-- |
-- Create a value of 'Rule' 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:
--
-- 'tags', 'rule_tags' - The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
--
-- 'name', 'rule_name' - The name of the rule.
--
-- 'ruleId', 'rule_ruleId' - A unique identifier for the rule.
--
-- 'ruleArn', 'rule_ruleArn' - The Amazon Resource Name (ARN) of the rule.
--
-- 'triggerEventSource', 'rule_triggerEventSource' - The event source to trigger the rule.
--
-- 'function', 'rule_function' - The conditions of the rule.
--
-- 'actions', 'rule_actions' - A list of actions to be run when the rule is triggered.
--
-- 'publishStatus', 'rule_publishStatus' - The publish status of the rule.
--
-- 'createdTime', 'rule_createdTime' - The timestamp for when the rule was created.
--
-- 'lastUpdatedTime', 'rule_lastUpdatedTime' - The timestamp for the when the rule was last updated.
--
-- 'lastUpdatedBy', 'rule_lastUpdatedBy' - The Amazon Resource Name (ARN) of the user who last updated the rule.
newRule ::
  -- | 'name'
  Prelude.Text ->
  -- | 'ruleId'
  Prelude.Text ->
  -- | 'ruleArn'
  Prelude.Text ->
  -- | 'triggerEventSource'
  RuleTriggerEventSource ->
  -- | 'function'
  Prelude.Text ->
  -- | 'publishStatus'
  RulePublishStatus ->
  -- | 'createdTime'
  Prelude.UTCTime ->
  -- | 'lastUpdatedTime'
  Prelude.UTCTime ->
  -- | 'lastUpdatedBy'
  Prelude.Text ->
  Rule
newRule :: Text
-> Text
-> Text
-> RuleTriggerEventSource
-> Text
-> RulePublishStatus
-> UTCTime
-> UTCTime
-> Text
-> Rule
newRule
  Text
pName_
  Text
pRuleId_
  Text
pRuleArn_
  RuleTriggerEventSource
pTriggerEventSource_
  Text
pFunction_
  RulePublishStatus
pPublishStatus_
  UTCTime
pCreatedTime_
  UTCTime
pLastUpdatedTime_
  Text
pLastUpdatedBy_ =
    Rule'
      { $sel:tags:Rule' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:name:Rule' :: Text
name = Text
pName_,
        $sel:ruleId:Rule' :: Text
ruleId = Text
pRuleId_,
        $sel:ruleArn:Rule' :: Text
ruleArn = Text
pRuleArn_,
        $sel:triggerEventSource:Rule' :: RuleTriggerEventSource
triggerEventSource = RuleTriggerEventSource
pTriggerEventSource_,
        $sel:function:Rule' :: Text
function = Text
pFunction_,
        $sel:actions:Rule' :: [RuleAction]
actions = forall a. Monoid a => a
Prelude.mempty,
        $sel:publishStatus:Rule' :: RulePublishStatus
publishStatus = RulePublishStatus
pPublishStatus_,
        $sel:createdTime:Rule' :: POSIX
createdTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreatedTime_,
        $sel:lastUpdatedTime:Rule' :: POSIX
lastUpdatedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastUpdatedTime_,
        $sel:lastUpdatedBy:Rule' :: Text
lastUpdatedBy = Text
pLastUpdatedBy_
      }

-- | The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
rule_tags :: Lens.Lens' Rule (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
rule_tags :: Lens' Rule (Maybe (HashMap Text Text))
rule_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:Rule' :: Rule -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: Rule
s@Rule' {} Maybe (HashMap Text Text)
a -> Rule
s {$sel:tags:Rule' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: Rule) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | A unique identifier for the rule.
rule_ruleId :: Lens.Lens' Rule Prelude.Text
rule_ruleId :: Lens' Rule Text
rule_ruleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {Text
ruleId :: Text
$sel:ruleId:Rule' :: Rule -> Text
ruleId} -> Text
ruleId) (\s :: Rule
s@Rule' {} Text
a -> Rule
s {$sel:ruleId:Rule' :: Text
ruleId = Text
a} :: Rule)

-- | The Amazon Resource Name (ARN) of the rule.
rule_ruleArn :: Lens.Lens' Rule Prelude.Text
rule_ruleArn :: Lens' Rule Text
rule_ruleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {Text
ruleArn :: Text
$sel:ruleArn:Rule' :: Rule -> Text
ruleArn} -> Text
ruleArn) (\s :: Rule
s@Rule' {} Text
a -> Rule
s {$sel:ruleArn:Rule' :: Text
ruleArn = Text
a} :: Rule)

-- | The event source to trigger the rule.
rule_triggerEventSource :: Lens.Lens' Rule RuleTriggerEventSource
rule_triggerEventSource :: Lens' Rule RuleTriggerEventSource
rule_triggerEventSource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {RuleTriggerEventSource
triggerEventSource :: RuleTriggerEventSource
$sel:triggerEventSource:Rule' :: Rule -> RuleTriggerEventSource
triggerEventSource} -> RuleTriggerEventSource
triggerEventSource) (\s :: Rule
s@Rule' {} RuleTriggerEventSource
a -> Rule
s {$sel:triggerEventSource:Rule' :: RuleTriggerEventSource
triggerEventSource = RuleTriggerEventSource
a} :: Rule)

-- | The conditions of the rule.
rule_function :: Lens.Lens' Rule Prelude.Text
rule_function :: Lens' Rule Text
rule_function = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {Text
function :: Text
$sel:function:Rule' :: Rule -> Text
function} -> Text
function) (\s :: Rule
s@Rule' {} Text
a -> Rule
s {$sel:function:Rule' :: Text
function = Text
a} :: Rule)

-- | A list of actions to be run when the rule is triggered.
rule_actions :: Lens.Lens' Rule [RuleAction]
rule_actions :: Lens' Rule [RuleAction]
rule_actions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {[RuleAction]
actions :: [RuleAction]
$sel:actions:Rule' :: Rule -> [RuleAction]
actions} -> [RuleAction]
actions) (\s :: Rule
s@Rule' {} [RuleAction]
a -> Rule
s {$sel:actions:Rule' :: [RuleAction]
actions = [RuleAction]
a} :: Rule) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The publish status of the rule.
rule_publishStatus :: Lens.Lens' Rule RulePublishStatus
rule_publishStatus :: Lens' Rule RulePublishStatus
rule_publishStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {RulePublishStatus
publishStatus :: RulePublishStatus
$sel:publishStatus:Rule' :: Rule -> RulePublishStatus
publishStatus} -> RulePublishStatus
publishStatus) (\s :: Rule
s@Rule' {} RulePublishStatus
a -> Rule
s {$sel:publishStatus:Rule' :: RulePublishStatus
publishStatus = RulePublishStatus
a} :: Rule)

-- | The timestamp for when the rule was created.
rule_createdTime :: Lens.Lens' Rule Prelude.UTCTime
rule_createdTime :: Lens' Rule UTCTime
rule_createdTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {POSIX
createdTime :: POSIX
$sel:createdTime:Rule' :: Rule -> POSIX
createdTime} -> POSIX
createdTime) (\s :: Rule
s@Rule' {} POSIX
a -> Rule
s {$sel:createdTime:Rule' :: POSIX
createdTime = POSIX
a} :: Rule) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The timestamp for the when the rule was last updated.
rule_lastUpdatedTime :: Lens.Lens' Rule Prelude.UTCTime
rule_lastUpdatedTime :: Lens' Rule UTCTime
rule_lastUpdatedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {POSIX
lastUpdatedTime :: POSIX
$sel:lastUpdatedTime:Rule' :: Rule -> POSIX
lastUpdatedTime} -> POSIX
lastUpdatedTime) (\s :: Rule
s@Rule' {} POSIX
a -> Rule
s {$sel:lastUpdatedTime:Rule' :: POSIX
lastUpdatedTime = POSIX
a} :: Rule) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The Amazon Resource Name (ARN) of the user who last updated the rule.
rule_lastUpdatedBy :: Lens.Lens' Rule Prelude.Text
rule_lastUpdatedBy :: Lens' Rule Text
rule_lastUpdatedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Rule' {Text
lastUpdatedBy :: Text
$sel:lastUpdatedBy:Rule' :: Rule -> Text
lastUpdatedBy} -> Text
lastUpdatedBy) (\s :: Rule
s@Rule' {} Text
a -> Rule
s {$sel:lastUpdatedBy:Rule' :: Text
lastUpdatedBy = Text
a} :: Rule)

instance Data.FromJSON Rule where
  parseJSON :: Value -> Parser Rule
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Rule"
      ( \Object
x ->
          Maybe (HashMap Text Text)
-> Text
-> Text
-> Text
-> RuleTriggerEventSource
-> Text
-> [RuleAction]
-> RulePublishStatus
-> POSIX
-> POSIX
-> Text
-> Rule
Rule'
            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
"Tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"Name")
            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
"RuleId")
            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
"RuleArn")
            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
"TriggerEventSource")
            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
"Function")
            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
"Actions" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"PublishStatus")
            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")
            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
"LastUpdatedTime")
            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
"LastUpdatedBy")
      )

instance Prelude.Hashable Rule where
  hashWithSalt :: Int -> Rule -> Int
hashWithSalt Int
_salt Rule' {[RuleAction]
Maybe (HashMap Text Text)
Text
POSIX
RulePublishStatus
RuleTriggerEventSource
lastUpdatedBy :: Text
lastUpdatedTime :: POSIX
createdTime :: POSIX
publishStatus :: RulePublishStatus
actions :: [RuleAction]
function :: Text
triggerEventSource :: RuleTriggerEventSource
ruleArn :: Text
ruleId :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
$sel:lastUpdatedBy:Rule' :: Rule -> Text
$sel:lastUpdatedTime:Rule' :: Rule -> POSIX
$sel:createdTime:Rule' :: Rule -> POSIX
$sel:publishStatus:Rule' :: Rule -> RulePublishStatus
$sel:actions:Rule' :: Rule -> [RuleAction]
$sel:function:Rule' :: Rule -> Text
$sel:triggerEventSource:Rule' :: Rule -> RuleTriggerEventSource
$sel:ruleArn:Rule' :: Rule -> Text
$sel:ruleId:Rule' :: Rule -> Text
$sel:name:Rule' :: Rule -> Text
$sel:tags:Rule' :: Rule -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ruleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RuleTriggerEventSource
triggerEventSource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
function
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [RuleAction]
actions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` RulePublishStatus
publishStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
createdTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
lastUpdatedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lastUpdatedBy

instance Prelude.NFData Rule where
  rnf :: Rule -> ()
rnf Rule' {[RuleAction]
Maybe (HashMap Text Text)
Text
POSIX
RulePublishStatus
RuleTriggerEventSource
lastUpdatedBy :: Text
lastUpdatedTime :: POSIX
createdTime :: POSIX
publishStatus :: RulePublishStatus
actions :: [RuleAction]
function :: Text
triggerEventSource :: RuleTriggerEventSource
ruleArn :: Text
ruleId :: Text
name :: Text
tags :: Maybe (HashMap Text Text)
$sel:lastUpdatedBy:Rule' :: Rule -> Text
$sel:lastUpdatedTime:Rule' :: Rule -> POSIX
$sel:createdTime:Rule' :: Rule -> POSIX
$sel:publishStatus:Rule' :: Rule -> RulePublishStatus
$sel:actions:Rule' :: Rule -> [RuleAction]
$sel:function:Rule' :: Rule -> Text
$sel:triggerEventSource:Rule' :: Rule -> RuleTriggerEventSource
$sel:ruleArn:Rule' :: Rule -> Text
$sel:ruleId:Rule' :: Rule -> Text
$sel:name:Rule' :: Rule -> Text
$sel:tags:Rule' :: Rule -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ruleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RuleTriggerEventSource
triggerEventSource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
function
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [RuleAction]
actions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RulePublishStatus
publishStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
createdTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastUpdatedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
lastUpdatedBy