DEFINITION MODULE SimGraphUtils;
  (*******************************************************************
    Module  SimGraphUtils     (MW_V3.0)
      Copyright (c) 1989-2006 by Olivier Roth, Andreas Fischlin, Dimitrios
      Gyalistras and ETH Zurich.
    Purpose   Utilities to make I/O to the graph window and the
              graph of the 'ModelWorks' modelling and simulation
              environment.
    Remarks   Most procedures behave similar to those of the module
              DM2DGraphs and may be combined with many procedures
              from DMWindIO. The window and its associated graph are
              objects of the 'ModelWorks' environment and should
              therefore not be removed.
              This module is part of the optional client interface of
              'ModelWorks', an interactive Modula-2 modelling and
              simulation environment.
    Programming
      o Design
        Olivier Roth              11/09/1989
      o Implementation
        Olivier Roth              12/09/1989
        Andreas Fischlin          15/09/1989
        Dimitrios Gyalistras      13/07/1990
    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:  22/04/1996  AF
  *******************************************************************)
  FROM SimBase IMPORT MWWindowArrangement, Model, Stain, LineStyle, Graphing;
  FROM DMWindIO IMPORT Color;
  FROM Matrices IMPORT Matrix;
  TYPE
    Curve;
  VAR
    nonexistent: Curve;  (* read only! *)
  (**********************************************************************)
  (*#####   Control ModelWorks windows on a multi-screen machine   #####*)
  (**********************************************************************)
  PROCEDURE PlaceGraphOnSuperScreen(defltwa: MWWindowArrangement);
  (* Defines the default window arrangement according to 'defltwa'
  and places the ModelWorks graph window on the largest color
  screen in case the Model Definition Program is running on a
  multi-screen machine. *)
  (******************************************************)
  (*#####   Access the ModelWorks 'Graph' window   #####*)
  (******************************************************)
  PROCEDURE SelectForOutputGraph;
  (* This procedures brings the ModelWorks 'Graph' window to front
  and makes it the current output window.  This allows subsequently
  calls to almost all of the I/O procedures of the 'Dialog
  Machine' module 'DMWindIO'.  *)
  (************************)
  (*#####   Curves   #####*)
  (************************)
  (*
    The following procedures server to access the GRAPH in the 'Graph'
    window similar to the routines exported by module DM2DGraphs (see
    'Dialog Machine')
  *)
  PROCEDURE DefineCurve( VAR c: Curve;
                         col: Stain;  style: LineStyle;  sym: CHAR );
  (* Every curve has it own plotting style and color.This allows
  for the simultaneous drawing of an arbitary number of curves
  within the ModelWorks graph. sym specifies a character which is
  drawn repeatedly at the data points, they help identifying a
  curve (sym = 0C, no mark is plotted).
  Use this procedure also if you want to alter an allready existing
  curve.  *)
  PROCEDURE RemoveCurve( VAR c: Curve );
  (* This procedure removes a curve definition. This procedure sets c
  to nonexistent. *)
  PROCEDURE DrawLegend( c: Curve;  x, y: INTEGER;  comment: ARRAY OF CHAR );
  (* Draws a portion of curve c with the current attributes at position
  x and y and writes the comment to the right of c. After this procedure
  the pen location is just to the right of the string "comment", so it«s
  possibe to add for example values of parameters by calling DMWindIO
  procedures WriteReal (etc.) just after this procedure. *)
  PROCEDURE Plot( c: Curve;  newX, newY: REAL );
  (* You can plot (draw a curve) from the last (saved) position to the point
  specified by the new coordinates newX and newY.
  Note:   ModelWorks resets the pen position when clearing the graph.
  Errors: If the point specified by newX and newY lies outside the integer
          (pixel) range DM2DGraphsDone will be set to FALSE. *)
  PROCEDURE Move( c: Curve;  newX, newY: REAL );
  (* moves the pen to postion (x,y). Typically used to draw several curves
  with the same attributes to reset the pen position after having drawn a
  curve.
  Errors: If the point specified by x and y lies outside the integer (pixel)
          range DM2DGraphsDone will be set to FALSE. *)
  PROCEDURE PlotSym( x, y: REAL;  sym: CHAR );
  (* draws the symbol sym at the position (x,y). May be used as an alternate
  method to make scatter grams.
  Errors: If the point specified by x and y lies outside the integer (pixel)
          range DM2DGraphsDone will be set to FALSE. *)
  PROCEDURE PlotCurve( c: Curve; nrOfPoints: CARDINAL; x, y: ARRAY OF REAL );
  (* Plots an entier sequence of nrOfPoints coordinate pairs contained within
  the two vectors x and y. May also be useful to implement an update mechanism.
  Errors: - If the point specified by x and y lies outside the integer (pixel)
            range DM2DGraphsDone will be set to FALSE.
          - If the maximum number of elements of x or y is less than nrOfPoints,
            then only the lower number of elements of either x or y will be
            plotted. WARNING: The x and y arrays are value parameters,
            hence require sufficient stack size at run time. The design of
            this routine is for curves of a rather small dimension.  To
            plot large data sets use instead of PlotCurve the procedure
            DeclDispDataM (see below).  *)
  PROCEDURE GraphToWindowPoint( xReal, yReal: REAL;
                                VAR xInt, yInt: INTEGER );
  (* Calculates the pixel coordinates (xInt and yInt) of the
  graph's window (see WindowIO) from the specified graph
  coordinates (xReal and yReal). Note that the vertical axis of the
  ModelWorks graph is transformed to yMin = 0.0 and yMax = 1.0 (see
  also procedure MVValToPoint).
  Errors: If the point specified by xReal and yReal lies outside
          the integer (pixel) range, DM2DGraphsDone will be set to
          FALSE and xInt and yInt is set to MIN(INTEGER) or
          MAX(INTEGER) respectively. *)
  PROCEDURE WindowToGraphPoint( xInt, yInt: INTEGER;
                                VAR xReal, yReal: REAL );
  (* Calculates graph coordinates (xReal and yReal) from the
  specified pixel coordinates (xInt and yInt) of the graph's window
  (see WindowIO). Note that the vertical axis of the ModelWorks
  graph is transformed to yMin = 0.0 and yMax = 1.0 (see also
  procedure PointToMVVal).
  Errors: If the point specified by xReal and yReal lies outside the
          integer (pixel) range, DM2DGraphsDone will be set to FALSE
          and xInt and yInt is set to MIN(INTEGER) or MAX(INTEGER)
          respectively. *)
  (***********************************************************************)
  (*#####   Drawing procedures used in a ModelWorks aware context   #####*)
  (***********************************************************************)
  PROCEDURE InstallGraphClickHandler(gch: PROC);
  (* Installs the mouse click handler procedure gch into the
  ModelWorks simulation environment.  After successful
  installation, each time the simulationist clicks into the graph
  window, gch will be called and a pair of xpixel coordinates [x,y]
  where the mouse click occurred, are passed to the handler.  Use
  procedures such as PointToMVVal to interprete the meaning of the
  point [x,y] in terms of monitorable variables. *)
  VAR
    timeIsIndep: REAL;
  PROCEDURE PointToMVVal(xInt,yInt: INTEGER; m: Model; VAR mv: REAL;
                         VAR curG: Graphing): REAL;
  (* Returns the corresponding value of the monitorable variable mv
  of the model m from the given pixel coordinates (xInt and yInt)
  of the ModelWorks graph window. As a side effect the routine
  returns also the current graphing of the mv. In case the mv
  should currently not be in display (curG=notInGraph), the value
  is returned as if curG would have been isY. To denote the
  independent variable time, use timeIsIndep as the actual
  parameter for mv (see also procedure WindowToGraphPoint).
  Errors: If m or mv should not be known to ModelWorks' model base,
          the routine displays an appropriate error message and returns
          0.0 and curG=notInGraph.
          If the point specified by xReal and yReal lies outside the
          integer (pixel) range, DM2DGraphsDone will be set to FALSE
          and xInt and yInt is set to MIN(INTEGER) or MAX(INTEGER)
          respectively. *)
  PROCEDURE MVValToPoint(val: REAL; m: Model; VAR mv: REAL;
                         VAR curG: Graphing): INTEGER;
  (* Returns the pixel coordinate for the window Graph (see
  WindowIO) from the specified coordinate val interpreted for the
  monitorable variable mv of the model m. As a side effect the
  routine returns also the current graphing of the mv. In case the
  mv should currently not be in display (curG=notInGraph), the
  value is returned as if curG would have been isY. To denote the
  independent variable time, use timeIsIndep as the actual
  parameter for mv (see also procedure GraphToWindowPoint).
  Errors: If m or mv should not be known to ModelWorks' model base,
          the routine displays an appropriate error message and returns
          0 and curG=notInGraph.
          If the point specified by val lies outside the integer
          (pixel) range, DM2DGraphsDone will be set to FALSE and the
          routine returns either MIN(INTEGER) or MAX(INTEGER)
          respectively. *)
  PROCEDURE TimeIsX() : BOOLEAN;
  (* Above procedure returns whether time is the current abscissa (x axis). *)
  TYPE
    Abscissa = RECORD isMV: POINTER TO REAL; xMin,xMax: REAL END;
  PROCEDURE CurrentAbscissa(VAR a: Abscissa);
  (* Returns a pointer (isMV) to the monitorable variable currently used as
  abscissa and its extremes (xMin~curScaleMin,xMax~curScaleMax). In case that
  time is in use, isMV will point to timeIsIndep *)
  (*************************************************************)
  (*#####   Procedures to convert different Color Types   #####*)
  (*************************************************************)
  PROCEDURE StainToColor( stain: Stain;  VAR color: Color );
  PROCEDURE ColorToStain( color: Color;  VAR stain: Stain );
  (* Translates Stain from module SimBase to Color from module
  DMWindIO and vice versa; exception for StainToColor:
  autoDefCol is translated to black. *)
  (***********************************************************************)
  (*#####   Display data series (e.g. for validation) all at once   #####*)
  (***********************************************************************)
   (*
   Follow these steps to use the data display feature of that module:
   1. Declare an ordinary monitorable variable with the procedure 'DeclMV'
      as a "master" monitorable variable for data arrays to be
      declared later (see next step). Several properties, i.e. descr,
      ident, unit, (and curve attributes as color, linestyle, symbol)
      will be inheritated by the later associated data arrays. So if the
      monitorable variable's graphing variable is set 'isY' the data are
      selected to be displayed. (This mv is called "master"-mv in what
      follows)
   2. Since the data arrays symbol (CHAR), line style (LineStyle) and
      color (Stain) will be taken from the "master" monitorable variable
      you can call 'SetCurveAttrForMV' and ev. 'SetDefltCurveAttrForMV'.
   3. Declare the associated data arrays with the "master" monitorable
      variable, the independent monitorable variable, and all the data
      arrays with a call to 'DeclDispData'.
   4. To enable the display mechanism the monitorable variable mvDepVar
      must be isY and mvIndepVar must be isX. If another monitorable
      variable represents the current x axis then nothing can be
      displayed.
   5. ModelWorks will display automatically all declared data in the
      normal graph of the "Graph" window at the specified moment,
      i.e. typically at InitMonitoring, or at TermMonitoring. To
      allow for a general control of the moment of display the
      procedure 'DisplayDataNow' and 'DisplayAllDataNow' are also
      exported.
   Caution:
      - Be sure to follow the steps given above in the correct
        order (1 before 3!) or no data can be declared and displayed.
      - Do not assign any values to the "master" monitorable variable
        to avoid conflicts with the data declaration.
      - Setting writeInTable or writeOnFile of the "Master" monitorable
        variable is not prohibited but makes no sence, since a
        dummy value {NAN(017)} and not the data series will be displayed.
  *)
  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;
                          withRangeBars: BOOLEAN;
                          dispTime     : DisplayTime     );
  (* In order to display a data series (e.g. validation data) f.ex. before a
  simulation run, the necessary data have to be declared beforehand, i.e.
  normally just at the end of all other ModelWorks objects declarations.
  The variables are as follows:
    mDepVar      : model to which belongs the mvDepVar
    mvDepVar     : monitorable variable representing the dependent data array
    mIndepVar    : model to which belongs the mvIndepVar
    mvIndepVar   : monitorable variable representing the independent data array,
                   if mvIndepVar is specified
                   "timeIsIndep" (or is not a declared monitorable var), then
                   "time" is assumed to be the independent variable,
    x            : array of independent values,
    v            : array of dependent values,
    vLo          : array of lower e.g. confidence or range values,
    vUp          : array of upper e.g. confidence or range values,
    n            : number of given data,
    withRangeBars: flag, if TRUE range bars will be drawn using vLo and vUp,
    dispTime     : the time when the data should be displayed,
  Note:
  The curve attributes of the data to display can be set through the
  procedure 'SetCurvAttrForMV' on the monitorable variable 'mvDepVar' and
  the default strategy for curve attributes assignments are the same as for
  ordinary monitorable variables for color and symbol but not for the
  lineStyle:
    the default line style is hidden which means that the connections from
    [x,v]-point to [x,v]-point are not drawn. In that case and if withRangeBars
    is set true then the error bars are displayd solidly. All other line styles
    are applied to the connections from point to point as well as to the error
    bars themselves.
  This procedure allows also redeclare such data series, i.e. to associate
  other data to the same mvDepVar and mvIndepVar.
  WARNING: The x, v, vLo, vUp arrays are value parameters,
            hence require sufficient stack size at run time. The design of
            this routine is for vectors of a rather small dimension.  To
            plot large data sets use instead of this routine the procedure
            DeclDispDataM (see below).
   *)
  PROCEDURE DeclDispDataM( mDepVar      : Model;  VAR mvDepVar  : REAL;
                           mIndepVar    : Model;  VAR mvIndepVar: REAL;
                           data         : Matrix;
                           withRangeBars: BOOLEAN;
                           dispTime     : DisplayTime     );
  (* alternate form of DeclDispData (described above) using type Matrix to pass
   * the data (x = col 1, v = col 2, vLo = col 3, vUp = col 4) *)
  PROCEDURE DisplayDataNow( mDepVar : Model;  VAR mvDepVar  : REAL );
  (* This procedure allows to display a series of e.g. validation data
  before a simulation run. The previously declared data are displayed
  in the current graph window under the following conditions:
    + the data have been declared properly and are valid;
    + the associated monitorable variable is selected to be displayed (isY);
    + the declared indepVar is the currently active independent
      monitorable variable (isX);
    + the declared indepVar is either not a monitorable variable (for
      example 'timeIsIndep' what implies that time is meant) and time is
      the selected independent var;
    + the data fall into the declared scaling range;
   *)
  PROCEDURE DisplayAllDataNow;
  (* Displays all declared datasets at the specified moments. The same conditions
  apply as for 'DisplayDataNow'.
   *)
  PROCEDURE DoForAllDispData( p: DispDataProc );
  (* Calls procedure p for all DispData currently declared. Be
  careful when using this procedure, since it allows to access
  also DispData-definitions which may not belong to the caller.
  *)
  PROCEDURE RemoveDispData( mDepVar : Model;  VAR mvDepVar  : REAL );
  (* This procedure allows to free the memory from the declared data
  to display.
   *)
  PROCEDURE SetDispDataM( mDepVar: Model;  VAR mvDepVar: REAL;  data: Matrix  );
  PROCEDURE GetDispDataM( mDepVar: Model;  VAR mvDepVar: REAL;  VAR data: Matrix  );
  (* these procedures allow to set/retrieve the installed data through matrices *)
END SimGraphUtils.