{-# 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.Rum.Types.AppMonitor
-- 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.Rum.Types.AppMonitor 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.Rum.Types.AppMonitorConfiguration
import Amazonka.Rum.Types.CustomEvents
import Amazonka.Rum.Types.DataStorage
import Amazonka.Rum.Types.StateEnum

-- | A RUM app monitor collects telemetry data from your application and
-- sends that data to RUM. The data includes performance and reliability
-- information such as page load time, client-side errors, and user
-- behavior.
--
-- /See:/ 'newAppMonitor' smart constructor.
data AppMonitor = AppMonitor'
  { -- | A structure that contains much of the configuration data for the app
    -- monitor.
    AppMonitor -> Maybe AppMonitorConfiguration
appMonitorConfiguration :: Prelude.Maybe AppMonitorConfiguration,
    -- | The date and time that this app monitor was created.
    AppMonitor -> Maybe Text
created :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether this app monitor allows the web client to define and
    -- send custom events.
    --
    -- For more information about custom events, see
    -- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch-RUM-custom-events.html Send custom events>.
    AppMonitor -> Maybe CustomEvents
customEvents :: Prelude.Maybe CustomEvents,
    -- | A structure that contains information about whether this app monitor
    -- stores a copy of the telemetry data that RUM collects using CloudWatch
    -- Logs.
    AppMonitor -> Maybe DataStorage
dataStorage :: Prelude.Maybe DataStorage,
    -- | The top-level internet domain name for which your application has
    -- administrative authority.
    AppMonitor -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | The unique ID of this app monitor.
    AppMonitor -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The date and time of the most recent changes to this app monitor\'s
    -- configuration.
    AppMonitor -> Maybe Text
lastModified :: Prelude.Maybe Prelude.Text,
    -- | The name of the app monitor.
    AppMonitor -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The current state of the app monitor.
    AppMonitor -> Maybe StateEnum
state :: Prelude.Maybe StateEnum,
    -- | The list of tag keys and values associated with this app monitor.
    AppMonitor -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)
  }
  deriving (AppMonitor -> AppMonitor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppMonitor -> AppMonitor -> Bool
$c/= :: AppMonitor -> AppMonitor -> Bool
== :: AppMonitor -> AppMonitor -> Bool
$c== :: AppMonitor -> AppMonitor -> Bool
Prelude.Eq, ReadPrec [AppMonitor]
ReadPrec AppMonitor
Int -> ReadS AppMonitor
ReadS [AppMonitor]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AppMonitor]
$creadListPrec :: ReadPrec [AppMonitor]
readPrec :: ReadPrec AppMonitor
$creadPrec :: ReadPrec AppMonitor
readList :: ReadS [AppMonitor]
$creadList :: ReadS [AppMonitor]
readsPrec :: Int -> ReadS AppMonitor
$creadsPrec :: Int -> ReadS AppMonitor
Prelude.Read, Int -> AppMonitor -> ShowS
[AppMonitor] -> ShowS
AppMonitor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AppMonitor] -> ShowS
$cshowList :: [AppMonitor] -> ShowS
show :: AppMonitor -> String
$cshow :: AppMonitor -> String
showsPrec :: Int -> AppMonitor -> ShowS
$cshowsPrec :: Int -> AppMonitor -> ShowS
Prelude.Show, forall x. Rep AppMonitor x -> AppMonitor
forall x. AppMonitor -> Rep AppMonitor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AppMonitor x -> AppMonitor
$cfrom :: forall x. AppMonitor -> Rep AppMonitor x
Prelude.Generic)

