{-# 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.SWF.Types.ActivityTypeConfiguration
-- 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.SWF.Types.ActivityTypeConfiguration 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.SWF.Types.TaskList

-- | Configuration settings registered with the activity type.
--
-- /See:/ 'newActivityTypeConfiguration' smart constructor.
data ActivityTypeConfiguration = ActivityTypeConfiguration'
  { -- | The default maximum time, in seconds, before which a worker processing a
    -- task must report progress by calling RecordActivityTaskHeartbeat.
    --
    -- You can specify this value only when /registering/ an activity type. The
    -- registered default value can be overridden when you schedule a task
    -- through the @ScheduleActivityTask@ Decision. If the activity worker
    -- subsequently attempts to record a heartbeat or returns a result, the
    -- activity worker receives an @UnknownResource@ fault. In this case,
    -- Amazon SWF no longer considers the activity task to be valid; the
    -- activity worker should clean up the activity task.
    --
    -- The duration is specified in seconds, an integer greater than or equal
    -- to @0@. You can use @NONE@ to specify unlimited duration.
    ActivityTypeConfiguration -> Maybe Text
defaultTaskHeartbeatTimeout :: Prelude.Maybe Prelude.Text,
    -- | The default task list specified for this activity type at registration.
    -- This default is used if a task list isn\'t provided when a task is
    -- scheduled through the @ScheduleActivityTask@ Decision. You can override
    -- the default registered task list when scheduling a task through the
    -- @ScheduleActivityTask@ Decision.
    ActivityTypeConfiguration -> Maybe TaskList
defaultTaskList :: Prelude.Maybe TaskList,
    -- | The default task priority for tasks of this activity type, specified at
    -- registration. If not set, then @0@ is used as the default priority. This
    -- default can be overridden when scheduling an activity task.
    --
    -- Valid values are integers that range from Java\'s @Integer.MIN_VALUE@
    -- (-2147483648) to @Integer.MAX_VALUE@ (2147483647). Higher numbers
    -- indicate higher priority.
    --
    -- For more information about setting task priority, see
    -- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/programming-priority.html Setting Task Priority>
    -- in the /Amazon SWF Developer Guide/.
    ActivityTypeConfiguration -> Maybe Text
defaultTaskPriority :: Prelude.Maybe Prelude.Text,
    -- | The default maximum duration, specified when registering the activity
    -- type, for tasks of this activity type. You can override this default
    -- when scheduling a task through the @ScheduleActivityTask@ Decision.
    --
    -- The duration is specified in seconds, an integer greater than or equal
    -- to @0@. You can use @NONE@ to specify unlimited duration.
    ActivityTypeConfiguration -> Maybe Text
defaultTaskScheduleToCloseTimeout :: Prelude.Maybe Prelude.Text,
    -- | The default maximum duration, specified when registering the activity
    -- type, that a task of an activity type can wait before being assigned to
    -- a worker. You can override this default when scheduling a task through
    -- the @ScheduleActivityTask@ Decision.
    --
    -- The duration is specified in seconds, an integer greater than or equal
    -- to @0@. You can use @NONE@ to specify unlimited duration.
    ActivityTypeConfiguration -> Maybe Text
defaultTaskScheduleToStartTimeout :: Prelude.Maybe Prelude.Text,
    -- | The default maximum duration for tasks of an activity type specified
    -- when registering the activity type. You can override this default when
    -- scheduling a task through the @ScheduleActivityTask@ Decision.
    --
    -- The duration is specified in seconds, an integer greater than or equal
    -- to @0@. You can use @NONE@ to specify unlimited duration.
    ActivityTypeConfiguration -> Maybe Text
defaultTaskStartToCloseTimeout :: Prelude.Maybe Prelude.Text
  }
  deriving (ActivityTypeConfiguration -> ActivityTypeConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActivityTypeConfiguration -> ActivityTypeConfiguration -> Bool
$c/= :: ActivityTypeConfiguration -> ActivityTypeConfiguration -> Bool
== :: ActivityTypeConfiguration -> ActivityTypeConfiguration -> Bool
$c== :: ActivityTypeConfiguration -> ActivityTypeConfiguration -> Bool
Prelude.Eq, ReadPrec [ActivityTypeConfiguration]
ReadPrec ActivityTypeConfiguration
Int -> ReadS ActivityTypeConfiguration
ReadS [ActivityTypeConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ActivityTypeConfiguration]
$creadListPrec :: ReadPrec [ActivityTypeConfiguration]
readPrec :: ReadPrec ActivityTypeConfiguration
$creadPrec :: ReadPrec ActivityTypeConfiguration
readList :: ReadS [ActivityTypeConfiguration]
$creadList :: ReadS [ActivityTypeConfiguration]
readsPrec :: Int -> ReadS ActivityTypeConfiguration
$creadsPrec :: Int -> ReadS ActivityTypeConfiguration
Prelude.Read, Int -> ActivityTypeConfiguration -> ShowS
[ActivityTypeConfiguration] -> ShowS
ActivityTypeConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActivityTypeConfiguration] -> ShowS
$cshowList :: [ActivityTypeConfiguration] -> ShowS
show :: ActivityTypeConfiguration -> String
$cshow :: ActivityTypeConfiguration -> String
showsPrec :: Int -> ActivityTypeConfiguration -> ShowS
$cshowsPrec :: Int -> ActivityTypeConfiguration -> ShowS
Prelude.Show, forall x.
Rep ActivityTypeConfiguration x -> ActivityTypeConfiguration
forall x.
ActivityTypeConfiguration -> Rep ActivityTypeConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ActivityTypeConfiguration x -> ActivityTypeConfiguration
$cfrom :: forall x.
ActivityTypeConfiguration -> Rep ActivityTypeConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'ActivityTypeConfiguration' 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:
--
-- 'defaultTaskHeartbeatTimeout', 'activityTypeConfiguration_defaultTaskHeartbeatTimeout' - The default maximum time, in seconds, before which a worker processing a
-- task must report progress by calling RecordActivityTaskHeartbeat.
--
-- You can specify this value only when /registering/ an activity type. The
-- registered default value can be overridden when you schedule a task
-- through the @ScheduleActivityTask@ Decision. If the activity worker
-- subsequently attempts to record a heartbeat or returns a result, the
-- activity worker receives an @UnknownResource@ fault. In this case,
-- Amazon SWF no longer considers the activity task to be valid; the
-- activity worker should clean up the activity task.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
--
-- 'defaultTaskList', 'activityTypeConfiguration_defaultTaskList' - The default task list specified for this activity type at registration.
-- This default is used if a task list isn\'t provided when a task is
-- scheduled through the @ScheduleActivityTask@ Decision. You can override
-- the default registered task list when scheduling a task through the
-- @ScheduleActivityTask@ Decision.
--
-- 'defaultTaskPriority', 'activityTypeConfiguration_defaultTaskPriority' - The default task priority for tasks of this activity type, specified at
-- registration. If not set, then @0@ is used as the default priority. This
-- default can be overridden when scheduling an activity task.
--
-- Valid values are integers that range from Java\'s @Integer.MIN_VALUE@
-- (-2147483648) to @Integer.MAX_VALUE@ (2147483647). Higher numbers
-- indicate higher priority.
--
-- For more information about setting task priority, see
-- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/programming-priority.html Setting Task Priority>
-- in the /Amazon SWF Developer Guide/.
--
-- 'defaultTaskScheduleToCloseTimeout', 'activityTypeConfiguration_defaultTaskScheduleToCloseTimeout' - The default maximum duration, specified when registering the activity
-- type, for tasks of this activity type. You can override this default
-- when scheduling a task through the @ScheduleActivityTask@ Decision.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
--
-- 'defaultTaskScheduleToStartTimeout', 'activityTypeConfiguration_defaultTaskScheduleToStartTimeout' - The default maximum duration, specified when registering the activity
-- type, that a task of an activity type can wait before being assigned to
-- a worker. You can override this default when scheduling a task through
-- the @ScheduleActivityTask@ Decision.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
--
-- 'defaultTaskStartToCloseTimeout', 'activityTypeConfiguration_defaultTaskStartToCloseTimeout' - The default maximum duration for tasks of an activity type specified
-- when registering the activity type. You can override this default when
-- scheduling a task through the @ScheduleActivityTask@ Decision.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
newActivityTypeConfiguration ::
  ActivityTypeConfiguration
newActivityTypeConfiguration :: ActivityTypeConfiguration
newActivityTypeConfiguration =
  ActivityTypeConfiguration'
    { $sel:defaultTaskHeartbeatTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskHeartbeatTimeout =
        forall a. Maybe a
Prelude.Nothing,
      $sel:defaultTaskList:ActivityTypeConfiguration' :: Maybe TaskList
defaultTaskList = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultTaskPriority:ActivityTypeConfiguration' :: Maybe Text
defaultTaskPriority = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultTaskScheduleToCloseTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskScheduleToCloseTimeout =
        forall a. Maybe a
Prelude.Nothing,
      $sel:defaultTaskScheduleToStartTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskScheduleToStartTimeout =
        forall a. Maybe a
Prelude.Nothing,
      $sel:defaultTaskStartToCloseTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskStartToCloseTimeout = forall a. Maybe a
Prelude.Nothing
    }

-- | The default maximum time, in seconds, before which a worker processing a
-- task must report progress by calling RecordActivityTaskHeartbeat.
--
-- You can specify this value only when /registering/ an activity type. The
-- registered default value can be overridden when you schedule a task
-- through the @ScheduleActivityTask@ Decision. If the activity worker
-- subsequently attempts to record a heartbeat or returns a result, the
-- activity worker receives an @UnknownResource@ fault. In this case,
-- Amazon SWF no longer considers the activity task to be valid; the
-- activity worker should clean up the activity task.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
activityTypeConfiguration_defaultTaskHeartbeatTimeout :: Lens.Lens' ActivityTypeConfiguration (Prelude.Maybe Prelude.Text)
activityTypeConfiguration_defaultTaskHeartbeatTimeout :: Lens' ActivityTypeConfiguration (Maybe Text)
activityTypeConfiguration_defaultTaskHeartbeatTimeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivityTypeConfiguration' {Maybe Text
defaultTaskHeartbeatTimeout :: Maybe Text
$sel:defaultTaskHeartbeatTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
defaultTaskHeartbeatTimeout} -> Maybe Text
defaultTaskHeartbeatTimeout) (\s :: ActivityTypeConfiguration
s@ActivityTypeConfiguration' {} Maybe Text
a -> ActivityTypeConfiguration
s {$sel:defaultTaskHeartbeatTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskHeartbeatTimeout = Maybe Text
a} :: ActivityTypeConfiguration)

