ETHZ_Logo RAMSES_Logo_Right    RAMSES    RAMSES_Logo_Left Systems Ecology   

Example: TableGraph

Screen Dump


Source Code


MODULE TableGraph;

  (**************************************************************)
  (*                                                            *)
  (*   Sample demo program module for the 'Dialog Machine'.     *)
  (*                                                            *)
  (*   May be used to read numerical data from a normal         *)
  (*   text file and display them as line charts.               *)
  (*   The numerical data may be edited in a table and the      *)
  (*   various chart parameters may be altered interactively.   *)
  (*                                                            *)
  (*   Demonstrates the usage of DMEditFields and DM2DGraphs.   *)
  (*                                                            *)
  (*                                                            *)
  (*        Version 1.1 English    date:  6/Sep/95  ( af, or )  *)
  (*                                                            *)
  (**************************************************************)
  (*                                                            *)
  (*        Programming:     A.Itten                            *)
  (*                         C E L T I A                        *)
  (*                         Swiss Federal Institute of Techno- *)
  (*                         logy Zurich ETHZ                   *)
  (*                         ETH-Zentrum                        *)
  (*                         CH-8092 Zuerich                    *)
  (*                                                            *)
  (**************************************************************)

  FROM DMSystem     IMPORT ScreenHeight, ScreenWidth, MenuBarHeight,
                           ScrollBarWidth, TitleBarHeight,
                           ComputerSystem, MacII;
  FROM DMMathLib    IMPORT Real, Sin;
  FROM DMMaster     IMPORT MouseHandlers,
                           AddSetupProc, RunDialogMachine, Wait,
                           ShowWaitSymbol, HideWaitSymbol, DialogMachineTask;
 
  FROM DMMenus      IMPORT Menu, Command, AccessStatus, Marking,
                           InstallMenu, InstallCommand, InstallQuitCommand,
                           Separator, InstallSeparator, InstallAbout,
                           DisableCommand, EnableCommand, ChangeCommandText;

  FROM DMWindows    IMPORT Window, WFFixPoint, WindowsDone,
                           WindowKind, ScrollBars, CloseAttr, ZoomAttr, WindowFrame,
                           CreateWindow, SetRestoreProc, SetCloseProc, DummyRestoreProc,
                           AutoRestoreProc, UpdateWindow, NoBackground,
                           GetWindowFrame, RectArea, RemoveWindow,
                           WindowExists, PutOnTop;

  FROM DMWindIO     IMPORT WindowFont, GreyContent, FontStyle, FontStyles,
                           SetWindowFont, CellHeight, CellWidth,
                           EraseContent, Area, SetPos, WriteLn,
                           MoveOriginTo, SetContSize, SetScrollStep,
                           AutoScrollProc, SetScrollProc, SetPattern, pat,
                           SelectForOutput, SetPen, WriteReal, WriteString,
                           Write, WriteCard, WriteInt,
                           LineTo, Color, red, green, blue, magenta, cyan, 
                           yellow, white, black;

  FROM DMEditFields IMPORT EditItem, ItemType, RadioBut, Direction,
                           EditFieldsDone,
                           MakePushButton, BeginRadioButtonSet,
                           AddRadioButton, EndRadioButtonSet, MakeCheckBox,
                           MakeStringField, MakeRealField,
                           EditHandler, InstallEditHandler, GetEditItemType,
                           IsChar, IsCardinal, IsInteger, IsReal,
                           GetRadioButtonSet, GetCheckBox, GetString,
                           SetChar, SetCardinal, SetInteger, SetReal,
                           SetRadioButtonSet, SetCheckBox, SetString,
                           EnableItem, DisableItem, SelectField,
                           RemoveEditItem, RemoveAllEditItems;

  FROM DMEntryForms IMPORT FormFrame, WriteLabel, UseEntryForm;

  FROM DMConversions IMPORT RealFormat, RealToString, StringToReal;

  FROM DMMessages         IMPORT DoInform;

  IMPORT                   DMFiles;

  FROM DM2DGraphs IMPORT   Graph, Curve, GridFlag, ScalingType,
                           PlottingStyle, Range, AxisType,
                           DM2DGraphsDone,
                           DefGraph, DefCurve, RedefCurve, RedefGraph,
                           ClearGraph, DrawGraph, DoForAllGraphs,
                           Plot, Move, PlotCurve, RemoveGraph, RemoveAllGraphs;



  CONST maxColumns =   6;  (* max number of colomns *)
        maxLines   = 100;  (* max number of lines *)

        border     = 30;
        cellLength = 12;
        margin     =  5;


  VAR
    controlMenu      : Menu;
      openCommand,
      saveCommand,
      quitCommand    : Command;
    winMenu        : Menu;
      graphCommand,
      ctrlCommand   : Command;

    controlWindow,
    tableWindow,
    graphWindow      : Window;
    cf, wf           : WindowFrame;
    controlRect      : RectArea;
    dateFile         : DMFiles.TextFile;

    ch, cw,             (* width and height of a cell in the table *)
    usedLines,
    usedColumns,
    xCol             : INTEGER;

    drawCol          : BITSET;

    table            : ARRAY [ 0..maxColumns-1], [0..maxLines-1] OF EditItem;
    value            : ARRAY [-1..maxColumns-1], [0..maxLines-1] OF REAL;
    rb               : ARRAY [-1..maxColumns-1] OF RadioBut;
    cb               : ARRAY [ 0..maxColumns-1] OF EditItem;
    xAxRBS,
    drawPB,
    xMinField,
    xMaxField,
    yMinField,
    yMaxField,
    xTitleField,
    yTitleField,
    xMode, yMode,
    axisSelector     : EditItem;
    xTitle, yTitle   : ARRAY[0..64] OF CHAR;

    xLin, xLog,
    yLin, yLog,
    xAxRB, yAxRB     : RadioBut;

    fieldsInstalled,            (* TRUE if the fields in the control window are installed *)
    xAxisSelected,
    tableDirty       : BOOLEAN; (* TRUE if table was edited *)

    graph            : Graph;
    curve            : ARRAY [0..maxColumns-1]  OF Curve;
    xAx, yAx         : AxisType;
    grid             : GridFlag;
    grErr            : BOOLEAN;


 (********************************    Table Procedures     **************************************)


  PROCEDURE MarkWindowAsDirty( ei: EditItem );
    (* Installed to the Dialog Machine as an "Edit Handler" ( see DMEditFIelds ) *)
  BEGIN
    tableDirty:= TRUE;
  END MarkWindowAsDirty;


  PROCEDURE  TableRestoreProc( u: Window );
    (* Update procedure of the table window. Redraws only the head line and the left border
       of the table. All edit fields are restored by DMEditFields. *)
    VAR i: INTEGER;
  BEGIN
    FOR i:= 1 TO usedLines DO
      SetPen( 3, -border -i*ch );
      WriteInt( i, 3 );
    END; (*FOR*)
    SetPen( 3, -2*CellHeight() ); WriteString( "Nr:" );
    FOR i:= 0 TO usedColumns -1 DO
      SetPen( border +i*cw  +( cw -CellWidth() ) DIV 2 , -2*CellHeight() );
      Write( CHR( i+ORD( "A" ) ) );
    END; (*FOR*)
  END TableRestoreProc;


  PROCEDURE MakeTableWindow;
    (* Creates the table window and installs all associated edit fields *)
    VAR i, j: INTEGER;
  BEGIN
    WITH wf DO
      (* fill screen *)
      w:= ScreenWidth() -ScrollBarWidth() -2*margin;
      h:= ScreenHeight() -MenuBarHeight() 
          -TitleBarHeight() -ScrollBarWidth() -2*margin;
      x:= margin;
      y:= margin +ScrollBarWidth();
    END; (*WITH*)

    (* create a window of kind GrowOrShrinkOrDrag, with two scrollbars, without a close box,
       with a zoom box and with the fix point for growing at top left. Because we want first
       define some window parameters different to the default values, we assign the dummy
       restore procedure which does no window updating. *)
    CreateWindow( tableWindow,
                  GrowOrShrinkOrDrag, WithBothScrollBars,
                  WithoutCloseBox, WithZoomBox, topLeft, wf, "Table",
                  DummyRestoreProc );

    SetWindowFont( Monaco, 9, FontStyle{} );
    ch:= CellHeight() +5;
    cw:= cellLength*CellWidth() +8;

    WITH cf DO  (* actual content frame *)
      x:= 0;
      y:= -( usedLines +1 )*ch -2*border;
      w:= usedColumns*cw +2*border;
      h:= ( usedLines +1 )*ch +2*border;
    END; (*WITH*)

    (* Definition of the actual size of the window content  and the step by wich the Dialog Machine
       will scroll if the user clicks inside the up or down arrow. The default Scroll procedure
       will be used. *)
    SetContSize( tableWindow, cf );
    SetScrollStep( tableWindow, cw, ch );
    SetScrollProc( tableWindow, AutoScrollProc );

    (* insallation of the edit fields of type RealField. Their initital values are defined in
       the procedure InitGraph and the legal range is set to the maximum. *)
    ShowWaitSymbol;
    FOR j:= 0 TO usedLines-1 DO
      FOR i:= 0 TO usedColumns-1 DO
        MakeRealField ( tableWindow, table[i, j], i*cw +border,
                   -border -( j+1 )*ch, cellLength,
                   value[i, j], MIN( REAL ), MAX( REAL ) );
      END; (*FOR*)
    END; (*FOR*)

    (* select first field in the table. *)
    SelectField( table[0, 0] );

    tableDirty:= FALSE;

    (* install the procedure MarkWindowAsDirty as an edit handler into the window *)
    InstallEditHandler( tableWindow, MarkWindowAsDirty );

    (* now assign our restore procedure and create an implicit update event *)
    SetRestoreProc( tableWindow, TableRestoreProc );

    HideWaitSymbol;
  END MakeTableWindow;

 (********************************   Close Window Handler  **************************************)

  PROCEDURE CollectControlInput(): BOOLEAN; FORWARD;


  PROCEDURE CloseWindowHandler( u: Window; VAR  goon: BOOLEAN );
    (* this procedure is assigned to the control and graph window to perform some tasks
       in case the user closes the approprate window *)
  BEGIN
    IF u = controlWindow THEN
      goon:= CollectControlInput();
    ELSIF u = graphWindow THEN
      RemoveGraph( graph );
      goon := TRUE;
    END; (*IF*)
  END CloseWindowHandler;


 (********************* Control Procedures ************************)

  PROCEDURE DrawRect( rect: RectArea );  (* draw a rectangle in current output window *)
  BEGIN
    SetPattern( pat[dark] );
    WITH rect DO
      SetPen( x, y );
      LineTo( x  , y+h ); LineTo( x+w, y+h );
      LineTo( x+w, y   ); LineTo( x  , y   );
    END; (*WITH*)
  END DrawRect;


  PROCEDURE  ControlRestoreProc( u: Window );
  (* Write those things into the window, which will be not updated by DMEditFields *)
  BEGIN
    IF xAxisSelected THEN
      SetPen( 15, -55 ); WriteString( "x-Axis" );
    ELSE
      SetPen( 15, -55 ); WriteString( "y-Axis" );
    END; (*IF*)
    SetPen(  15, - 59 ); LineTo( 70, -59 );
    SetPen(  15, -100 ); WriteString( "Min =" );
    SetPen( 150, -100 ); WriteString( "Max =" );
    SetPen(  15, -125 ); WriteString( "Title =" );
    DrawRect( controlRect );
  END ControlRestoreProc;


  PROCEDURE ChangeControlWindow( ei: EditItem );
  (* this procedure is used as an Edit handler: it changes the appereance of the control window
     every time the user selects the other radio button to indicate that he/she want\264s to
     alter the other axis parameters. This mechanism is used to make the control window as small
     as possible. *)
    VAR rb1, rb2: RadioBut;
        i  : INTEGER;
        ch : ARRAY[0..0] OF CHAR;
  BEGIN
    SelectForOutput( controlWindow );
    IF ( ei = axisSelector ) THEN (* axis selector radio button set clicked *)
      GetRadioButtonSet( axisSelector, rb1 ); (* get new value *)
      IF ( rb1 = xAxRB ) AND NOT xAxisSelected THEN
        (* if x-axis not already selected then first collect the user input for the
           y-axis parameters. If there is no error then remove all edit items of the
           y-axis and install the item of the x-axis. *)
        IF CollectControlInput() THEN
          xAxisSelected:= TRUE;
          RemoveEditItem( yMode );           (* radioButtonSet *)
          FOR i:= 0 TO usedColumns -1 DO
            RemoveEditItem( cb[i] );         (* all checkboxes *)
          END; (*FOR*)
          RemoveEditItem( yMinField );       (* RealField *)
          RemoveEditItem( yMaxField );       (* RealField *)
          RemoveEditItem( yTitleField );     (* StringField *)

          SetPen( 15, -55 ); WriteString( "x-Axis" );
          BeginRadioButtonSet( controlWindow, xMode );
            AddRadioButton( xLin, 120, -55, "linear" );
            AddRadioButton( xLog, 210, -55, "log scale" );
            IF xAx.scale = lin THEN rb2:= xLin ELSE rb2:= xLog END;
          EndRadioButtonSet( rb2 );
          BeginRadioButtonSet( controlWindow, xAxRBS );
          AddRadioButton( rb[-1], 15, -75, "Nr:" );
          FOR i:= 0 TO usedColumns -1 DO
            ch[0]:= CHR( i+ORD( "A" ) );
            AddRadioButton( rb[i], 25 +( i+1 )*35, -75, ch );
          END; (*FOR*)
          EndRadioButtonSet( rb[xCol] );
          MakeRealField  ( controlWindow, xMinField,  65, -100, 8, xAx.range.min, MIN( REAL ), MAX( REAL ) );
          MakeRealField  ( controlWindow, xMaxField, 201, -100, 8, xAx.range.max, MIN( REAL ), MAX( REAL ) );
          MakeStringField( controlWindow, xTitleField, 65, -125, 25, xAx.label );
          SelectField( xMinField );
        ELSE (* in case of an error return to y-axis input mode *)
          SetRadioButtonSet( axisSelector, yAxRB );
        END; (*IF*)
      ELSIF ( rb1 = yAxRB ) AND xAxisSelected THEN
        (* if y-axis not already selected then first collect the user input for the
           x-axis parameters. If there is no error then remove all edit items of the
           x-axis and install the item of the y-axis. *)
        IF CollectControlInput() THEN
          xAxisSelected:= FALSE;
          RemoveEditItem( xMode );          (* radioButtonSet *)
          RemoveEditItem( xAxRBS );         (* radioButtonSet *)
          RemoveEditItem( xMinField );      (* RealField *)
          RemoveEditItem( xMaxField );      (* RealField *)
          RemoveEditItem( xTitleField );    (* StringField *)

          SetPen( 15, -55 ); WriteString( "y-Axis" );
          BeginRadioButtonSet( controlWindow, yMode );
            AddRadioButton( yLin, 120, -55, "linear" );
            AddRadioButton( yLog, 210, -55, "log scale" );
            IF yAx.scale = lin THEN rb2:= yLin ELSE rb2:= yLog END;
          EndRadioButtonSet( rb2 );
          FOR i:= 0 TO usedColumns -1 DO
            ch[0]:= CHR( i+ORD( "A" ) );
            MakeCheckBox( controlWindow, cb[i], 25 +( i+1 )*35, -75, ch, i IN drawCol );
          END; (*FOR*)
          MakeRealField  ( controlWindow, yMinField,  65, -100, 8, yAx.range.min, MIN( REAL ), MAX( REAL ) );
          MakeRealField  ( controlWindow, yMaxField, 201, -100, 8, yAx.range.max, MIN( REAL ), MAX( REAL ) );
          MakeStringField( controlWindow, yTitleField, 65, -125, 25, yAx.label );
          SelectField( yMinField );
        ELSE (* in case of an error return to y-axis input mode *)
          SetRadioButtonSet( axisSelector, xAxRB );
        END; (*IF*)
      END; (*IF*)
    END; (*IF*)
  END ChangeControlWindow;


  PROCEDURE Draw; FORWARD;


  PROCEDURE MakeControlWindow;
    VAR wf   : WindowFrame;
        i    : INTEGER;
        ch   : ARRAY[0..0] OF CHAR;
        defRB: RadioBut;
  BEGIN
    IF NOT WindowExists( controlWindow ) THEN
      WITH wf DO
        (* window of fixed size *)
        w:= 360;
        h:= 145;
        (* center in lower third of screen *)
        x:= (ScreenWidth() - w) DIV 2;
        y:= ((ScreenHeight() - MenuBarHeight()) DIV 3 - h) DIV 2; 
        IF y= MacII THEN
      usedColumns:= maxColumns;
    ELSE
      usedColumns:= 3;
    END; (*IF*)
    usedLines  := maxLines;
    InitGraph;
    MakeTableWindow;
    MakeGraphWindow;
    MakeControlWindow;
  END DoSetUp;

 (********************* Menu Installation ***********************)

  PROCEDURE SetUpMenus;
  BEGIN
    InstallAbout(   "About TableGraph ...", 300, 160, AboutProc );
    InstallMenu(    controlMenu, "Control", enabled );
    InstallCommand( controlMenu, openCommand, "Open\u2026 ", Open,
                    enabled, unchecked );
    InstallCommand( controlMenu, saveCommand, "Save as\u2026", Save,
                    enabled, unchecked );
    InstallQuitCommand( "Quit", QuitP, "Q" );

    InstallMenu(    winMenu, "Windows", enabled );
    InstallCommand( winMenu, graphCommand, "Graph", Draw,
                    enabled, unchecked );
    InstallSeparator( winMenu, line );
    InstallCommand( winMenu, ctrlCommand, "Control Panel", MakeControlWindow,
                    enabled, unchecked );
    AddSetupProc ( DoSetUp, 0 );
    NoBackground;
  END SetUpMenus;


BEGIN
  SetUpMenus;
  RunDialogMachine;
END TableGraph.

  RAMSES@env.ethz.ch Last modified 1/30/23 [Top of page]   

Modula-2 website ring
List all    |    <<  Prev    |    Next  >>    |    Join