aivika-distributed-0.5: 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.DIO

Contents

Description

Tested with: GHC 7.10.3

This module defines DIO as an instance of the MonadDES and EventIOQueueing type classes.

Synopsis

Documentation

data DIO a Source #

The distributed computation based on IO.

Instances

Monad DIO Source # 

Methods

(>>=) :: DIO a -> (a -> DIO b) -> DIO b #

(>>) :: DIO a -> DIO b -> DIO b #

return :: a -> DIO a #

fail :: String -> DIO a #

Functor DIO Source # 

Methods

fmap :: (a -> b) -> DIO a -> DIO b #

(<$) :: a -> DIO b -> DIO a #

Applicative DIO Source # 

Methods

pure :: a -> DIO a #

(<*>) :: DIO (a -> b) -> DIO a -> DIO b #

(*>) :: DIO a -> DIO b -> DIO b #

(<*) :: DIO a -> DIO b -> DIO a #

MonadException DIO Source # 

Methods

catchComp :: Exception e => DIO a -> (e -> DIO a) -> DIO a #

finallyComp :: DIO a -> DIO b -> DIO a #

throwComp :: Exception e => e -> DIO a #

data Ref DIO # 
data Ref DIO = Ref {}
data Ref DIO # 
data Ref DIO = Ref {}
data EventQueue DIO # 
data Generator DIO # 
data StrategyQueue DIO FCFS # 
data StrategyQueue DIO LCFS # 

data DIOParams Source #

The parameters for the DIO computation.

Constructors

DIOParams 

Fields

Instances

Eq DIOParams Source # 
Ord DIOParams Source # 
Show DIOParams Source # 
Generic DIOParams Source # 

Associated Types

type Rep DIOParams :: * -> * #

Binary DIOParams Source # 
type Rep DIOParams Source # 
type Rep DIOParams = D1 (MetaData "DIOParams" "Simulation.Aivika.Distributed.Optimistic.Internal.DIO" "aivika-distributed-0.5-6fHLga6dsBxI6C3Kj6ud4C" False) (C1 (MetaCons "DIOParams" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dioLoggingPriority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Priority)) ((:*:) (S1 (MetaSel (Just Symbol "dioUndoableLogSizeThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "dioOutputMessageQueueSizeThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) (S1 (MetaSel (Just Symbol "dioTransientMessageQueueSizeThreshold") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "dioSyncTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "dioAllowPrematureIO") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dioAllowSkippingOutdatedMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "dioProcessMonitoringEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "dioProcessMonitoringDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dioProcessReconnectingEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "dioProcessReconnectingDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Just Symbol "dioKeepAliveInterval") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "dioTimeServerAcknowledgmentTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))))))

runDIO :: DIO a -> DIOParams -> ProcessId -> Process (ProcessId, Process a) Source #

Run the computation using the specified parameters along with time server process identifier and return the inbox process identifier and a new simulation process.

defaultDIOParams :: DIOParams Source #

The default parameters for the DIO computation

dioParams :: DIO DIOParams Source #

Return the parameters of the current computation.

messageInboxId :: DIO ProcessId Source #

Return the process identifier of the inbox that receives messages.

timeServerId :: DIO ProcessId Source #

Return the time server process identifier.

logDIO :: Priority -> String -> DIO () Source #

Log the message with the specified priority.

terminateDIO :: DIO () Source #

Terminate the simulation including the processes in all nodes connected to the time server.

registerDIO :: DIO () Source #

Register the simulation process in the time server, which requires some initial quorum to start synchronizing the global time.

unregisterDIO :: DIO () Source #

Unregister the simulation process from the time server without affecting the processes in other nodes connected to the corresponding time server.

monitorProcessDIO :: ProcessId -> DIO () Source #

Monitor the specified process.

processMonitorSignal :: Signal DIO ProcessMonitorNotification Source #

A signal triggered when coming the process monitor notification from the Cloud Haskell back-end.

Orphan instances