Copyright | Copyright (c) 2009-2017 David Sorokin <david.sorokin@gmail.com> |
---|---|
License | BSD3 |
Maintainer | David Sorokin <david.sorokin@gmail.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Tested with: GHC 8.0.1
It defines the implementation details of some types. You should never use it in ordinary simulation models. The module is destined for those who will extend the library.
Synopsis
- data Specs m = Specs {}
- data Method
- data Run m = Run {
- runSpecs :: Specs m
- runIndex :: Int
- runCount :: Int
- runEventQueue :: EventQueue m
- runGenerator :: Generator m
- data Point m = Point {
- pointSpecs :: Specs m
- pointRun :: Run m
- pointTime :: Double
- pointPriority :: EventPriority
- pointIteration :: Int
- pointPhase :: Int
- newtype Parameter m a = Parameter (Run m -> m a)
- newtype Simulation m a = Simulation (Run m -> m a)
- newtype Dynamics m a = Dynamics (Point m -> m a)
- newtype Event m a = Event (Point m -> m a)
- data EventProcessing
- type EventPriority = Int
- class EventQueueing m where
- data EventQueue m :: *
- newEventQueue :: Specs m -> m (EventQueue m)
- enqueueEventWithPriority :: Double -> EventPriority -> Event m () -> Event m ()
- enqueueEvent :: Double -> Event m () -> Event m ()
- runEvent :: Event m a -> Dynamics m a
- runEventWith :: EventProcessing -> Event m a -> Dynamics m a
- eventQueueCount :: Event m Int
- invokeParameter :: Run m -> Parameter m a -> m a
- invokeSimulation :: Run m -> Simulation m a -> m a
- invokeDynamics :: Point m -> Dynamics m a -> m a
- invokeEvent :: Point m -> Event m a -> m a
Documentation
It defines the simulation specs.
Specs | |
|
It defines the integration method.
Euler | Euler's method |
RungeKutta2 | the 2nd order Runge-Kutta method |
RungeKutta4 | the 4th order Runge-Kutta method |
RungeKutta4b | the 4th order Runge-Kutta 3/8-method |
It indentifies the simulation run.
Run | |
|
It defines the simulation point appended with the additional information.
Point | |
|
newtype Parameter m a Source #
The Parameter
monad that allows specifying the model parameters.
For example, they can be used when running the Monte-Carlo simulation.
In general, this monad is very useful for representing a computation which is external relative to the model itself.
Instances
newtype Simulation m a Source #
A value in the Simulation
monad represents a computation
within the simulation run.
Simulation (Run m -> m a) |
Instances
A value in the Dynamics
monad represents a polymorphic time varying function
defined in the whole spectrum of time values as a single entity. It is ideal for
numerical approximating integrals.
Instances
A value in the Event
monad transformer represents a polymorphic time varying
function which is strongly synchronized with the event queue.
Instances
data EventProcessing Source #
Defines how the events are processed.
CurrentEvents | either process all earlier and then current events,
or raise an error if the current simulation time is less
than the actual time of the event queue (safe within
the |
EarlierEvents | either process all earlier events not affecting
the events at the current simulation time,
or raise an error if the current simulation time is less
than the actual time of the event queue (safe within
the |
CurrentEventsOrFromPast | either process all earlier and then current events, or do nothing if the current simulation time is less than the actual time of the event queue (do not use unless the documentation states the opposite) |
EarlierEventsOrFromPast | either process all earlier events, or do nothing if the current simulation time is less than the actual time of the event queue (do not use unless the documentation states the opposite) |
Instances
Show EventProcessing Source # | |
Defined in Simulation.Aivika.Trans.Internal.Types showsPrec :: Int -> EventProcessing -> ShowS # show :: EventProcessing -> String # showList :: [EventProcessing] -> ShowS # | |
Eq EventProcessing Source # | |
Defined in Simulation.Aivika.Trans.Internal.Types (==) :: EventProcessing -> EventProcessing -> Bool # (/=) :: EventProcessing -> EventProcessing -> Bool # | |
Ord EventProcessing Source # | |
Defined in Simulation.Aivika.Trans.Internal.Types compare :: EventProcessing -> EventProcessing -> Ordering # (<) :: EventProcessing -> EventProcessing -> Bool # (<=) :: EventProcessing -> EventProcessing -> Bool # (>) :: EventProcessing -> EventProcessing -> Bool # (>=) :: EventProcessing -> EventProcessing -> Bool # max :: EventProcessing -> EventProcessing -> EventProcessing # min :: EventProcessing -> EventProcessing -> EventProcessing # |
type EventPriority = Int Source #
The event priority (greater is higher).
class EventQueueing m where Source #
A type class of monads that allow enqueueing the events.
data EventQueue m :: * Source #
It represents the event queue.
newEventQueue :: Specs m -> m (EventQueue m) Source #
Create a new event queue by the specified specs with simulation session.
enqueueEventWithPriority :: Double -> EventPriority -> Event m () -> Event m () Source #
Enqueue the event which must be actuated at the specified time given the priority.
enqueueEvent :: Double -> Event m () -> Event m () Source #
Enqueue the event which must be actuated at the specified time.
runEvent :: Event m a -> Dynamics m a Source #
Run the EventT
computation in the current simulation time
within the DynamicsT
computation involving all pending
CurrentEvents
in the processing too.
runEventWith :: EventProcessing -> Event m a -> Dynamics m a Source #
Run the EventT
computation in the current simulation time
within the DynamicsT
computation specifying what pending events
should be involved in the processing.
eventQueueCount :: Event m Int Source #
Return the number of pending events that should be yet actuated.
Instances
EventQueueing IO Source # | An implementation of the |
Defined in Simulation.Aivika.IO.Event data EventQueue IO Source # newEventQueue :: Specs IO -> IO (EventQueue IO) Source # enqueueEventWithPriority :: Double -> EventPriority -> Event IO () -> Event IO () Source # enqueueEvent :: Double -> Event IO () -> Event IO () Source # runEvent :: Event IO a -> Dynamics IO a Source # runEventWith :: EventProcessing -> Event IO a -> Dynamics IO a Source # |
invokeSimulation :: Run m -> Simulation m a -> m a Source #
Invoke the Simulation
computation.