DEFINITION MODULE SimMaster;
  (*****************************************************************
    Module  SimMaster     (MW_V3.0)
      Copyright (c) 1986-2006 by Markus Ulrich, Andreas Fischlin, Dimitrios
      Gyalistras and ETH Zurich.
    Purpose   Master module controlling the 'ModelWorks' simulation
              environment.
    Remarks   This module uses the 'Dialog Machine' for conducting the
              user dialog during an interactive simulation session.
              This module is part of the mandatory client interface of
              'ModelWorks', an interactive Modula-2 modelling and
              simulation environment.
    Programming
      o Design
        Markus Ulrich             09/09/1986
        Andreas Fischlin          22/04/1989
        Dimitrios Gyalistras      02/05/1989
      o Implementation
        Markus Ulrich             09/09/1986
        Andreas Fischlin          22/04/1989
        Dimitrios Gyalistras      02/05/1989
    ETH Zurich
    Systems Ecology
    CHN E 35.1
    Universitaetstrasse 16
    8092 Zurich
    SWITZERLAND
    URLs:
        <mailto:RAMSES@env.ethz.ch>
        <http://www.sysecol.ethz.ch>
        <http://www.sysecol.ethz.ch/SimSoftware/RAMSES>
    Last revision of definition:  05/01/1994  DG
  *******************************************************************)
  (****************************************************************)
  (*  Running of the standard interactive simulation environment  *)
  (****************************************************************)
  PROCEDURE RunSimEnvironment( initSimEnv: PROC );
  (*
    Starts the standard interactive simulation environment of
    ModelWorks. This procedure is typically called within the
    body of a program module (a "model definition program", in short
    "MDP") containing or importing model definitions.  Procedure
    "initSimEnv" may be used to extend the standard simulation
    environment by e.g. installing additional menus with their
    commands or also to install a particular model.  See the
    description of the "Dialog Machine" to see how user interface
    extensions are programmed. Typically, initSimEnv will
    contain calls to procedures such as DMMenus.InstallMenu or
    DMWindows.CreateWindow.  A sample program text
    follows:
          MODULE MyModelDefProg;
            FROM DMMenus IMPORT InstallMenu,...;
            FROM DMWindows IMPORT CreateWindow,...;
            FROM SimMaster IMPORT RunSimEnvironment;
            FROM SimBase IMPORT DeclM,...;
            ...
            PROCEDURE ModelDefinitions;
            BEGIN
              DeclM(...); DeclM(...); ...
            END ModelDefinitions;
            PROCEDURE InitMySimEnvironment;
            BEGIN
              InstallMenu(...);
              CreateWindow(...);
            END InitMySimEnvironment;
          BEGIN
            ModelDefinitions;
            RunSimEnvironment( InitMySimEnvironment );
          END MyModelDefProg;
    RunSimEnvironment may be called more then once given that
    each new call occurs on a next higher subprogram level (see
    also DMMaster, DMSystem, and DMOpSys). If you wish to exit
    the simulation environment under control of another program
    (i.e. not by selecting the command "File/Quit") call StopRun
    followed by a call to the DialogMachine-procedure
    DMMaster.QuitDialogMachine. (Re)starting of the interactive
    simulation environment after exiting it on a certain sub-
    program level is possible by calling RunSimEnvironment again.
  *)
  PROCEDURE SimEnvRunning( progLevel: CARDINAL ):BOOLEAN;
  (*
    Returns true if RunSimEnvironment has been called on the
    program level progLevel. SimEnvRunning( DMSystem.CurrentDMLevel() )
    checks whether the simulation environment runs on your
    program's level.
  *)
  PROCEDURE InstallDefSimEnv( defineSimEnv: PROC );
  (*
    Install the procedure "defineSimEnv" as the client procedure
    used to (re)define the interactive simulation environment
    immediately after ModelWorks objects, such as the regular menu
    bar and IO-windows, have been activated and displayed and after
    the simulation environment initialization procedure (see
    "RunSimEnvironment" above) has been called. In particular,
    "defineSimEnv" may be reexecuted by the simulationist by choosing
    the menu command "Settings/Define simulation environment".
    Typical usage of this procedure will open an additional window
    for customized output or will read data from a file.
  *)
  PROCEDURE ExecuteDefSimEnv;
  (*
    Executes the simulation environment (re)definition procedure
    installed bu means of InstallDefSimEnv at the current program
    level.
  *)
  (***************************************************************)
  (*            States of the simulation environment             *)
  (***************************************************************)
  TYPE
    MWState =
        (noSimulation,  (* no simulation going on *)
        simulating,     (* during simulation *)
        pause,          (* current simulation temporarily halted *)
        noModel);       (* no models declared *)
    MWSubState =
        (noRun,      (* in an experiment but not in SimMaster.SimRun *)
        running,     (* in an experiment and in SimMaster.SimRun *)
        noSubState,  (* not in an experiment *)
        stopped);    (* in an experiment which has been stopped (killed) *)
  PROCEDURE GetMWState(VAR s: MWState);
  PROCEDURE GetMWSubState(VAR ss: MWSubState);
  (*
    Allows to determine the current state of ModelWorks during a
    simulation session.
  *)
  PROCEDURE InstallStateChangeSignaling( doAtStateChange: PROC );
  (*
    Installs the client's procedure "doAtStateChange" in ModelWorks
    which will be called each time a change in the state of
    ModelWorks during a simulation session occurs. The current
    state my be obtained by calling GetMWState and GetMWSubState
    (see above).
  *)
  (***************************************************************)
  (*                   Simulation run conditions                 *)
  (***************************************************************)
  TYPE
    StartConsistencyProcedure = PROCEDURE(): BOOLEAN;
    TerminateConditionProcedure = PROCEDURE(): BOOLEAN;
  PROCEDURE InstallStartConsistency( startAllowed: StartConsistencyProcedure );
  (*
    Procedure "startAllowed" is called at the begin of a simulation
    run, right after the execution of the "Initial"-procedures of
    all models (see procedure SimBase.DeclM) or before resuming a
    simulation run after a pause. If it returns FALSE, the
    simulation will be aborted and the simulation environment
    returns to the program state "noSimulation" if no experiment is
    currently running or to the state "simulating/noRun", if an
    experiment is currently executed. If startAllowed returns TRUE
    the simulation is normally continued. Typically this procedure
    is used to check consistency in the initial conditions, e.g. to
    test relations among parameters and initial values.  Since the
    simulationist may interactively change values of parameters
    independently from each other (entry forms test only range
    errors), this consistency test is important in case the model
    equations would be undefined if the conditions were not met.
  *)
  PROCEDURE InstallTerminateCondition( isAtEnd: TerminateConditionProcedure );
  (*
    Procedure "isAtEnd" is called at the end of each time
    (integration) step during simulation.  If it returns TRUE, the
    simulation will be terminated. i.e one of the states
    "noSimulation" or "simulating/noRun" is assumed, the latter
    being the case if an experiment is currently executed. Note
    however, that this mechanism does not correspond to a real
    state event handling, as no iterations to find exact values and
    location on time axis are executed.
  *)
  (***************************************************************)
  (*     Control of elementary and structured simulation runs    *)
  (***************************************************************)
  PROCEDURE SimRun;
  (*
    Perform a single simulation run with the current parameter and
    other variable settings.  Typically this routine is used to do
    several simulation runs, e.g. the construction of a whole phase
    portrait by means of a single menu command or to indentify a
    model parameter.
  *)
  PROCEDURE PauseRun;
  (*
    Sets the flag for the state transition from the program state
    "simulating" into the program state "pause" and will only
    return after the simulationist has chosen the menu command
    "Resume run" under menu "Solve" or until the procedure ResumeRun
    is called, e.g. by means of an additionally installed menu.
  *)
  PROCEDURE ResumeRun;
  (*
    Sets the flag for the state transition from the program state
    "pause" into the program state "simulating".
  *)
  PROCEDURE StopRun;
  (*
    Sets the flag for the state transition from one of the program states
    "simulating" or "pause" into one of the program states "noSimulation"
    or "noModel" (the second state is assumed if no models are present
    after termination of the run).
  *)
  PROCEDURE InstallExperiment( doExperiment: PROC );
  (*
    Install an experiment which may be executed by the user by
    selecting the menu command "Start Experiment" under menu
    "Solve" which corresponds to the call of procedure SimExperiment.
    The procedure "doExperiment" is provided by the modeller and
    contains typically calls to the procedure SimRun (see above).
  *)
  PROCEDURE SimExperiment;
  (*
    Performs the experiment declared for the current program level
    by means of procedure InstallExperiment.
  *)
  PROCEDURE StopExperiment;
  (*
    If an experiment is currently running, this procedure sets the
    flag for the state transition from the program state/substate
    "simulating/running" or "pause/running" into the program state
    "simulating/stopped". In this new state any further calls to
    SimRun are discarded until your experiment-procedure is
    actually finished. Than one of the states "noSimulation" or
    "noModel" is assumed, according to whether any models are
    present after termination of the experiment or not.
    To stop only an individual simulation run, but not the entire
    experiment, use StopRun or InstallTerminateCondition (see above).
  *)
  PROCEDURE ExperimentRunning(): BOOLEAN;
  (*
    ExperimentRunning returns true if a structured simulation run
    is currently in execution, i.e. if the simulationist has
    reached the state simulating by selecting the menu command
    "Start experiment" from menu "Solve" or if the procedure
    SimExperiment has been called. It corresponds to the
    boolean expression "MWSubState<>noSubState".
  *)
  PROCEDURE ExperimentAborted(): BOOLEAN;
  (*
    ExperimentAborted returns true if a running structured
    simulation (experiment) has been stopped (killed)  by the
    simulationist or due to a call to StopExperiment.  It
    corresponds to the boolean expression "MWSubState=stopped".
  *)
  PROCEDURE CurrentSimNr(): INTEGER;
  (*
    Returns the current simulation run number k. This procedure is
    typically called in the client procedure Initial, e.g. to
    assign parameter values depending on the current run k in a
    structured simulation (k = 1, 2, 3, ...).
  *)
  PROCEDURE CurrentTime(): REAL;
  (*
    Returns the current simulation time.
  *)
  PROCEDURE CurrentStep(): INTEGER;
  (*
    Returns the index associated to the current discrete time, i.e.
    the number of coincidence timepoints that have occurred till
    now since begin of the simulation (if the current timepoint is
    a coincidence timepoint, it has already occurred).
  *)
  PROCEDURE LastCoincidenceTime():REAL;
  (*
    Returns the last coincidence time, i.e. the last timepoint at
    which the state of any possibly declared discrete models would
    have been updated.
  *)
END SimMaster.