ETHZ_Logo RAMSES_Logo_Right   RAMSES   RAMSES_Logo_Left Systems Ecology  
Start    search button      Modules:   A-Z   Function   Layer        QuickRefs:   DM   AuxLib   AuxLibE   SciLib   EasyMW   MW   ISIS   RMSLib

ModelWorks Quick Reference
MW_Logo
SimBase   SimDeltaCalc   SimEvents   SimGraphUtils   SimIntegrate   SimMaster   SimObjects  
                                         ModelWorks
                                Version 3.0.7 (October 2004)

       Copyright (c) 1986-2006 by Andreas Fischlin, Olivier Roth, Markus Ulrich,
       Dimitrios Gyalistras and ETH Zurich.

       mailto://RAMSES@env.ethz.ch                      http://www.sysecol.ethz.ch/

       (***************************************************************************)
       (*#####        C L I E N T   I N T E R F A C E   M O D U L E S        #####*)
       (***************************************************************************)

       The authors reserve the right to make changes, additions, and improvements
       to the software or documentation at any time without notice to any person or
       organization; no guarantee is made that further versions of either will be
       compatible with any  other version.

       The authors hereby disclaim any and all guarantees and warranties on the
       software or its documentation, both expressed or implied.  No liability
       of any form shall be assumed by the authors.  Any user of this sofware uses
       it at his or her own risk and no fitness for any purpose whatsoever nor
       waranty of merchantability are claimed or implied.

       | Marks lines which contain objects which have been added since Version 1.0.


(*==================================     SimBase     ==================================*)

  (* Declaration of models and model objects: *)
  TYPE
    Model;
|   StateVar    = REAL;         Derivative = REAL;         NewState = REAL;
|   AuxVar      = REAL;         Parameter  = REAL;
|   InVar       = REAL;         OutVar     = REAL;

    IntegrationMethod = (Euler, Heun, RungeKutta4, RungeKutta45Var, stiff, discreteTime, discreteEvent);
    RTCType = (rtc, noRtc);
    StashFiling = (writeOnFile, notOnFile);
    Tabulation = (writeInTable, notInTable);
    Graphing = (isX, isY, isZ, notInGraph);

| VAR notDeclaredModel: Model; (* read only variable *)

  PROCEDURE DeclM(VAR m: Model; defaultMethod: IntegrationMethod; initialize, input, output, dynamic, terminate: PROC;
                  declModelObjects: PROC; descriptor, identifier: ARRAY OF CHAR; about: PROC);
  PROCEDURE DeclSV(VAR s: StateVar; VAR ds: Derivative (*or NewState*); defaultInitial, minCurInit, maxCurInit: REAL;
                   descriptor, identifier, unit: ARRAY OF CHAR);
  PROCEDURE DeclP(VAR p: Parameter; defaultVal, minCurVal, maxCurVal: REAL; runTimeChange: RTCType;
                  descriptor, identifier, unit: ARRAY OF CHAR);
  PROCEDURE DeclMV(VAR mv: REAL; defaultScaleMin, defaultScaleMax: REAL; descriptor, identifier, unit: ARRAY OF CHAR;
                   defaultSF: StashFiling; defaultT: Tabulation; defaultG: Graphing);

| PROCEDURE CurCalcM(): Model;
| PROCEDURE CurAboutM(): Model;
  PROCEDURE SelectM (m: Model; VAR done: BOOLEAN);

  PROCEDURE NoInitialize; PROCEDURE NoInput; PROCEDURE NoOutput; PROCEDURE NoDynamic; PROCEDURE NoTerminate;
  PROCEDURE NoModelObjects; PROCEDURE NoAbout; PROCEDURE DoNothing;

  (* Modifying of models and model objects: *)
  PROCEDURE GetDefltM (VAR m: Model; VAR defaultMethod: IntegrationMethod;
                       VAR initialize, input, output, dynamic, terminate: PROC;
                       VAR descriptor, identifier: ARRAY OF CHAR; VAR about: PROC);
  PROCEDURE SetDefltM (VAR m: Model; defaultMethod: IntegrationMethod;
                           initialize, input, output, dynamic, terminate: PROC;
                           descriptor, identifier: ARRAY OF CHAR; about: PROC);
  PROCEDURE GetDefltSV    (m: Model; VAR s: StateVar; VAR defaultInit, minCurInit, maxCurInit: REAL;
                           VAR descriptor, identifier, unit: ARRAY OF CHAR);
  PROCEDURE SetDefltSV    (m: Model; VAR s: StateVar; defaultInit, minCurInit, maxCurInit: REAL;
                              descriptor, identifier, unit: ARRAY OF CHAR);
  PROCEDURE GetDefltP     (m: Model; VAR p: Parameter; VAR defaultVal, minVal, maxVal: REAL;
                           VAR runTimeChange: RTCType;
                           VAR descriptor, identifier, unit: ARRAY OF CHAR);
  PROCEDURE SetDefltP     (m: Model; VAR p: Parameter; defaultVal, minVal, maxVal: REAL;
                               runTimeChange: RTCType;
                               descriptor, identifier, unit: ARRAY OF CHAR);
  PROCEDURE GetDefltMV    (m: Model; VAR mv: REAL; VAR defaultScaleMin, defaultScaleMax: REAL;
                           VAR descriptor, identifier, unit: ARRAY OF CHAR;
                           VAR defaultSF: StashFiling; VAR defaultT: Tabulation;
                           VAR defaultG: Graphing);
  PROCEDURE SetDefltMV    (m: Model; VAR mv: REAL; defaultScaleMin, defaultScaleMax: REAL;
                               descriptor, identifier, unit: ARRAY OF CHAR;
                               defaultSF: StashFiling; defaultT: Tabulation;
                               defaultG: Graphing);

  PROCEDURE GetM (VAR m: Model;               VAR curMethod: IntegrationMethod);
  PROCEDURE SetM (VAR m: Model;                   curMethod: IntegrationMethod);
  PROCEDURE GetSV    (m: Model; VAR s:  StateVar; VAR curInit: REAL);
  PROCEDURE SetSV    (m: Model; VAR s:  StateVar;     curInit: REAL);
  PROCEDURE GetP     (m: Model; VAR p:  Parameter; VAR curVal: REAL);
  PROCEDURE SetP     (m: Model; VAR p:  Parameter;     curVal: REAL);
  PROCEDURE GetMV    (m: Model; VAR mv: REAL; VAR curScaleMin, curScaleMax: REAL;
                      VAR curSF: StashFiling; VAR curT: Tabulation; VAR curG: Graphing);
  PROCEDURE SetMV    (m: Model; VAR mv: REAL;     curScaleMin, curScaleMax: REAL;
                          curSF: StashFiling;     curT: Tabulation;     curG: Graphing);

| PROCEDURE ResetAllIntegrationMethods;
| PROCEDURE ResetAllInitialValues;
| PROCEDURE ResetAllParameters;
| PROCEDURE ResetAllStashFiling;
| PROCEDURE ResetAllTabulation;
| PROCEDURE ResetAllGraphing;
| PROCEDURE ResetAllScaling;

  (* Model attributes: *)
| TYPE Attribute = INTEGER;    CONST noAttr = MIN(Attribute);
| PROCEDURE SetModelAttr(m: Model; val: Attribute);
| PROCEDURE GetModelAttr(m: Model): Attribute;
| PROCEDURE SetObjAttr(m: Model; VAR o: REAL; val: Attribute);
| PROCEDURE GetObjAttr(m: Model; VAR o: REAL):     Attribute;

  (* Access helps for all models and all model objects:  *)
| PROCEDURE MDeclared(m: Model): BOOLEAN;
| PROCEDURE SVDeclared(m: Model; VAR sv: StateVar): BOOLEAN;
| PROCEDURE PDeclared(m: Model; VAR p: Parameter): BOOLEAN;
| PROCEDURE MVDeclared(m: Model; VAR mv: REAL): BOOLEAN;

| TYPE ModelProc = PROCEDURE( VAR Model, VAR Attribute );     ModelObjectProc = PROCEDURE( Model, VAR REAL, VAR Attribute );

| PROCEDURE DoForAllModels( p: ModelProc );
| PROCEDURE DoForAllSVs   ( m: Model; p: ModelObjectProc );
| PROCEDURE DoForAllPs    ( m: Model; p: ModelObjectProc );
| PROCEDURE DoForAllMVs   ( m: Model; p: ModelObjectProc );


  (* Removing of models and model objects: *)
  PROCEDURE RemoveM     (VAR m: Model);
  PROCEDURE RemoveSV    (m: Model; VAR s : StateVar);
  PROCEDURE RemoveMV    (m: Model; VAR mv: REAL);
  PROCEDURE RemoveP     (m: Model; VAR p : Parameter);
  PROCEDURE RemoveAllModels;

  (* Global simulation parameters and project description: *)
  PROCEDURE SetDefltGlobSimPars(    t0, tend, h, er, c, hm: REAL);
  PROCEDURE GetDefltGlobSimPars(VAR t0, tend, h, er, c, hm: REAL);

  PROCEDURE SetDefltProjDescrs(    title,remark,footer: ARRAY OF CHAR;
                                   wtitle,wremark,autofooter,
                                   recM, recSV, recP, recMV, recG: BOOLEAN);
  PROCEDURE GetDefltProjDescrs(VAR title,remark,footer: ARRAY OF CHAR;
                               VAR wtitle,wremark,autofooter,
                                   recM, recSV, recP, recMV, recG: BOOLEAN);
| PROCEDURE SetDefltTabFuncRecording(    recTF: BOOLEAN);
| PROCEDURE GetDefltTabFuncRecording( VAR recTF: BOOLEAN);

  PROCEDURE SetDefltIndepVarIdent(    descr,ident,unit: ARRAY OF CHAR);
| PROCEDURE GetDefltIndepVarIdent(VAR descr,ident,unit: ARRAY OF CHAR);

  PROCEDURE SetGlobSimPars(    t0, tend, h, er, c, hm: REAL);
  PROCEDURE GetGlobSimPars(VAR t0, tend, h, er, c, hm: REAL);
  PROCEDURE SetProjDescrs(    title,remark,footer: ARRAY OF CHAR;
                              wtitle,wremark,autofooter,
                              recM, recSV, recP, recMV, recG: BOOLEAN);
  PROCEDURE GetProjDescrs(VAR title,remark,footer: ARRAY OF CHAR;
                          VAR wtitle,wremark,autofooter,
                              recM, recSV, recP, recMV, recG: BOOLEAN);
| PROCEDURE SetTabFuncRecording(    recTF: BOOLEAN);
| PROCEDURE GetTabFuncRecording(VAR recTF: BOOLEAN);

  PROCEDURE SetIndepVarIdent(    descr,ident,unit: ARRAY OF CHAR);
| PROCEDURE GetIndepVarIdent(VAR descr,ident,unit: ARRAY OF CHAR);

| PROCEDURE ResetGlobSimPars;
| PROCEDURE ResetProjDescrs;

      PROCEDURE SetMonInterval(hm: REAL); (* only for upward compatibility *)
      PROCEDURE SetIntegrationStep(h: REAL); (* only for upward compatibility *)
      PROCEDURE SetSimTime(t0,tend: REAL); (* only for upward compatibility *)

  (* Control of Display and Monitoring: *)
  PROCEDURE TileWindows;
  PROCEDURE StackWindows;

| PROCEDURE InstallTileWindowsHandler(doAtTile:PROC);
| PROCEDURE InstallStackWindowsHandler(doAtStack:PROC);

  TYPE MWWindow = (MIOW, SVIOW, PIOW, MVIOW, TableW, GraphW, AboutMW, TimeW);

  PROCEDURE SetWindowPlace(mww: MWWindow;     x,y,w,h: INTEGER);
  PROCEDURE GetWindowPlace(mww: MWWindow; VAR x,y,w,h: INTEGER; VAR isOpen : BOOLEAN);
  PROCEDURE SetDefltWindowPlace(mww: MWWindow;     x,y,w,h: INTEGER);
  PROCEDURE GetDefltWindowPlace(mww: MWWindow; VAR x,y,w,h: INTEGER; VAR enabled: BOOLEAN);
  PROCEDURE CloseWindow(w: MWWindow);

  TYPE
    IOWColsDisplay = RECORD
      descrCol, identCol : BOOLEAN;
      CASE iow: MWWindow OF
        MIOW  : m : RECORD
                     integMethCol: BOOLEAN;
                    END(*RECORD*);
      | SVIOW : sv: RECORD
                     unitCol, sVInitCol: BOOLEAN;
                     fw,dec: INTEGER;
                    END(*RECORD*);
      | PIOW  : p : RECORD
                     unitCol, pValCol, pRtcCol: BOOLEAN;
                     fw,dec: INTEGER;
                    END(*RECORD*);
      | MVIOW : mv: RECORD
                     unitCol, scaleMinCol, scaleMaxCol, mVMonSetCol: BOOLEAN;
                     fw,dec: INTEGER;
                    END(*RECORD*);
      END(*CASE*)
    END(*RECORD*);

  PROCEDURE SetIOWColDisplay     (mww: MWWindow;     wd: IOWColsDisplay );
  PROCEDURE GetIOWColDisplay     (mww: MWWindow; VAR wd: IOWColsDisplay );
  PROCEDURE SetDefltIOWColDisplay(mww: MWWindow;     wd: IOWColsDisplay );
  PROCEDURE GetDefltIOWColDisplay(mww: MWWindow; VAR wd: IOWColsDisplay );

  PROCEDURE DisableWindow(w: MWWindow);
  PROCEDURE EnableWindow (w: MWWindow);

| TYPE MWWindowArrangement = (current, stacked, tiled);
| PROCEDURE SetDefltWindowArrangement(    a: MWWindowArrangement);
| PROCEDURE GetDefltWindowArrangement(VAR a: MWWindowArrangement);
| PROCEDURE GetWindowArrangement     (VAR a: MWWindowArrangement);
| PROCEDURE ResetWindows;

  PROCEDURE SuppressMonitoring;
  PROCEDURE ResumeMonitoring;
  PROCEDURE InstallClientMonitoring( initClientMon, doClientMon, termClientMon: PROC );

| PROCEDURE SetStashFileName     (     sfn: ARRAY OF CHAR);
| PROCEDURE GetStashFileName     (VAR  sfn: ARRAY OF CHAR);
| PROCEDURE SetDefltStashFileName(    dsfn: ARRAY OF CHAR);
| PROCEDURE GetDefltStashFileName(VAR dsfn: ARRAY OF CHAR);
| PROCEDURE SetStashFileType     (     filetype, creator: ARRAY OF CHAR);
| PROCEDURE GetStashFileType     (VAR  filetype, creator: ARRAY OF CHAR);
| PROCEDURE SetDefltStashFileType(    dFiletype,dCreator: ARRAY OF CHAR);
| PROCEDURE GetDefltStashFileType(VAR dFiletype,dCreator: ARRAY OF CHAR);
  PROCEDURE SwitchStashFile      (newsfn: ARRAY OF CHAR);
| PROCEDURE ResetStashFile;

  PROCEDURE Message(m: ARRAY OF CHAR);

  TYPE
    Stain = (coal, snow, ruby, emerald, sapphire, turquoise, pink, gold, autoDefCol);
    LineStyle = (unbroken, broken, dashSpotted, spotted, invisible, purge, autoDefStyle);

  CONST autoDefSym = 200C;

  PROCEDURE SetCurveAttrForMV(m: Model; VAR mv: REAL;
                              st: Stain; ls: LineStyle; sym: CHAR);
  PROCEDURE GetCurveAttrForMV(m: Model; VAR mv: REAL;
                              VAR st: Stain; VAR ls: LineStyle; VAR sym: CHAR);
  PROCEDURE SetDefltCurveAttrForMV(m: Model; VAR mv: REAL;
                                   st: Stain; ls: LineStyle; sym: CHAR);
  PROCEDURE GetDefltCurveAttrForMV(m: Model; VAR mv: REAL;
                                   VAR st: Stain; VAR ls: LineStyle; VAR sym: CHAR);

| PROCEDURE ResetAllCurveAttributes;

| PROCEDURE ClearTable;
  PROCEDURE ClearGraph;
  PROCEDURE DumpGraph;

  (* Assignment of predefined values to global default  *)
  (* values and resetting of all current values         *)
| PROCEDURE SetPredefinitions;
| PROCEDURE ResetAll;

  (* Preferences and simulation environment modes: *)
  PROCEDURE SetDocumentRunAlwaysMode( dra: BOOLEAN );
  PROCEDURE GetDocumentRunAlwaysMode( VAR dra: BOOLEAN );
| PROCEDURE SetAskStashFileTypeMode(asft: BOOLEAN);
| PROCEDURE GetAskStashFileTypeMode(VAR asft: BOOLEAN);

  PROCEDURE SetRedrawTableAlwaysMode( rta: BOOLEAN );
  PROCEDURE GetRedrawTableAlwaysMode( VAR rta: BOOLEAN );
  PROCEDURE SetCommonPageUpRows( rows: CARDINAL );
  PROCEDURE GetCommonPageUpRows( VAR rows: CARDINAL );

  PROCEDURE SetRedrawGraphAlwaysMode( rga: BOOLEAN );
  PROCEDURE GetRedrawGraphAlwaysMode( VAR rga: BOOLEAN );
  PROCEDURE SetColorVectorGraphSaveMode(cvgs: BOOLEAN);
  PROCEDURE GetColorVectorGraphSaveMode(VAR cvgs: BOOLEAN);

  (* Customization of keyboard shortcuts for menu commands *)
  TYPE
|   MWMenuCommand = ( pageSetUpCmd, printGraphCmd, preferencesCmd, customizeCmd,

| (*core commands*)  setGlobSimParsCmd, setProjDescrCmd, selectStashFileCmd,

|                    resetGlobSimParsCmd, resetProjDescrCmd, resetStashFileCmd,
|                    resetWindowsCmd, resetAllIntegrMethodsCmd, resetAllInitialValuesCmd,
|                    resetAllParametersCmd, resetAllStashFilingCmd, resetAllTabulationCmd,
|                    resetAllGraphingCmd, resetAllScalingCmd, resetAllCurveAttrsCmd,
|                    resetAllCmd, defineSimEnvCmd,

| (*core commands*)  tileWindowsCmd, stackWindowsCmd, modelsCmd, stateVarsCmd,
| (*core commands*)  modelParamsCmd, monitorableVarsCmd, tableCmd, clearTableCmd,
| (*core commands*)  graphCmd, clearGraphCmd,

| (*core commands*)  startRunCmd, haltOrResumeRunCmd, stopCmd, startExperimentCmd);


| PROCEDURE SetMenuCmdAliasChar(cmd: MWMenuCommand; alias: CHAR);
| PROCEDURE GetMenuCmdAliasChar(cmd: MWMenuCommand; VAR alias: CHAR);

| PROCEDURE ResetCoreMenuCmdsAliasChars;
| PROCEDURE ResetAllMenuCmdsAliasChars;

(*==================================    SimMaster    ==================================*)

  (* Running of the standard interactive simulation environment *)
| PROCEDURE RunSimEnvironment( initSimEnv: PROC );
| PROCEDURE SimEnvRunning( progLevel: CARDINAL ):BOOLEAN;
| PROCEDURE InstallDefSimEnv( defineSimEnv: PROC );
| PROCEDURE ExecuteDefSimEnv;

  (* States of the simulation environment *)
  TYPE
    MWState    = (noSimulation, simulating, pause, noModel);
    MWSubState = (noRun, running, noSubState, stopped);

  PROCEDURE GetMWState   (VAR s: MWState);
  PROCEDURE GetMWSubState(VAR ss: MWSubState);
| PROCEDURE InstallStateChangeSignaling( doAtStateChange: PROC );

  (* Simulation run conditions *)
  TYPE TerminateConditionProcedure = PROCEDURE(): BOOLEAN;
       StartConsistencyProcedure   = PROCEDURE(): BOOLEAN;

| PROCEDURE InstallStartConsistency  ( startAllowed: StartConsistencyProcedure );
| PROCEDURE InstallTerminateCondition( isAtEnd: TerminateConditionProcedure);

  (* Control of elementary and structured simulation runs *)
  PROCEDURE SimRun;
  PROCEDURE PauseRun;
| PROCEDURE ResumeRun;
| PROCEDURE StopRun;

  PROCEDURE InstallExperiment( doExperiment: PROC );
| PROCEDURE SimExperiment;
| PROCEDURE StopExperiment;

  PROCEDURE ExperimentRunning(): BOOLEAN;
  PROCEDURE ExperimentAborted(): BOOLEAN;
  PROCEDURE CurrentSimNr(): INTEGER;

  PROCEDURE CurrentTime(): REAL;
  PROCEDURE CurrentStep(): INTEGER;
  PROCEDURE LastCoincidenceTime(): REAL;

(*  ==================================     E N D     ================================  *)

                    ModelWorks may be freely copied but not for profit!


  (***********************************************************************************)
  (*#####   O P T I O N A L   C L I E N T   I N T E R F A C E   M O D U L E     #####*)
  (***********************************************************************************)

(*==================================    SimEvents    ==================================*)

  CONST
    minEventClass=0; maxEventClass=3000; unknownEventClass=maxEventClass; timeAdvanceEventClass=maxEventClass-7;
    always = MIN(REAL); never = MAX(REAL);

  TYPE
    EventClass=[ minEventClass.. maxEventClass]; Transaction= ADDRESS;
    StateTransitionFunction = PROCEDURE( Transaction);
    StateTransition = RECORD ec: EventClass; fct: StateTransitionFunction; END;

  VAR
    nilTransaction: Transaction; (* read only! *)
    noStateTransition: ARRAY[0..0] OF StateTransition; (* read only! *)
    dummyDEVChg: REAL; (* read only! *)  schedulingDone: BOOLEAN;

  PROCEDURE EventClassExists( ec: EventClass): BOOLEAN;
  PROCEDURE AsTransaction(VAR d: ARRAY OF BYTE): Transaction;

  PROCEDURE DeclDEVM    (VAR m: Model;     initialize, input, output: PROC;
        			     statetransfct: ARRAY OF StateTransition; terminate, declModelObjects: PROC;
        			     descriptor, identifier: ARRAY OF CHAR; about: PROC);
  PROCEDURE GetDefltDEVM(VAR m: Model; VAR initialize, input, output: PROC;
            			 VAR statetransfct: ARRAY OF StateTransition; VAR terminate: PROC;
            			 VAR descriptor, identifier: ARRAY OF CHAR; VAR about: PROC);
  PROCEDURE SetDefltDEVM(VAR m: Model;     initialize, input, output: PROC;
          			     statetransfct: ARRAY OF StateTransition; terminate: PROC;
          			     descriptor, identifier: ARRAY OF CHAR; about: PROC);

  PROCEDURE InitEventScheduler;
  PROCEDURE ScheduleEvent(ec: EventClass; tau: REAL; alfa: Transaction);
| PROCEDURE ScheduleEventAt(ec: EventClass; t: REAL; alfa: Transaction);
  PROCEDURE NextEventAt(): REAL;
  PROCEDURE ProbeNextPendingEvent(VAR ec: EventClass; VAR when: REAL; VAR alfa: Transaction);
  PROCEDURE GetNextPendingEvent  (VAR ec: EventClass; VAR when: REAL; VAR alfa: Transaction);
  PROCEDURE PendingEvents(): INTEGER;
| PROCEDURE SchedulingOnlyAfter(tmin: REAL);    PROCEDURE EarliestSchedulingPossibleAt(): REAL;
  PROCEDURE DiscardEventsAfter(ec: EventClass; aftert: REAL; alfa: Transaction);
  PROCEDURE DiscardEventsBefore(beforet: REAL);

(*==================================   SimObjects    ==================================*)

  FROM SYSTEM    IMPORT ADDRESS;    FROM DMStrings IMPORT String;     FROM SimBase   IMPORT Model;

| TYPE RefAttr;

| VAR aDetachedRefAttr: RefAttr;

| PROCEDURE AttachRefAttrToModel  (m: Model; VAR a: RefAttr; val: ADDRESS);
| PROCEDURE DetachRefAttrFromModel(m: Model; VAR a: RefAttr );
| PROCEDURE AttachRefAttrToObject  (m: Model; VAR o: REAL; VAR a: RefAttr; val: ADDRESS);
| PROCEDURE DetachRefAttrFromObject(m: Model; VAR o: REAL; VAR a: RefAttr );
| PROCEDURE FindModelRefAttr (m: Model; VAR a: RefAttr);
| PROCEDURE FindObjectRefAttr(m: Model; VAR o: REAL; VAR a: RefAttr);
| PROCEDURE SetRefAttr(a: RefAttr; val: ADDRESS);
| PROCEDURE GetRefAttr(a: RefAttr): ADDRESS;

| PROCEDURE CurCalcMRefAttr(): ADDRESS;
| PROCEDURE CurAboutMRefAttr(): ADDRESS;

| PROCEDURE ModelLevel (m: Model):CARDINAL;
| PROCEDURE ObjectLevel(m: Model; VAR o: REAL):CARDINAL;

  TYPE
|   MWObj = (Mo, SV, Pa, MV, AV );
|   RealPtr = POINTER TO REAL;
|   PtrToClientObject = ADDRESS;

|   ModelPtr = POINTER TO ModelHeader;
|   ModelHeader = RECORD
|     ident		: String;
|     descr		: String;
|     fill1		: String;  (* not used *)
|     fill2  	: RealPtr; (* not used *)
|     fill3,               (* not used *)
|     fill4	    : REAL;    (* not used *)
|     nrAttr	: INTEGER;
|     refAttr	: PtrToClientObject; (* read only *)
|     chAttr	: CHAR;   (* may be freely used to mark the object *)
|     kind		: MWObj;  (* read only!! *)
|     parentM	: Model;  (* not used *)
|     next		: ModelPtr; (* read only!! *)
|     prev		: ModelPtr; (* read only!! *)
|  END(*ModelHeader*);

|  MObjPtr = POINTER TO MObjectHeader;
|  MObjectHeader = RECORD
|    ident		: String;
|    descr		: String;
|    unit		: String;
|    varAdr	: RealPtr; (* read only!!; real itself may be altered
|                            is the actual state var in case of an sv *)
|    min, max	: REAL;    (* is curScaleMin, curScaleMax in case of mv *)
|    nrAttr	: INTEGER; (* SimBase.Attribute *)
|    refAttr	: PtrToClientObject; (* read only *)
|    chAttr	: CHAR;    (* may be freely used to mark the object;
|                           e.g. used by module IdentifyPars to mark
|                           parameters for identification. *)
|    kind		: MWObj;  (* read only!! *)
|    parentM	: Model;  (* read only!! *)
|    next		: MObjPtr; (* read only!! *)
|    prev		: MObjPtr; (* read only!! *)
|  END(*MObjectHeader*);


| PROCEDURE FirstM(): ModelPtr;
| PROCEDURE MPtrToM(m: ModelPtr): Model;
| PROCEDURE MToMPtr(m: Model): ModelPtr;
| PROCEDURE IsSystem(m: ModelPtr): BOOLEAN; (* support for ISIS, see module SysModBase *)
| PROCEDURE FirstSV( m: Model ): MObjPtr;
| PROCEDURE SVsDeriv( sv: MObjPtr ): RealPtr; (* returns pointer to sv's Derivative or NewState *)
| PROCEDURE GetSVsInits( objp: MObjPtr; VAR defaultInit,curInit: REAL);
| PROCEDURE FirstP ( m: Model ): MObjPtr;
| PROCEDURE FirstMV( m: Model ): MObjPtr;
| PROCEDURE GetMVsDfltMon ( objp: MObjPtr;
|                           VAR defaultScaleMin,defaultScaleMax: REAL;
|                           VAR defaultSf: StashFiling;
|                           VAR defaultT: Tabulation;
|                           VAR defaultG: Graphing);
| PROCEDURE GetMVsCurMon( objp: MObjPtr;
|                         VAR curSf: StashFiling;
|                         VAR curT: Tabulation;
|                         VAR curG: Graphing);

| PROCEDURE LastM(): ModelPtr;
| PROCEDURE LastSV( m: Model ): MObjPtr;
| PROCEDURE LastP ( m: Model ): MObjPtr;
| PROCEDURE LastMV( m: Model ): MObjPtr;

| PROCEDURE RemoveAllSVsOfM (m: MPt);
| PROCEDURE RemoveAllPsOfM (m: MPt);
| PROCEDURE RemoveAllMVsOfM (m: MPt);
| PROCEDURE RemoveAllOfM (m: MPt);

(*==================================   SimDeltaCalc  ==================================*)

| TYPE  DeltaVar;       DeltaProc = PROCEDURE ( (*ySim~*)REAL, (*yData*)REAL ): REAL;

| VAR defaultDelta: DeltaProc;

| PROCEDURE InstallDeltaProc( VAR mvDepVar: REAL; compDelta: DeltaProc );
| PROCEDURE InitDeltaStat( VAR mvDepVar: REAL;  xSim, ySim: REAL; VAR dv: DeltaVar );
| PROCEDURE AccuDelta( dv: DeltaVar; xSim, ySim: REAL );
| PROCEDURE GetDeltaStat( VAR mvDepVar: REAL; VAR sumY, sumY2, sumAbsY: REAL; VAR count: INTEGER );
| PROCEDURE SetDeltaStat( VAR mvDepVar: REAL; sumY, sumY2, sumAbsY: REAL; count: INTEGER );
| PROCEDURE WriteDeltaStatMsg( VAR mvDepVar: REAL );

(*==================================  SimGraphUtils  ==================================*)

  FROM SimBase  IMPORT MWWindowArrangement, Model, Stain, LineStyle, Graphing;
  FROM DMWindIO IMPORT Color;
  FROM Matrices IMPORT Matrix;

  TYPE Curve;           VAR nonexistent : Curve;  (* read only! *)

  PROCEDURE PlaceGraphOnSuperScreen(defltwa: MWWindowArrangement);
  PROCEDURE SelectForOutputGraph;
  PROCEDURE DefineCurve( VAR c: Curve; st: Stain;  style: LineStyle;  sym: CHAR );
  PROCEDURE RemoveCurve( VAR c: Curve );
  PROCEDURE DrawLegend( c: Curve;  x, y: INTEGER;  comment: ARRAY OF CHAR );
  PROCEDURE Plot( c: Curve;  newX, newY: REAL );
  PROCEDURE Move( c: Curve;  newX, newY: REAL );
  PROCEDURE PlotSym( x, y: REAL;  sym: CHAR );
  PROCEDURE PlotCurve( c: Curve; nrOfPoints: CARDINAL; x, y: ARRAY OF REAL );
  PROCEDURE GraphToWindowPoint( xReal, yReal: REAL; VAR xInt, yInt: INTEGER );
  PROCEDURE WindowToGraphPoint( xInt, yInt: INTEGER; VAR xReal, yReal: REAL );

  TYPE Abscissa = RECORD isMV: POINTER TO REAL; xMin,xMax: REAL END;

  VAR timeIsIndep: REAL;

  PROCEDURE InstallGraphClickHandler(gch: PROC);
  PROCEDURE MVValToPoint(val: REAL; m: Model; VAR mv: REAL; VAR curG: Graphing): INTEGER;
  PROCEDURE PointToMVVal(xInt,yInt: INTEGER; m: Model; VAR mv: REAL; VAR curG: Graphing): REAL;
  PROCEDURE CurrentAbscissa(VAR a: Abscissa);		
  PROCEDURE TimeIsX() : BOOLEAN;

  PROCEDURE StainToColor( stain: Stain;  VAR color: Color );
  PROCEDURE ColorToStain( color: Color;  VAR stain: Stain );

  TYPE DisplayTime = ( showAtInit, showAtTerm, noAutoShow );
      DispDataProc = PROCEDURE( Model, VAR REAL );
  PROCEDURE DeclDispData( mDepVar    : Model;  VAR mvDepVar  : REAL;
                          mIndepVar  : Model;  VAR mvIndepVar: REAL;
                          x, v,
                          vLo, vUp   : ARRAY OF REAL;
                          n          : INTEGER;
                          withErrBars: BOOLEAN;
                          dispTime   : DisplayTime     );
  PROCEDURE DisplayDataNow( mDepVar : Model;  VAR mvDepVar  : REAL );
  PROCEDURE DisplayAllDataNow;
  PROCEDURE DoForAllDispData( p: DispDataProc );
  PROCEDURE RemoveDispData( mDepVar : Model;  VAR mvDepVar  : REAL );

  PROCEDURE DeclDispDataM( mDepVar    : Model;  VAR mvDepVar  : REAL;
                           mIndepVar  : Model;  VAR mvIndepVar: REAL;
                           data       : Matrix;
                           withErrBars: BOOLEAN;
                           dispTime   : DisplayTime     );
  PROCEDURE SetDispDataM( mDepVar: Model;  VAR mvDepVar: REAL;  data: Matrix  );
  PROCEDURE GetDispDataM( mDepVar: Model;  VAR mvDepVar: REAL;  VAR data: Matrix  );

(*==================================   SimIntegrate  ==================================*)

  PROCEDURE Integrate ( m: Model; from, till: REAL);

(*  ==================================     E N D     ================================  *)

                    ModelWorks may be freely copied but not for profit!

  Contact RAMSES@env.ethz.ch Last updated: 25-Jul-2011 [Top of page]