-- |
-- Create a value of 'AppMonitor' 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:
--
-- 'appMonitorConfiguration', 'appMonitor_appMonitorConfiguration' - A structure that contains much of the configuration data for the app
-- monitor.
--
-- 'created', 'appMonitor_created' - The date and time that this app monitor was created.
--
-- 'customEvents', 'appMonitor_customEvents' - Specifies whether this app monitor allows the web client to define and
-- send custom events.
--
-- For more information about custom events, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch-RUM-custom-events.html Send custom events>.
--
-- 'dataStorage', 'appMonitor_dataStorage' - A structure that contains information about whether this app monitor
-- stores a copy of the telemetry data that RUM collects using CloudWatch
-- Logs.
--
-- 'domain', 'appMonitor_domain' - The top-level internet domain name for which your application has
-- administrative authority.
--
-- 'id', 'appMonitor_id' - The unique ID of this app monitor.
--
-- 'lastModified', 'appMonitor_lastModified' - The date and time of the most recent changes to this app monitor\'s
-- configuration.
--
-- 'name', 'appMonitor_name' - The name of the app monitor.
--
-- 'state', 'appMonitor_state' - The current state of the app monitor.
--
-- 'tags', 'appMonitor_tags' - The list of tag keys and values associated with this app monitor.
newAppMonitor ::
  AppMonitor
newAppMonitor :: AppMonitor
newAppMonitor =
  AppMonitor'
    { $sel:appMonitorConfiguration:AppMonitor' :: Maybe AppMonitorConfiguration
appMonitorConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:created:AppMonitor' :: Maybe Text
created = forall a. Maybe a
Prelude.Nothing,
      $sel:customEvents:AppMonitor' :: Maybe CustomEvents
customEvents = forall a. Maybe a
Prelude.Nothing,
      $sel:dataStorage:AppMonitor' :: Maybe DataStorage
dataStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:domain:AppMonitor' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
      $sel:id:AppMonitor' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModified:AppMonitor' :: Maybe Text
lastModified = forall a. Maybe a
Prelude.Nothing,
      $sel:name:AppMonitor' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:state:AppMonitor' :: Maybe StateEnum
state = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:AppMonitor' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | A structure that contains much of the configuration data for the app
-- monitor.
appMonitor_appMonitorConfiguration :: Lens.Lens' AppMonitor (Prelude.Maybe AppMonitorConfiguration)
appMonitor_appMonitorConfiguration :: Lens' AppMonitor (Maybe AppMonitorConfiguration)
appMonitor_appMonitorConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe AppMonitorConfiguration
appMonitorConfiguration :: Maybe AppMonitorConfiguration
$sel:appMonitorConfiguration:AppMonitor' :: AppMonitor -> Maybe AppMonitorConfiguration
appMonitorConfiguration} -> Maybe AppMonitorConfiguration
appMonitorConfiguration) (\s :: AppMonitor
s@AppMonitor' {} Maybe AppMonitorConfiguration
a -> AppMonitor
s {$sel:appMonitorConfiguration:AppMonitor' :: Maybe AppMonitorConfiguration
appMonitorConfiguration = Maybe AppMonitorConfiguration
a} :: AppMonitor)

-- | The date and time that this app monitor was created.
appMonitor_created :: Lens.Lens' AppMonitor (Prelude.Maybe Prelude.Text)
appMonitor_created :: Lens' AppMonitor (Maybe Text)
appMonitor_created = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe Text
created :: Maybe Text
$sel:created:AppMonitor' :: AppMonitor -> Maybe Text
created} -> Maybe Text
created) (\s :: AppMonitor
s@AppMonitor' {} Maybe Text
a -> AppMonitor
s {$sel:created:AppMonitor' :: Maybe Text
created = Maybe Text
a} :: AppMonitor)

-- | Specifies whether this app monitor allows the web client to define and
-- send custom events.
--
-- For more information about custom events, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch-RUM-custom-events.html Send custom events>.
appMonitor_customEvents :: Lens.Lens' AppMonitor (Prelude.Maybe CustomEvents)
appMonitor_customEvents :: Lens' AppMonitor (Maybe CustomEvents)
appMonitor_customEvents = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe CustomEvents
customEvents :: Maybe CustomEvents
$sel:customEvents:AppMonitor' :: AppMonitor -> Maybe CustomEvents
customEvents} -> Maybe CustomEvents
customEvents) (\s :: AppMonitor
s@AppMonitor' {} Maybe CustomEvents
a -> AppMonitor
s {$sel:customEvents:AppMonitor' :: Maybe CustomEvents
customEvents = Maybe CustomEvents
a} :: AppMonitor)

