aivika-transformers-5.7: Transformers for the Aivika simulation library

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

Simulation.Aivika.Trans.Signal

Contents

Description

Tested with: GHC 8.0.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 m a Source #

The signal that can have disposable handlers.

Constructors

Signal 

Fields

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

    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.

Instances

MonadDES m => Functor (Signal m) Source # 

Methods

fmap :: (a -> b) -> Signal m a -> Signal m b #

(<$) :: a -> Signal m b -> Signal m a #

MonadDES m => Semigroup (Signal m a) Source # 

Methods

(<>) :: Signal m a -> Signal m a -> Signal m a #

sconcat :: NonEmpty (Signal m a) -> Signal m a #

stimes :: Integral b => b -> Signal m a -> Signal m a #

MonadDES m => Monoid (Signal m a) Source # 

Methods

mempty :: Signal m a #

mappend :: Signal m a -> Signal m a -> Signal m a #

mconcat :: [Signal m a] -> Signal m a #

handleSignal_ :: MonadDES m => Signal m a -> (a -> Event m ()) -> Event m () Source #

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

handleSignalComposite :: MonadDES m => Signal m a -> (a -> Event m ()) -> Composite m () Source #

Like handleSignal but within the Composite computation.

data SignalSource m a Source #

The signal source that can publish its signal.

newSignalSource :: MonadDES m => Simulation m (SignalSource m a) Source #

Create a new signal source.

newSignalSource0 :: (MonadDES m, MonadRef0 m) => m (SignalSource m a) Source #

Create a new signal source within more low level computation than Simulation.

publishSignal :: SignalSource m a -> Signal m a Source #

Publish the signal.

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

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

Useful Combinators

mapSignal :: MonadDES m => (a -> b) -> Signal m a -> Signal m b Source #

Map the signal according the specified function.

mapSignalM :: MonadDES m => (a -> Event m b) -> Signal m a -> Signal m b Source #

Compose the signal.

apSignal :: MonadDES m => Event m (a -> b) -> Signal m a -> Signal m b Source #

Transform the signal.

filterSignal :: MonadDES m => (a -> Bool) -> Signal m a -> Signal m a Source #

Filter only those signal values that satisfy the specified predicate.

filterSignal_ :: MonadDES m => (a -> Bool) -> Signal m a -> Signal m () Source #

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

filterSignalM :: MonadDES m => (a -> Event m Bool) -> Signal m a -> Signal m a Source #

Filter only those signal values that satisfy the specified predicate.

filterSignalM_ :: MonadDES m => (a -> Event m Bool) -> Signal m a -> Signal m () Source #

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

emptySignal :: MonadDES m => Signal m a Source #

An empty signal which is never triggered.

merge2Signals :: MonadDES m => Signal m a -> Signal m a -> Signal m a Source #

Merge two signals.

merge3Signals :: MonadDES m => Signal m a -> Signal m a -> Signal m a -> Signal m a Source #

Merge three signals.

merge4Signals :: MonadDES m => Signal m a -> Signal m a -> Signal m a -> Signal m a -> Signal m a Source #

Merge four signals.

merge5Signals :: MonadDES m => Signal m a -> Signal m a -> Signal m a -> Signal m a -> Signal m a -> Signal m a Source #

Merge five signals.

Signal Arriving

arrivalSignal :: MonadDES m => Signal m a -> Signal m (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.

Delaying Signal

delaySignal :: MonadDES m => Double -> Signal m a -> Signal m a Source #

Delay the signal values for the specified time interval.

delaySignalM :: MonadDES m => Event m Double -> Signal m a -> Signal m a Source #

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

Signal History

data SignalHistory m a Source #

Represents the history of the signal values.

signalHistorySignal :: SignalHistory m a -> Signal m a Source #

The signal for which the history is created.

newSignalHistory :: MonadDES m => Signal m a -> Composite m (SignalHistory m a) Source #

Create a history of the signal values.

newSignalHistoryStartingWith :: MonadDES m => Maybe a -> Signal m a -> Composite m (SignalHistory m a) Source #

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

readSignalHistory :: MonadDES m => SignalHistory m a -> Event m (Array Int Double, Array Int a) Source #

Read the history of signal values.

Creating Signal in Time Points

newSignalInTimes :: MonadDES m => [Double] -> Event m (Signal m Double) Source #

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

newSignalInIntegTimes :: MonadDES m => Event m (Signal m Double) Source #

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

newSignalInStartTime :: MonadDES m => Event m (Signal m Double) Source #

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

newSignalInStopTime :: MonadDES m => Event m (Signal m Double) Source #

Return a signal that is triggered in the final time.

newSignalInTimeGrid :: MonadDES m => Int -> Event m (Signal m Int) Source #

Return a signal that is trigged in the grid by specified size.

Return a signal that is trigged in the grid by specified size.

Signalable Computations

data Signalable m a Source #

Describes a computation that also signals when changing its value.

Constructors

Signalable 

Fields

Instances

MonadDES m => ResultComputing Signalable m Source # 
Functor m => Functor (Signalable m) Source # 

Methods

fmap :: (a -> b) -> Signalable m a -> Signalable m b #

(<$) :: a -> Signalable m b -> Signalable m a #

(MonadDES m, Semigroup a) => Semigroup (Signalable m a) Source # 

Methods

(<>) :: Signalable m a -> Signalable m a -> Signalable m a #

sconcat :: NonEmpty (Signalable m a) -> Signalable m a #

stimes :: Integral b => b -> Signalable m a -> Signalable m a #

(MonadDES m, Monoid a, Semigroup a) => Monoid (Signalable m a) Source # 

Methods

mempty :: Signalable m a #

mappend :: Signalable m a -> Signalable m a -> Signalable m a #

mconcat :: [Signalable m a] -> Signalable m a #

(MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Signalable m (Vector e)) m Source # 
(Ix i, Show i, MonadDES m, ResultItemable (ResultValue [e])) => ResultProvider (Signalable m (Array i e)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (TimingStats a))) => ResultProvider (Signalable m (TimingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a), ResultItemable (ResultValue (SamplingStats a))) => ResultProvider (Signalable m (SamplingCounter a)) m Source # 
(MonadDES m, ResultItemable (ResultValue a)) => ResultProvider (Signalable m a) m Source # 

signalableChanged :: MonadDES m => Signalable m a -> Signal m a Source #

Return a signal notifying that the value has changed.

emptySignalable :: (MonadDES m, Monoid a) => Signalable m a Source #

Return an identity.

appendSignalable :: (MonadDES m, Semigroup a) => Signalable m a -> Signalable m a -> Signalable m a Source #

An associative operation.

Debugging

traceSignal :: MonadDES m => String -> Signal m a -> Signal m a Source #

Show the debug message with the current simulation time.