aivika-realtime-0.4: Soft real-time simulation module for the Aivika library
CopyrightCopyright (c) 2016-2017 David Sorokin <david.sorokin@gmail.com>
LicenseBSD3
MaintainerDavid Sorokin <david.sorokin@gmail.com>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Simulation.Aivika.RealTime.RT

Description

Tested with: GHC 8.0.1

This module defines a soft real-time computation based on IO.

Synopsis

Soft real-time computation

data RT m a Source #

The soft real-time computation based on IO-derived computation m.

Instances

Instances details
(Functor m, Monad m, MonadIO m, MonadException m) => MonadComp (RT m) Source #

An instantiation of the MonadComp type class.

Instance details

Defined in Simulation.Aivika.RealTime.Comp

(Monad m, MonadIO m, MonadException m, MonadComp m) => MonadDES (RT m) Source #

An implementation of the MonadDES type class.

Instance details

Defined in Simulation.Aivika.RealTime.RT

MonadException m => MonadException (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Internal.RT

Methods

catchComp :: Exception e => RT m a -> (e -> RT m a) -> RT m a #

finallyComp :: RT m a -> RT m b -> RT m a #

throwComp :: Exception e => e -> RT m a #

(Functor m, Monad m, MonadIO m) => MonadGenerator (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Generator

Associated Types

data Generator (RT m) #

(Monad m, MonadIO m, MonadException m) => EventIOQueueing (RT m) Source #

An implementation of the EventIOQueueing type class.

Instance details

Defined in Simulation.Aivika.RealTime.RT

Methods

enqueueEventIO :: Double -> Event (RT m) () -> Event (RT m) () #

MonadIO m => EventQueueing (RT m) Source #

An implementation of the EventQueueing type class.

Instance details

Defined in Simulation.Aivika.RealTime.Internal.Event

Associated Types

data EventQueue (RT m) #

Methods

newEventQueue :: Specs (RT m) -> RT m (EventQueue (RT m)) #

enqueueEventWithPriority :: Double -> EventPriority -> Event (RT m) () -> Event (RT m) () #

enqueueEvent :: Double -> Event (RT m) () -> Event (RT m) () #

runEvent :: Event (RT m) a -> Dynamics (RT m) a #

runEventWith :: EventProcessing -> Event (RT m) a -> Dynamics (RT m) a #

eventQueueCount :: Event (RT m) Int #

(Monad m, MonadIO m) => MonadRef (RT m) Source #

The RT monad is an instance of MonadRef.

Instance details

Defined in Simulation.Aivika.RealTime.Ref.Base.Lazy

Associated Types

data Ref (RT m) a #

Methods

newRef :: a -> Simulation (RT m) (Ref (RT m) a) #

readRef :: Ref (RT m) a -> Event (RT m) a #

writeRef :: Ref (RT m) a -> a -> Event (RT m) () #

modifyRef :: Ref (RT m) a -> (a -> a) -> Event (RT m) () #

equalRef :: Ref (RT m) a -> Ref (RT m) a -> Bool #

MonadIO m => MonadRef0 (RT m) Source #

The RT monad is an instance of MonadRef0.

Instance details

Defined in Simulation.Aivika.RealTime.Ref.Base.Lazy

Methods

newRef0 :: a -> RT m (Ref (RT m) a) #

(Monad m, MonadIO m) => MonadRef (RT m) Source #

The RT monad is an instance of MonadRef.

Instance details

Defined in Simulation.Aivika.RealTime.Ref.Base.Strict

Associated Types

data Ref (RT m) a #

Methods

newRef :: a -> Simulation (RT m) (Ref (RT m) a) #

readRef :: Ref (RT m) a -> Event (RT m) a #

writeRef :: Ref (RT m) a -> a -> Event (RT m) () #

modifyRef :: Ref (RT m) a -> (a -> a) -> Event (RT m) () #

equalRef :: Ref (RT m) a -> Ref (RT m) a -> Bool #

MonadIO m => MonadRef0 (RT m) Source #

The RT monad is an instance of MonadRef0.

Instance details

Defined in Simulation.Aivika.RealTime.Ref.Base.Strict

Methods

newRef0 :: a -> RT m (Ref (RT m) a) #

MonadIO m => MonadIO (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Internal.RT

Methods

liftIO :: IO a -> RT m a #

Applicative m => Applicative (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Internal.RT

Methods

pure :: a -> RT m a #

(<*>) :: RT m (a -> b) -> RT m a -> RT m b #

liftA2 :: (a -> b -> c) -> RT m a -> RT m b -> RT m c #

(*>) :: RT m a -> RT m b -> RT m b #

(<*) :: RT m a -> RT m b -> RT m a #

Functor m => Functor (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Internal.RT

Methods

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

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

Monad m => Monad (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Internal.RT

Methods

(>>=) :: RT m a -> (a -> RT m b) -> RT m b #

(>>) :: RT m a -> RT m b -> RT m b #

return :: a -> RT m a #

(DequeueStrategy (RT m) FCFS, MonadComp m, MonadIO m) => DeletingQueueStrategy (RT m) FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyQueueDelete :: Eq a => StrategyQueue (RT m) FCFS a -> a -> Event (RT m) Bool #

strategyQueueDeleteBy :: StrategyQueue (RT m) FCFS a -> (a -> Bool) -> Event (RT m) (Maybe a) #

strategyQueueContains :: Eq a => StrategyQueue (RT m) FCFS a -> a -> Event (RT m) Bool #

strategyQueueContainsBy :: StrategyQueue (RT m) FCFS a -> (a -> Bool) -> Event (RT m) (Maybe a) #

(DequeueStrategy (RT m) LCFS, MonadComp m, MonadIO m) => DeletingQueueStrategy (RT m) LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyQueueDelete :: Eq a => StrategyQueue (RT m) LCFS a -> a -> Event (RT m) Bool #

strategyQueueDeleteBy :: StrategyQueue (RT m) LCFS a -> (a -> Bool) -> Event (RT m) (Maybe a) #

strategyQueueContains :: Eq a => StrategyQueue (RT m) LCFS a -> a -> Event (RT m) Bool #

strategyQueueContainsBy :: StrategyQueue (RT m) LCFS a -> (a -> Bool) -> Event (RT m) (Maybe a) #

(DequeueStrategy (RT m) SIRO, MonadComp m, MonadIO m) => DeletingQueueStrategy (RT m) SIRO Source #

An implementation of the SIRO queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyQueueDelete :: Eq a => StrategyQueue (RT m) SIRO a -> a -> Event (RT m) Bool #

strategyQueueDeleteBy :: StrategyQueue (RT m) SIRO a -> (a -> Bool) -> Event (RT m) (Maybe a) #

strategyQueueContains :: Eq a => StrategyQueue (RT m) SIRO a -> a -> Event (RT m) Bool #

strategyQueueContainsBy :: StrategyQueue (RT m) SIRO a -> (a -> Bool) -> Event (RT m) (Maybe a) #

(DequeueStrategy (RT m) StaticPriorities, MonadComp m, MonadIO m) => DeletingQueueStrategy (RT m) StaticPriorities Source #

An implementation of the StaticPriorities queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

(QueueStrategy (RT m) FCFS, MonadComp m, MonadIO m) => DequeueStrategy (RT m) FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyDequeue :: StrategyQueue (RT m) FCFS a -> Event (RT m) a #

(QueueStrategy (RT m) LCFS, MonadComp m, MonadIO m) => DequeueStrategy (RT m) LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyDequeue :: StrategyQueue (RT m) LCFS a -> Event (RT m) a #

(QueueStrategy (RT m) SIRO, MonadComp m, MonadIO m) => DequeueStrategy (RT m) SIRO Source #

An implementation of the SIRO queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyDequeue :: StrategyQueue (RT m) SIRO a -> Event (RT m) a #

(QueueStrategy (RT m) StaticPriorities, MonadComp m, MonadIO m) => DequeueStrategy (RT m) StaticPriorities Source #

An implementation of the StaticPriorities queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

(DequeueStrategy (RT m) FCFS, MonadComp m, MonadIO m) => EnqueueStrategy (RT m) FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyEnqueue :: StrategyQueue (RT m) FCFS a -> a -> Event (RT m) () #

(DequeueStrategy (RT m) LCFS, MonadComp m, MonadIO m) => EnqueueStrategy (RT m) LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyEnqueue :: StrategyQueue (RT m) LCFS a -> a -> Event (RT m) () #

(DequeueStrategy (RT m) SIRO, MonadComp m, MonadIO m) => EnqueueStrategy (RT m) SIRO Source #

A template-based implementation of the SIRO queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Methods

strategyEnqueue :: StrategyQueue (RT m) SIRO a -> a -> Event (RT m) () #

(Monad m, MonadComp m, MonadIO m) => QueueStrategy (RT m) FCFS Source #

An implementation of the FCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Associated Types

data StrategyQueue (RT m) FCFS :: Type -> Type #

(MonadComp m, MonadIO m) => QueueStrategy (RT m) LCFS Source #

An implementation of the LCFS queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Associated Types

data StrategyQueue (RT m) LCFS :: Type -> Type #

(MonadComp m, MonadIO m) => QueueStrategy (RT m) SIRO Source #

An implementation of the SIRO queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Associated Types

data StrategyQueue (RT m) SIRO :: Type -> Type #

(MonadComp m, MonadIO m) => QueueStrategy (RT m) StaticPriorities Source #

An implementation of the StaticPriorities queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

Associated Types

data StrategyQueue (RT m) StaticPriorities :: Type -> Type #

(DequeueStrategy (RT m) StaticPriorities, MonadComp m, MonadIO m) => PriorityQueueStrategy (RT m) StaticPriorities Double Source #

An implementation of the StaticPriorities queue strategy.

Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

data Generator (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Generator

data EventQueue (RT m) Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Internal.Event

newtype Ref (RT m) a Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Ref.Base.Lazy

newtype Ref (RT m) a = Ref {}
newtype Ref (RT m) a Source # 
Instance details

Defined in Simulation.Aivika.RealTime.Ref.Base.Strict

newtype Ref (RT m) a = Ref {}
newtype StrategyQueue (RT m) FCFS a Source # 
Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

newtype StrategyQueue (RT m) LCFS a Source # 
Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

newtype StrategyQueue (RT m) SIRO a Source # 
Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

newtype StrategyQueue (RT m) SIRO a = SIROQueue (Vector a)
newtype StrategyQueue (RT m) StaticPriorities a Source # 
Instance details

Defined in Simulation.Aivika.RealTime.QueueStrategy

data RTParams Source #

The parameters for the RT computation.

Constructors

RTParams 

Fields

data RTContext m Source #

The context of the RT computation.

data RTScaling Source #

How the modeling time is scaled to a real time.

Constructors

RTLinearScaling Double

one unit of modeling time interval matches the specified amount of real seconds

RTLogScaling Double

the logarithm of one unit of modeling time interval matches the specified amount of real seconds

RTScalingFunction (Double -> Double -> Double)

we explicitly define how many real seconds will we receive for the interval specified by the provided start time and current modeling time

runRT :: RT m a -> RTContext m -> m a Source #

Run the computation using the specified context.

defaultRTParams :: RTParams Source #

The default parameters for the RT computation, where one unit of modeling time matches one real second and the real time interval is specified with precision of one millisecond.

newRTContext :: RTParams -> IO (RTContext m) Source #

Create a new real-time computation context.

rtParams :: Monad m => RT m RTParams Source #

Return the parameters of the current computation.

rtScale Source #

Arguments

:: RTScaling

the scaling method

-> Double

the start modeling time

-> Double

the current modeling time

-> Double

the real time interval

Scale the modeling time to a real time.

Invoking actions within the simulation

applyEventRT :: MonadIO m => RTContext m -> Event (RT m) a -> m (Async a) Source #

Apply the Event computation within the soft real-time simulation with the specified context and return the result.

applyEventRT_ :: MonadIO m => RTContext m -> Event (RT m) () -> m () Source #

Apply the Event computation within the soft real-time simulation with the specified context.

enqueueEventRT :: MonadIO m => RTContext m -> Double -> Event (RT m) a -> m (Async a) Source #

Enqueue the Event computation within the soft real-time simulation with the specified context at the modeling time provided and then return the result.

enqueueEventRT_ :: MonadIO m => RTContext m -> Double -> Event (RT m) () -> m () Source #

Enqueue the Event computation within the soft real-time simulation with the specified context at the modeling time provided.

Orphan instances

(Monad m, MonadIO m, MonadException m, MonadComp m) => MonadDES (RT m) Source #

An implementation of the MonadDES type class.

Instance details

(Monad m, MonadIO m, MonadException m) => EventIOQueueing (RT m) Source #

An implementation of the EventIOQueueing type class.

Instance details

Methods

enqueueEventIO :: Double -> Event (RT m) () -> Event (RT m) () #