aivika-4.3.5: A multi-method simulation library

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

Simulation.Aivika.Signal

Contents

Description

Tested with: GHC 7.10.1

This module defines the signal which we can subscribe handlers to. These handlers can be disposed. The signal is triggered in the current time point actuating the corresponded computations from the handlers.

Synopsis

Handling and Triggering Signal

data Signal a Source

The signal that can have disposable handlers.

Constructors

Signal 

Fields

handleSignal :: (a -> Event ()) -> Event DisposableEvent

Subscribe the handler to the specified signal and return a nested computation within a disposable object that, being applied, unsubscribes the handler from this signal.

handleSignal_ :: Signal a -> (a -> Event ()) -> Event () Source

Subscribe the handler to the specified signal forever. To subscribe the disposable handlers, use function handleSignal.

data SignalSource a Source

The signal source that can publish its signal.

newSignalSource :: Simulation (SignalSource a) Source

Create a new signal source.

publishSignal :: SignalSource a -> Signal a Source

Publish the signal.

triggerSignal :: SignalSource a -> a -> Event () Source

Trigger the signal actuating all its handlers at the current simulation time point.

Useful Combinators

mapSignal :: (a -> b) -> Signal a -> Signal b Source

Map the signal according the specified function.

mapSignalM :: (a -> Event b) -> Signal a -> Signal b Source

Compose the signal.

apSignal :: Event (a -> b) -> Signal a -> Signal b Source

Transform the signal.

filterSignal :: (a -> Bool) -> Signal a -> Signal a Source

Filter only those signal values that satisfy the specified predicate.

filterSignal_ :: (a -> Bool) -> Signal a -> Signal () Source

Filter only those signal values that satisfy the specified predicate, but then ignoring the values.

filterSignalM :: (a -> Event Bool) -> Signal a -> Signal a Source

Filter only those signal values that satisfy the specified predicate.

filterSignalM_ :: (a -> Event Bool) -> Signal a -> Signal () Source

Filter only those signal values that satisfy the specified predicate, but then ignoring the values.

emptySignal :: Signal a Source

An empty signal which is never triggered.

merge2Signals :: Signal a -> Signal a -> Signal a Source

Merge two signals.

merge3Signals :: Signal a -> Signal a -> Signal a -> Signal a Source

Merge three signals.

merge4Signals :: Signal a -> Signal a -> Signal a -> Signal a -> Signal a Source

Merge four signals.

merge5Signals :: Signal a -> Signal a -> Signal a -> Signal a -> Signal a -> Signal a Source

Merge five signals.

Signal Arriving

arrivalSignal :: Signal a -> Signal (Arrival a) Source

Transform a signal so that the resulting signal returns a sequence of arrivals saving the information about the time points at which the original signal was received.

Creating Signal in Time Points

newSignalInTimes :: [Double] -> Event (Signal Double) Source

Return a signal that is triggered in the specified time points.

newSignalInIntegTimes :: Event (Signal Double) Source

Return a signal that is triggered in the integration time points. It should be called with help of runEventInStartTime.

newSignalInStartTime :: Event (Signal Double) Source

Return a signal that is triggered in the start time. It should be called with help of runEventInStartTime.

newSignalInStopTime :: Event (Signal Double) Source

Return a signal that is triggered in the final time.

Delaying Signal

delaySignal :: Double -> Signal a -> Signal a Source

Delay the signal values for the specified time interval.

delaySignalM :: Event Double -> Signal a -> Signal a Source

Delay the signal values for time intervals recalculated for each value.

Signal History

data SignalHistory a Source

Represents the history of the signal values.

signalHistorySignal :: SignalHistory a -> Signal a Source

The signal for which the history is created.

newSignalHistory :: Signal a -> Event (SignalHistory a) Source

Create a history of the signal values.

newSignalHistoryStartingWith :: Maybe a -> Signal a -> Event (SignalHistory a) Source

Create a history of the signal values starting with the optional initial value.

readSignalHistory :: SignalHistory a -> Event (Array Int Double, Array Int a) Source

Read the history of signal values.

Signalable Computations

data Signalable a Source

Describes a computation that also signals when changing its value.

Constructors

Signalable 

Fields

readSignalable :: Event a

Return a computation of the value.

signalableChanged_ :: Signal ()

Return a signal notifying that the value has changed but without providing the information about the changed value.

signalableChanged :: Signalable a -> Signal a Source

Return a signal notifying that the value has changed.

emptySignalable :: Monoid a => Signalable a Source

Return an identity.

appendSignalable :: Monoid a => Signalable a -> Signalable a -> Signalable a Source

An associative operation.

Debugging

traceSignal :: String -> Signal a -> Signal a Source

Show the debug message with the current simulation time.