aivika-distributed-1.2: Parallel distributed discrete event simulation module for the Aivika library

CopyrightCopyright (c) 2015-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Simulation.Aivika.Distributed.Optimistic.TimeServer

Description

Tested with: GHC 7.10.3

This module allows running the time server that coordinates the global simulation time.

Synopsis

Documentation

data TimeServerParams Source #

The time server parameters.

Constructors

TimeServerParams 

Fields

Instances

Eq TimeServerParams Source # 
Ord TimeServerParams Source # 
Show TimeServerParams Source # 
Generic TimeServerParams Source # 
Binary TimeServerParams Source # 
type Rep TimeServerParams Source # 
type Rep TimeServerParams = D1 * (MetaData "TimeServerParams" "Simulation.Aivika.Distributed.Optimistic.Internal.TimeServer" "aivika-distributed-1.2-34XhNfd7ARLHUummUSadXy" False) (C1 * (MetaCons "TimeServerParams" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tsLoggingPriority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Priority)) ((:*:) * (S1 * (MetaSel (Just Symbol "tsName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "tsReceiveTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tsTimeSyncTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "tsTimeSyncDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "tsProcessMonitoringEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "tsProcessMonitoringDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "tsProcessReconnectingEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "tsProcessReconnectingDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "tsSimulationMonitoringInterval") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "tsSimulationMonitoringTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "tsStrategy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TimeServerStrategy)))))))

data TimeServerEnv Source #

Those time server environment parameters that cannot be serialized and passed to another process via the net.

Constructors

TimeServerEnv 

Fields

data TimeServerStrategy Source #

The time server strategy.

Constructors

WaitIndefinitelyForLogicalProcess

wait for the logical process forever

TerminateDueToLogicalProcessTimeout Int

terminate the server due to the exceeded logical process timeout in microseconds, but not less than tsTimeSyncTimeout, which is a much more preferable option than significantly more risky UnregisterLogicalProcessDueToTimeout

UnregisterLogicalProcessDueToTimeout Int

unregister the logical process due to the exceeded timeout in microseconds, but not less than tsTimeSyncTimeout, which is a very risky option as there can be un-acknowledged messages by the just unregistered logical process that might shutdown, which would keep the global virtual time on the same value even if the existent logical processes had another local time

Instances

Eq TimeServerStrategy Source # 
Ord TimeServerStrategy Source # 
Show TimeServerStrategy Source # 
Generic TimeServerStrategy Source # 
Binary TimeServerStrategy Source # 
type Rep TimeServerStrategy Source # 
type Rep TimeServerStrategy = D1 * (MetaData "TimeServerStrategy" "Simulation.Aivika.Distributed.Optimistic.Internal.TimeServer" "aivika-distributed-1.2-34XhNfd7ARLHUummUSadXy" False) ((:+:) * (C1 * (MetaCons "WaitIndefinitelyForLogicalProcess" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TerminateDueToLogicalProcessTimeout" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "UnregisterLogicalProcessDueToTimeout" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))

defaultTimeServerParams :: TimeServerParams Source #

The default time server parameters.

defaultTimeServerEnv :: TimeServerEnv Source #

The default time server environment parameters.

timeServer :: Int -> TimeServerParams -> Process () Source #

Start the time server by the specified initial quorum and parameters. The quorum defines the number of logical processes that must be registered in the time server before the global time synchronization is started.

timeServerWithEnv :: Int -> TimeServerParams -> TimeServerEnv -> Process () Source #

A full version of timeServer that allows specifying the environment parameters.

curryTimeServer :: (Int, TimeServerParams) -> Process () Source #

A curried version of timeServer for starting the time server on remote node.