-- | A structure that contains information about whether this app monitor
-- stores a copy of the telemetry data that RUM collects using CloudWatch
-- Logs.
appMonitor_dataStorage :: Lens.Lens' AppMonitor (Prelude.Maybe DataStorage)
appMonitor_dataStorage :: Lens' AppMonitor (Maybe DataStorage)
appMonitor_dataStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe DataStorage
dataStorage :: Maybe DataStorage
$sel:dataStorage:AppMonitor' :: AppMonitor -> Maybe DataStorage
dataStorage} -> Maybe DataStorage
dataStorage) (\s :: AppMonitor
s@AppMonitor' {} Maybe DataStorage
a -> AppMonitor
s {$sel:dataStorage:AppMonitor' :: Maybe DataStorage
dataStorage = Maybe DataStorage
a} :: AppMonitor)

-- | The top-level internet domain name for which your application has
-- administrative authority.
appMonitor_domain :: Lens.Lens' AppMonitor (Prelude.Maybe Prelude.Text)
appMonitor_domain :: Lens' AppMonitor (Maybe Text)
appMonitor_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe Text
domain :: Maybe Text
$sel:domain:AppMonitor' :: AppMonitor -> Maybe Text
domain} -> Maybe Text
domain) (\s :: AppMonitor
s@AppMonitor' {} Maybe Text
a -> AppMonitor
s {$sel:domain:AppMonitor' :: Maybe Text
domain = Maybe Text
a} :: AppMonitor)

-- | The unique ID of this app monitor.
appMonitor_id :: Lens.Lens' AppMonitor (Prelude.Maybe Prelude.Text)
appMonitor_id :: Lens' AppMonitor (Maybe Text)
appMonitor_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe Text
id :: Maybe Text
$sel:id:AppMonitor' :: AppMonitor -> Maybe Text
id} -> Maybe Text
id) (\s :: AppMonitor
s@AppMonitor' {} Maybe Text
a -> AppMonitor
s {$sel:id:AppMonitor' :: Maybe Text
id = Maybe Text
a} :: AppMonitor)

-- | The date and time of the most recent changes to this app monitor\'s
-- configuration.
appMonitor_lastModified :: Lens.Lens' AppMonitor (Prelude.Maybe Prelude.Text)
appMonitor_lastModified :: Lens' AppMonitor (Maybe Text)
appMonitor_lastModified = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe Text
lastModified :: Maybe Text
$sel:lastModified:AppMonitor' :: AppMonitor -> Maybe Text
lastModified} -> Maybe Text
lastModified) (\s :: AppMonitor
s@AppMonitor' {} Maybe Text
a -> AppMonitor
s {$sel:lastModified:AppMonitor' :: Maybe Text
lastModified = Maybe Text
a} :: AppMonitor)

-- | The name of the app monitor.
appMonitor_name :: Lens.Lens' AppMonitor (Prelude.Maybe Prelude.Text)
appMonitor_name :: Lens' AppMonitor (Maybe Text)
appMonitor_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe Text
name :: Maybe Text
$sel:name:AppMonitor' :: AppMonitor -> Maybe Text
name} -> Maybe Text
name) (\s :: AppMonitor
s@AppMonitor' {} Maybe Text
a -> AppMonitor
s {$sel:name:AppMonitor' :: Maybe Text
name = Maybe Text
a} :: AppMonitor)

-- | The current state of the app monitor.
appMonitor_state :: Lens.Lens' AppMonitor (Prelude.Maybe StateEnum)
appMonitor_state :: Lens' AppMonitor (Maybe StateEnum)
appMonitor_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe StateEnum
state :: Maybe StateEnum
$sel:state:AppMonitor' :: AppMonitor -> Maybe StateEnum
state} -> Maybe StateEnum
state) (\s :: AppMonitor
s@AppMonitor' {} Maybe StateEnum
a -> AppMonitor
s {$sel:state:AppMonitor' :: Maybe StateEnum
state = Maybe StateEnum
a} :: AppMonitor)