-- | The default task list specified for this activity type at registration.
-- This default is used if a task list isn\'t provided when a task is
-- scheduled through the @ScheduleActivityTask@ Decision. You can override
-- the default registered task list when scheduling a task through the
-- @ScheduleActivityTask@ Decision.
activityTypeConfiguration_defaultTaskList :: Lens.Lens' ActivityTypeConfiguration (Prelude.Maybe TaskList)
activityTypeConfiguration_defaultTaskList :: Lens' ActivityTypeConfiguration (Maybe TaskList)
activityTypeConfiguration_defaultTaskList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivityTypeConfiguration' {Maybe TaskList
defaultTaskList :: Maybe TaskList
$sel:defaultTaskList:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe TaskList
defaultTaskList} -> Maybe TaskList
defaultTaskList) (\s :: ActivityTypeConfiguration
s@ActivityTypeConfiguration' {} Maybe TaskList
a -> ActivityTypeConfiguration
s {$sel:defaultTaskList:ActivityTypeConfiguration' :: Maybe TaskList
defaultTaskList = Maybe TaskList
a} :: ActivityTypeConfiguration)

-- | The default task priority for tasks of this activity type, specified at
-- registration. If not set, then @0@ is used as the default priority. This
-- default can be overridden when scheduling an activity task.
--
-- Valid values are integers that range from Java\'s @Integer.MIN_VALUE@
-- (-2147483648) to @Integer.MAX_VALUE@ (2147483647). Higher numbers
-- indicate higher priority.
--
-- For more information about setting task priority, see
-- <https://docs.aws.amazon.com/amazonswf/latest/developerguide/programming-priority.html Setting Task Priority>
-- in the /Amazon SWF Developer Guide/.
activityTypeConfiguration_defaultTaskPriority :: Lens.Lens' ActivityTypeConfiguration (Prelude.Maybe Prelude.Text)
activityTypeConfiguration_defaultTaskPriority :: Lens' ActivityTypeConfiguration (Maybe Text)
activityTypeConfiguration_defaultTaskPriority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivityTypeConfiguration' {Maybe Text
defaultTaskPriority :: Maybe Text
$sel:defaultTaskPriority:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
defaultTaskPriority} -> Maybe Text
defaultTaskPriority) (\s :: ActivityTypeConfiguration
s@ActivityTypeConfiguration' {} Maybe Text
a -> ActivityTypeConfiguration
s {$sel:defaultTaskPriority:ActivityTypeConfiguration' :: Maybe Text
defaultTaskPriority = Maybe Text
a} :: ActivityTypeConfiguration)

-- | The default maximum duration, specified when registering the activity
-- type, for tasks of this activity type. You can override this default
-- when scheduling a task through the @ScheduleActivityTask@ Decision.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
activityTypeConfiguration_defaultTaskScheduleToCloseTimeout :: Lens.Lens' ActivityTypeConfiguration (Prelude.Maybe Prelude.Text)
activityTypeConfiguration_defaultTaskScheduleToCloseTimeout :: Lens' ActivityTypeConfiguration (Maybe Text)
activityTypeConfiguration_defaultTaskScheduleToCloseTimeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivityTypeConfiguration' {Maybe Text
defaultTaskScheduleToCloseTimeout :: Maybe Text
$sel:defaultTaskScheduleToCloseTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
defaultTaskScheduleToCloseTimeout} -> Maybe Text
defaultTaskScheduleToCloseTimeout) (\s :: ActivityTypeConfiguration
s@ActivityTypeConfiguration' {} Maybe Text
a -> ActivityTypeConfiguration
s {$sel:defaultTaskScheduleToCloseTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskScheduleToCloseTimeout = Maybe Text
a} :: ActivityTypeConfiguration)

-- | The default maximum duration, specified when registering the activity
-- type, that a task of an activity type can wait before being assigned to
-- a worker. You can override this default when scheduling a task through
-- the @ScheduleActivityTask@ Decision.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
activityTypeConfiguration_defaultTaskScheduleToStartTimeout :: Lens.Lens' ActivityTypeConfiguration (Prelude.Maybe Prelude.Text)
activityTypeConfiguration_defaultTaskScheduleToStartTimeout :: Lens' ActivityTypeConfiguration (Maybe Text)
activityTypeConfiguration_defaultTaskScheduleToStartTimeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivityTypeConfiguration' {Maybe Text
defaultTaskScheduleToStartTimeout :: Maybe Text
$sel:defaultTaskScheduleToStartTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
defaultTaskScheduleToStartTimeout} -> Maybe Text
defaultTaskScheduleToStartTimeout) (\s :: ActivityTypeConfiguration
s@ActivityTypeConfiguration' {} Maybe Text
a -> ActivityTypeConfiguration
s {$sel:defaultTaskScheduleToStartTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskScheduleToStartTimeout = Maybe Text
a} :: ActivityTypeConfiguration)

-- | The default maximum duration for tasks of an activity type specified
-- when registering the activity type. You can override this default when
-- scheduling a task through the @ScheduleActivityTask@ Decision.
--
-- The duration is specified in seconds, an integer greater than or equal
-- to @0@. You can use @NONE@ to specify unlimited duration.
activityTypeConfiguration_defaultTaskStartToCloseTimeout :: Lens.Lens' ActivityTypeConfiguration (Prelude.Maybe Prelude.Text)
activityTypeConfiguration_defaultTaskStartToCloseTimeout :: Lens' ActivityTypeConfiguration (Maybe Text)
activityTypeConfiguration_defaultTaskStartToCloseTimeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ActivityTypeConfiguration' {Maybe Text
defaultTaskStartToCloseTimeout :: Maybe Text
$sel:defaultTaskStartToCloseTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
defaultTaskStartToCloseTimeout} -> Maybe Text
defaultTaskStartToCloseTimeout) (\s :: ActivityTypeConfiguration
s@ActivityTypeConfiguration' {} Maybe Text
a -> ActivityTypeConfiguration
s {$sel:defaultTaskStartToCloseTimeout:ActivityTypeConfiguration' :: Maybe Text
defaultTaskStartToCloseTimeout = Maybe Text
a} :: ActivityTypeConfiguration)

instance Data.FromJSON ActivityTypeConfiguration where
  parseJSON :: Value -> Parser ActivityTypeConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ActivityTypeConfiguration"
      ( \Object
x ->
          Maybe Text
-> Maybe TaskList
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> ActivityTypeConfiguration
ActivityTypeConfiguration'
            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
"defaultTaskHeartbeatTimeout")
            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
"defaultTaskList")
            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
"defaultTaskPriority")
            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
"defaultTaskScheduleToCloseTimeout")
            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
"defaultTaskScheduleToStartTimeout")
            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
"defaultTaskStartToCloseTimeout")
      )

instance Prelude.Hashable ActivityTypeConfiguration where
  hashWithSalt :: Int -> ActivityTypeConfiguration -> Int
hashWithSalt Int
_salt ActivityTypeConfiguration' {Maybe Text
Maybe TaskList
defaultTaskStartToCloseTimeout :: Maybe Text
defaultTaskScheduleToStartTimeout :: Maybe Text
defaultTaskScheduleToCloseTimeout :: Maybe Text
defaultTaskPriority :: Maybe Text
defaultTaskList :: Maybe TaskList
defaultTaskHeartbeatTimeout :: Maybe Text
$sel:defaultTaskStartToCloseTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskScheduleToStartTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskScheduleToCloseTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskPriority:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskList:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe TaskList
$sel:defaultTaskHeartbeatTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultTaskHeartbeatTimeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskList
defaultTaskList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultTaskPriority
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultTaskScheduleToCloseTimeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultTaskScheduleToStartTimeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
defaultTaskStartToCloseTimeout

instance Prelude.NFData ActivityTypeConfiguration where
  rnf :: ActivityTypeConfiguration -> ()
rnf ActivityTypeConfiguration' {Maybe Text
Maybe TaskList
defaultTaskStartToCloseTimeout :: Maybe Text
defaultTaskScheduleToStartTimeout :: Maybe Text
defaultTaskScheduleToCloseTimeout :: Maybe Text
defaultTaskPriority :: Maybe Text
defaultTaskList :: Maybe TaskList
defaultTaskHeartbeatTimeout :: Maybe Text
$sel:defaultTaskStartToCloseTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskScheduleToStartTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskScheduleToCloseTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskPriority:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
$sel:defaultTaskList:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe TaskList
$sel:defaultTaskHeartbeatTimeout:ActivityTypeConfiguration' :: ActivityTypeConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultTaskHeartbeatTimeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TaskList
defaultTaskList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultTaskPriority
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultTaskScheduleToCloseTimeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultTaskScheduleToStartTimeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
defaultTaskStartToCloseTimeout