-- | The list of tag keys and values associated with this app monitor.
appMonitor_tags :: Lens.Lens' AppMonitor (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
appMonitor_tags :: Lens' AppMonitor (Maybe (HashMap Text Text))
appMonitor_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AppMonitor' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:AppMonitor' :: AppMonitor -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: AppMonitor
s@AppMonitor' {} Maybe (HashMap Text Text)
a -> AppMonitor
s {$sel:tags:AppMonitor' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: AppMonitor) 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

instance Data.FromJSON AppMonitor where
  parseJSON :: Value -> Parser AppMonitor
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AppMonitor"
      ( \Object
x ->
          Maybe AppMonitorConfiguration
-> Maybe Text
-> Maybe CustomEvents
-> Maybe DataStorage
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe StateEnum
-> Maybe (HashMap Text Text)
-> AppMonitor
AppMonitor'
            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
"AppMonitorConfiguration")
            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
"Created")
            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
"CustomEvents")
            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
"DataStorage")
            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
"Domain")
            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
"Id")
            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
"LastModified")
            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
"State")
            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
"Tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable AppMonitor where
  hashWithSalt :: Int -> AppMonitor -> Int
hashWithSalt Int
_salt AppMonitor' {Maybe Text
Maybe (HashMap Text Text)
Maybe CustomEvents
Maybe DataStorage
Maybe StateEnum
Maybe AppMonitorConfiguration
tags :: Maybe (HashMap Text Text)
state :: Maybe StateEnum
name :: Maybe Text
lastModified :: Maybe Text
id :: Maybe Text
domain :: Maybe Text
dataStorage :: Maybe DataStorage
customEvents :: Maybe CustomEvents
created :: Maybe Text
appMonitorConfiguration :: Maybe AppMonitorConfiguration
$sel:tags:AppMonitor' :: AppMonitor -> Maybe (HashMap Text Text)
$sel:state:AppMonitor' :: AppMonitor -> Maybe StateEnum
$sel:name:AppMonitor' :: AppMonitor -> Maybe Text
$sel:lastModified:AppMonitor' :: AppMonitor -> Maybe Text
$sel:id:AppMonitor' :: AppMonitor -> Maybe Text
$sel:domain:AppMonitor' :: AppMonitor -> Maybe Text
$sel:dataStorage:AppMonitor' :: AppMonitor -> Maybe DataStorage
$sel:customEvents:AppMonitor' :: AppMonitor -> Maybe CustomEvents
$sel:created:AppMonitor' :: AppMonitor -> Maybe Text
$sel:appMonitorConfiguration:AppMonitor' :: AppMonitor -> Maybe AppMonitorConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AppMonitorConfiguration
appMonitorConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
created
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomEvents
customEvents
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataStorage
dataStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastModified
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateEnum
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags

instance Prelude.NFData AppMonitor where
  rnf :: AppMonitor -> ()
rnf AppMonitor' {Maybe Text
Maybe (HashMap Text Text)
Maybe CustomEvents
Maybe DataStorage
Maybe StateEnum
Maybe AppMonitorConfiguration
tags :: Maybe (HashMap Text Text)
state :: Maybe StateEnum
name :: Maybe Text
lastModified :: Maybe Text
id :: Maybe Text
domain :: Maybe Text
dataStorage :: Maybe DataStorage
customEvents :: Maybe CustomEvents
created :: Maybe Text
appMonitorConfiguration :: Maybe AppMonitorConfiguration
$sel:tags:AppMonitor' :: AppMonitor -> Maybe (HashMap Text Text)
$sel:state:AppMonitor' :: AppMonitor -> Maybe StateEnum
$sel:name:AppMonitor' :: AppMonitor -> Maybe Text
$sel:lastModified:AppMonitor' :: AppMonitor -> Maybe Text
$sel:id:AppMonitor' :: AppMonitor -> Maybe Text
$sel:domain:AppMonitor' :: AppMonitor -> Maybe Text
$sel:dataStorage:AppMonitor' :: AppMonitor -> Maybe DataStorage
$sel:customEvents:AppMonitor' :: AppMonitor -> Maybe CustomEvents
$sel:created:AppMonitor' :: AppMonitor -> Maybe Text
$sel:appMonitorConfiguration:AppMonitor' :: AppMonitor -> Maybe AppMonitorConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AppMonitorConfiguration
appMonitorConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
created
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomEvents
customEvents
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataStorage
dataStorage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
lastModified
      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 StateEnum
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags