home *** CD-ROM | disk | FTP | other *** search
/ Crawly Crypt Collection 1 / crawlyvol1.bin / apps / spread / opusprg / opussrc / gr.pas < prev    next >
Pascal/Delphi Source File  |  1988-05-16  |  34KB  |  812 lines

  1.  
  2.  
  3. {$M+}
  4. {$E+}
  5.  
  6. PROGRAM Mock;
  7.  
  8. {$I i:\opus.i}
  9. {$I i:\GCTV.inc}
  10.  
  11. {$I i:\gemsubs.def}
  12. {$I i:\vdi_aes.def}
  13. {$I i:\globsubs.def}
  14. {$I d:\pascal\opus\xbios.def}
  15. {$I d:\pascal\opus\stringfn.def}
  16.  
  17. PROCEDURE GET_NUM_SCR_ENTRIES ( direction : ExpandDirection );
  18.    { right expansion is based on start_col;
  19.      left expansion is based on finish_col }
  20.    LABEL 1;
  21.    VAR x_tot,i,j,width : INTEGER;
  22.    BEGIN
  23.         IF start_row < logical_row_1 THEN
  24.            start_row := logical_row_1
  25.         ELSE IF start_row > n_rows THEN
  26.            start_row := n_rows;
  27.         IF start_col < logical_col_1 THEN
  28.            start_col := logical_col_1
  29.         ELSE IF start_col > n_cols THEN
  30.            start_col := n_cols;
  31.         IF finish_col > n_cols THEN
  32.            finish_col := n_cols
  33.         ELSE IF finish_col < logical_col_1 THEN
  34.            finish_col := logical_col_1;   
  35.         Work_Rect(act_hdl,x_1,y_1,w_1,h_1);
  36. 1:      h_entry := 0;
  37.         width := w_1-x_margin;
  38.         x_tot := 0;
  39.         i := 1;
  40.         IF direction = ExRight THEN BEGIN
  41.            WHILE i <= max_screen_cols DO BEGIN { right expand }
  42.               IF start_col+i-1 <= n_cols THEN
  43.                  IF x_tot+col_width[start_col+i-1,pixels] < width THEN BEGIN
  44.                     h_entry := h_entry+1;
  45.                     x_tot := x_tot+col_width[start_col+i-1,pixels]
  46.                  END
  47.                  ELSE
  48.                     i := max_screen_cols+1;
  49.               i := i+1
  50.            END;
  51.            IF (start_col > logical_col_1) AND
  52.               (h_entry > 0) THEN { left expand if possible }
  53.               IF x_tot+col_width[start_col-1,pixels] < width THEN BEGIN
  54.                  start_col := start_col-1;
  55.                  GOTO 1
  56.               END;
  57.            IF h_entry < 1 THEN
  58.               h_entry := 1;
  59.            finish_col := start_col+h_entry-1; { no need to check if > n_cols }
  60.            IF finish_col < n_cols THEN BEGIN
  61.               virtual_f_col := finish_col+1;
  62.               virtual_h_entry := h_entry+1
  63.            END
  64.            ELSE BEGIN
  65.               virtual_f_col := finish_col;
  66.               virtual_h_entry := h_entry
  67.            END
  68.         END
  69.         ELSE BEGIN
  70.            WHILE i <= max_screen_cols DO BEGIN { left expand }
  71.               IF finish_col-i+1 >= logical_col_1 THEN
  72.                  IF x_tot+col_width[finish_col-i+1,pixels] < width THEN BEGIN
  73.                     h_entry := h_entry+1;
  74.                     x_tot := x_tot+col_width[finish_col-i+1,pixels]
  75.                  END
  76.                  ELSE
  77.                     i := max_screen_cols+1;
  78.               i := i+1
  79.            END;
  80.            IF (finish_col < n_cols) AND
  81.               (h_entry > 0) THEN { right expand if possible }
  82.               IF x_tot+col_width[finish_col+1,pixels] < width THEN BEGIN
  83.                  finish_col := finish_col+1;
  84.                  GOTO 1
  85.               END;
  86.            IF h_entry < 1 THEN
  87.               h_entry := 1;
  88.            start_col := finish_col-h_entry+1; { no need to check if < }
  89.            IF finish_col < n_cols THEN BEGIN  { logical_col_1 }
  90.               virtual_f_col := finish_col+1;
  91.               virtual_h_entry := h_entry+1
  92.            END
  93.            ELSE BEGIN
  94.               virtual_f_col := finish_col;
  95.               virtual_h_entry := h_entry
  96.            END
  97.         END;   
  98.         v_entry := (h_1-y_margin) DIV cell_height;
  99.         finish_row := start_row+v_entry-1;
  100.         IF finish_row > n_rows THEN
  101.            finish_row := n_rows;
  102.         IF finish_row < n_rows THEN BEGIN
  103.            virtual_f_row := finish_row+1;
  104.            virtual_v_entry := v_entry+1
  105.         END
  106.         ELSE BEGIN
  107.            virtual_f_row := finish_row;
  108.            virtual_v_entry := v_entry
  109.         END;
  110.         IF data_row < start_row THEN
  111.            data_row := start_row
  112.         ELSE IF data_row > finish_row THEN
  113.            data_row := finish_row;
  114.         IF data_col < start_col THEN
  115.            data_col := start_col
  116.         ELSE IF data_col > finish_col THEN
  117.            data_col := finish_col
  118.    END; { GET_NUM_SCR_ENTRIES }
  119.  
  120. PROCEDURE DEF_VERT_GRID;
  121.    VAR i,j : INTEGER;
  122.    BEGIN
  123.         i := x_1+x_margin;
  124.         j := 1;
  125.         vert_grid[1] := i;
  126.         WHILE j <= virtual_h_entry DO BEGIN
  127.             i := i+col_width[start_col+j-1,pixels];
  128.             vert_grid[j+1] := i;
  129.             j := j+1
  130.         END
  131.    END; { DEF_VERT_GRID }
  132.  
  133. PROCEDURE DEF_SHEET_AREA;
  134.    BEGIN
  135.        get_num_scr_entries(ExRight);
  136.        def_vert_grid;
  137.        find_screen_pos(data_row,data_col,scr_row,scr_col); { keep current }
  138.        save_attr { most current attributes; ESSENTIAL!!! }
  139.    END; { DEF_SHEET_AREA }
  140.  
  141. FUNCTION DATA_CLIP : BOOLEAN;
  142.    BEGIN
  143.        data_clip := TRUE;
  144.        Work_Rect(act_hdl,x_1,y_1,w_1,h_1);
  145.        clip_x := x_1+x_margin+1;
  146.        clip_y := y_1+y_margin+1;
  147.        clip_w := w_1-(x_margin+1);
  148.        clip_h := h_1-(y_margin+1);
  149.        IF redraw_flag THEN BEGIN
  150.           IF redraw_x >= clip_x THEN BEGIN { redraw area within data area? }
  151.              clip_x := redraw_x;
  152.              clip_w := redraw_w
  153.           END
  154.           ELSE IF redraw_x+redraw_w > clip_x THEN { width within data area? }
  155.              clip_w := redraw_x+redraw_w-clip_x { set width then }
  156.           ELSE
  157.              data_clip := FALSE; { note that we could set w = 0, but }
  158.           clip_y := redraw_y;    { Set_Clip doesn't seem to work with clip }
  159.           clip_h := redraw_h     { width of zero }
  160.        END;
  161.        Set_Clip(clip_x,clip_y,clip_w,clip_h)
  162.    END; { DATA_CLIP }
  163.  
  164. PROCEDURE DRAW_SHEET ( extent                              : ExtentType;
  165.                        row_start,row_end,col_start,col_end : INTEGER;
  166.                        blit_flag                           : BOOLEAN );
  167.    LABEL 1;
  168.    VAR
  169.       i,j,k,offset,width,t,t2 : INTEGER;
  170.    BEGIN
  171.         { extent determines which parts of the screen are painted and then
  172.           redrawn. if NoRowNames, for example, the row names as displayed
  173.           are protected from being redrawn by limiting the clipping
  174.           rectangle }
  175.         Work_Rect(act_hdl,x_1,y_1,w_1,h_1);
  176.         CASE extent OF
  177.            NoRowNames : Set_Clip(x_1+x_margin+1,y_1,w_1-x_margin-1,h_1);
  178.            NoColNames : Set_Clip(x_1,y_1+y_margin+1,w_1,h_1-(y_margin+1));
  179.            WholeSheet  : IF redraw_flag THEN
  180.                             Set_Clip(redraw_x,redraw_y,redraw_w,redraw_h)
  181.                          ELSE
  182.                             Set_Clip(x_1,y_1,w_1,h_1);
  183.            JustData    : IF NOT data_clip THEN
  184.                              GOTO 1;
  185.         END; { CASE extent }
  186.         IF NOT blit_flag THEN
  187.            Paint_Rect(x_1,y_1,w_1,h_1);
  188.         Line_Color(LightBlue); 
  189.         Line_Style(Solid);
  190.         width := x_1+w_1;
  191.         Line(x_1,y_1+cell_height-1,width,y_1+cell_height-1);
  192.         IF freeze_row > 0 THEN
  193.            Line(x_1,y_1+y_margin,width,y_1+y_margin);
  194.         IF freeze_col > 0 THEN BEGIN
  195.            Line(x_1+38,y_1,x_1+38,y_1+h_1);
  196.            Line(vert_grid[1],y_1,vert_grid[1],y_1+h_1)
  197.         END
  198.         ELSE   
  199.            Line(vert_grid[1],y_1,vert_grid[1],y_1+h_1);
  200.         t := y_1+y_margin-cell_height+1;
  201.         t2 := y_1+y_margin;
  202.         { set up pts_in array so that we only have to calculate the }
  203.         { vertical coordinates of the lines once }
  204.         FOR k := row_start TO row_end+1 DO
  205.             pts_in[k] := t+k*cell_height;
  206.         IF rez = 1 THEN { high }
  207.            offset := 3
  208.         ELSE
  209.            offset := 2;
  210.         FOR j := col_start+1 TO col_end+1 DO BEGIN { vertical lines... }
  211.             Line_Style(Solid);                     { these are easy    }
  212.             Line(vert_grid[j],y_1,vert_grid[j],t2); { col title separators }
  213.             IF grid_flag THEN BEGIN
  214.                My_Line_Style ($AAAA); { grid }
  215.                FOR k := row_start TO row_end DO
  216.                    Line(vert_grid[j],pts_in[k],vert_grid[j],pts_in[k+1]-offset)
  217.             END   
  218.         END;
  219.         i := y_1+y_margin+row_start*cell_height;
  220.         Line_Style(Solid);
  221.         FOR j := row_start TO row_end DO BEGIN { horizontal lines }
  222.             Line(x_1,i,vert_grid[1],i); { row title separators }
  223.             i := i+cell_height
  224.         END;
  225.         { The big problem in drawing the grid is avoiding shifting lines
  226.           when moving off screen; the screen is blitted in the pertinent
  227.           direction. Now if the pixels in every column of the same width
  228.           are not in exactly the same relative positions, a 'shift' of the
  229.           grid lines occurs upn blitting; this is most annoying. So the first
  230.           step in avoiding this is to break the lines up into segments and
  231.           process them all the same way. This also applies to the vertical grid
  232.           but for some reason that was easy to do. If it were that easy for
  233.           the horizontal lines...
  234.           For the horizontal grid, a line pattern of X X X X... is sufficient
  235.           for mono, if it's drawn as below; this avoids shifting lines when
  236.           the screen is blitted left to right. The line segments are all
  237.           processed in the same way. This also works in
  238.           color, but the 'grid' looks like a dim solid line; no way the monitor
  239.           has 640 pixels resolution. Does a different line-type work? Not that
  240.           I could discover; the VDI does NOT always start a line with the most
  241.           sig. bit of the line style ( why it works in mono I don't know ), and
  242.           varying the offsets from the vertgrids proved fruitless. So, by
  243.           DRAWING lines in color, segments which are different in each column
  244.           appear, and the shifting lines are back. Solution? Process the
  245.           segments by columns, doing all the rows in a column, and begin by
  246.           PLOTTING the pixels in the first row. Then for the remaining rows,
  247.           BLIT a 1-pixel high raster of the plotted points in the position of
  248.           each segment in that column, and plotting every row is just too slow.
  249.           This way, every segment is processed identically, and no more
  250.           shifting lines. }
  251.  
  252.         IF grid_flag THEN BEGIN
  253.            IF rez = 2 THEN { med rez }
  254.               FOR j := col_start TO col_end DO BEGIN
  255.                   i := y_1+y_margin+row_start*cell_height;
  256.                   IF redraw_flag THEN
  257.                      WHILE i < redraw_y DO BEGIN
  258.                         i := i+cell_height;
  259.                         row_start := row_start+1
  260.                      END;
  261.                   k := vert_grid[j]+2;
  262.                   WHILE k < vert_grid[j+1]-2 DO BEGIN
  263.                      Plot(k,i);
  264.                      k := k+8
  265.                   END;
  266.                   FOR k := row_start+1 TO row_end DO BEGIN
  267.                       Blit(screen_mfdb,screen_mfdb,vert_grid[j]+1,i,
  268.                            vert_grid[j]+1,i+cell_height,
  269.                            vert_grid[j+1]-vert_grid[j],1);
  270.                       i := i+cell_height
  271.                   END
  272.               END
  273.            ELSE BEGIN
  274.               My_Line_Style($AAAA); { grid }
  275.               i := y_1+y_margin+row_start*cell_height;
  276.               FOR j := row_start TO row_end DO BEGIN
  277.                   FOR k := col_start TO col_end DO
  278.                       Line(vert_grid[k]+2,i,vert_grid[k+1]-2,i);
  279.                   i := i+cell_height
  280.               END
  281.            END
  282.         END;   
  283. 1: END; (* DRAW_SHEET *)
  284.  
  285. PROCEDURE TOGGLE_INVERSE ( color,row,col : INTEGER );
  286.    { proc to toggle inverse video on a CELL; uses a Paint_Rect call to do this
  287.      and is very fast as opposed to old method ( see DRAW_INVERSE_VIDEO ),
  288.      since no draw_string is called and needn't worry about format of cell }
  289.    { accepts row,col as sheet not screen coordinates }
  290.    { has already had it's clip rectangle set }
  291.    VAR x,y,w,h,l_scr_row,l_scr_col : INTEGER;
  292.    BEGIN
  293.        find_screen_pos(row,col,l_scr_row,l_scr_col);
  294.        x := vert_grid[l_scr_col]+1;                 { upper left corner }
  295.        y := y_1+y_margin+1+(l_scr_row-1)*cell_height; { of cell }
  296.        w := col_width[col,pixels]-1;
  297.        h := cell_height-1;
  298.        Draw_Mode(XOR_Mode);
  299.        Paint_Color(color);
  300.        Paint_Rect(x,y,w,h);
  301.        Paint_Color(White);
  302.        Draw_Mode(Replace_Mode)
  303.    END; { TOGGLE_INVERSE }
  304.  
  305. PROCEDURE PREP_CELL ( ptr : CellPtr; VAR temp : STRING );
  306.    BEGIN
  307.        temp := '';
  308.        IF ptr <> NIL THEN
  309.           IF ptr^.status <> Empty THEN
  310.              WITH ptr^ DO
  311.                 CASE class OF
  312.                    Val  : prepare_num(ptr,temp);
  313.                    Labl : temp := str^;
  314.                    Expr :
  315.                       IF NOT form_flag THEN { don't display formulas }
  316.                          IF status < OK THEN { error! }
  317.                             temp := error_msg[status]
  318.                          ELSE
  319.                             prepare_num(ptr,temp)
  320.                       ELSE
  321.                          temp := str^
  322.                 END
  323.    END; { PREP_CELL }
  324.  
  325. PROCEDURE SET_STYLE ( format : INTEGER );
  326.    VAR style : INTEGER;
  327.    BEGIN
  328.       IF format & style_mask <> 0 THEN BEGIN
  329.          style := 0;
  330.          IF format & bold_mask <> 0 THEN
  331.             style := style | Bold;
  332.          IF format & italic_mask <> 0 THEN
  333.             style := style | Italics;
  334.          IF format & under_mask <> 0 THEN
  335.             style := style | Underlined;
  336.          Text_Style(style)
  337.       END
  338.    END; { SET_STYLE }
  339.    
  340. PROCEDURE DRAW_CELL ( row,col : INTEGER; force : BOOLEAN );
  341.    { row,col are the positions within the sheet, not the screen positions }
  342.    LABEL 1;
  343.    VAR i,l_scr_row,l_scr_col : INTEGER;
  344.        in_range              : BOOLEAN;
  345.        temp                  : STRING;
  346.        ptr                   : CellPtr;
  347.        a                     : AssignedStatus;
  348.    BEGIN
  349.        { draw cell contents; i.e. extent = just_data, so... }
  350.        IF NOT data_clip THEN
  351.           GOTO 1;
  352.        temp := '';
  353.        { now find out what screen row and col we're in }
  354.        find_screen_pos(row,col,l_scr_row,l_scr_col);
  355.        a := assigned(row,col,ptr);
  356.        { the following lets me move among unassigned cells
  357.          without having to draw a blank cell for them, taking more time and
  358.          possibly writing over assigned ones adjacent to it that overlap.
  359.          However, I can punt this by passing a TRUE 'force' value. Useful
  360.          when I know for sure that I'm NOT moving, i.e. changing cell class,
  361.          updating on-screen cells from within a dialog routine ( sort, prec,
  362.          etc. ) }
  363.        IF (a = Void) OR (a = Desolate) THEN
  364.           IF NOT force THEN BEGIN { force = true forces a draw of the cell }
  365.              toggle_inverse(Black,row,col);
  366.              GOTO 1
  367.           END;
  368.        IF block_set THEN
  369.           in_range := (row >= b_s_row) AND (row <= b_e_row) AND
  370.                       (col >= b_s_col) AND (col <= b_e_col)
  371.        ELSE
  372.           in_range := FALSE;
  373.        prep_cell(ptr,temp); { we know we're going to draw }
  374.        total := 0;
  375.        y_pos := y_1+y_margin+cell_height+(l_scr_row-1)*cell_height-1;
  376.        { must first blank out the cell to be sure that when we draw
  377.          this one, nothing from adjacent cells spills into it }
  378.        Paint_Rect(vert_grid[l_scr_col]+1,y_pos-cell_height+2,
  379.                   col_width[col,pixels]-1,cell_height-1);
  380.        IF ptr <> NIL THEN
  381.           WITH ptr^ DO BEGIN
  382.              set_style(format);
  383.              CASE find_just(ptr) OF
  384.                 VDI_Left : Draw_Just(vert_grid[l_scr_col]+1,y_pos,
  385.                                      VDI_Left,temp);
  386.                 VDI_Center : Draw_Just(vert_grid[l_scr_col]+1+
  387.                                        col_width[col,pixels] DIV 2,
  388.                                        y_pos,VDI_Center,temp);
  389.                 VDI_Right : Draw_Just(vert_grid[l_scr_col+1],y_pos,
  390.                                       VDI_Right,temp)
  391.              END; { CASE }
  392.              Text_Style(Normal)
  393.           END; { WITH }       
  394.        { at this point the current cell has been drawn in replace mode
  395.          and ISN'T highlighted }
  396.        IF in_range THEN
  397.           toggle_inverse(Black,row,col);
  398.        IF (row = data_row) AND (col = data_col) THEN
  399.           toggle_inverse(Black,row,col);
  400. 1: END; { DRAW_CELL }
  401.  
  402.  
  403. PROCEDURE DISPLAY_DATA ( extent                       : ExtentType;
  404.                          row_begin,row_end,col_begin,
  405.                          col_end                      : INTEGER );
  406.    LABEL 1,2,3;
  407.    VAR i,j,k,l,row,col,m,t,style : INTEGER;
  408.        found,over,quit           : BOOLEAN;
  409.        temp                      : STRING;
  410.        ptr                       : CellPtr;
  411.    BEGIN
  412.        IF row_begin < logical_row_1 THEN
  413.           row_begin := logical_row_1
  414.        ELSE IF row_begin > n_rows THEN
  415.           row_begin := n_rows;
  416.        IF col_begin < logical_col_1 THEN
  417.           col_begin := logical_col_1
  418.        ELSE IF col_begin > n_cols THEN
  419.           col_begin := n_cols;
  420.        IF row_end < logical_row_1 THEN
  421.           row_end := logical_row_1
  422.        ELSE IF row_end > n_rows THEN
  423.           row_end := n_rows;
  424.        IF col_end < logical_col_1 THEN
  425.           col_end := logical_col_1
  426.        ELSE IF col_end > n_cols THEN
  427.           col_end := n_cols;
  428.        temp := '';
  429.        Work_Rect(act_hdl,x_1,y_1,w_1,h_1);
  430.        IF redraw_flag THEN
  431.           Set_Clip(redraw_x,redraw_y,redraw_w,redraw_h)
  432.        ELSE
  433.           Set_Clip(x_1,y_1,w_1,h_1);
  434.        Text_Color(Red);
  435.        { draw row numbers; no_col_names means we aren't changing them and
  436.          that implies we have moved up or down and thus need to redraw the
  437.          row numbers }
  438.        IF (extent = WholeSheet) OR (extent = NoColNames) THEN BEGIN
  439.           j := y_1+cell_height+y_margin-1;
  440.           t := x_1+38 DIV 2;
  441.           IF freeze_row > 0 THEN BEGIN
  442.              int_to_string(freeze_row,temp);
  443.              Draw_Just(t,j-cell_height,VDI_Center,temp)
  444.           END;
  445.           FOR i := start_row TO row_begin-1 DO
  446.               j := j+cell_height;
  447.           FOR i := row_begin TO row_end DO BEGIN
  448.               int_to_string(i,temp);
  449.               Draw_Just(t,j,VDI_Center,temp);
  450.               j := j+cell_height
  451.           END
  452.        END;
  453.        { draw column letters; if no_row_names we have moved left or right
  454.          and hence must redraw the col names }
  455.        IF (extent = WholeSheet) OR (extent = NoRowNames) THEN BEGIN
  456.           t := y_1+cell_height-2;
  457.           j := col_begin-start_col+1;
  458.           IF freeze_col > 0 THEN
  459.              Draw_Just(x_1+39+col_width[freeze_col,pixels] DIV 2,t,
  460.                        VDI_Center,col_name[freeze_col]);
  461.           FOR i := col_begin TO col_end DO BEGIN
  462.               { in the middle of a cell }
  463.               Draw_Just(vert_grid[j]+1+col_width[i,pixels] DIV 2,t,
  464.                         VDI_Center,col_name[i]);
  465.               j := j+1
  466.           END
  467.        END;
  468.        
  469.        { first determine the y coordinates here rather than within the inner
  470.          loop for speed }
  471.          
  472.        pts_in[1] := y_1+y_margin+(row_begin-start_row+1)*cell_height-1;
  473.        FOR i := 2 TO row_end-row_begin+1 DO
  474.            pts_in[i] := pts_in[i-1]+cell_height;
  475.        Text_Color(Black);
  476.        
  477.        IF (extent = WholeSheet) OR (extent = NoColNames) THEN
  478.           IF freeze_col > 0 THEN BEGIN
  479.              clip_x := x_1+39;
  480.              clip_y := y_1+y_margin+1;
  481.              clip_w := col_width[freeze_col,pixels]-1;
  482.              clip_h := h_1-(y_margin+1);
  483.              IF redraw_flag THEN BEGIN
  484.                 IF redraw_x > clip_x+clip_w THEN
  485.                    GOTO 2
  486.                 ELSE IF redraw_x >= clip_x THEN BEGIN
  487.                    IF redraw_x+redraw_w > clip_x+clip_w THEN
  488.                       clip_w := clip_w-(redraw_x-clip_x)
  489.                    ELSE
  490.                       clip_w := redraw_w;
  491.                    clip_x := redraw_x
  492.                 END
  493.                 ELSE IF redraw_x+redraw_w > clip_x THEN BEGIN
  494.                    clip_w := redraw_x+redraw_w-clip_x;
  495.                    IF clip_w > col_width[freeze_col,pixels] THEN
  496.                       clip_w := col_width[freeze_col,pixels]
  497.                 END
  498.                 ELSE
  499.                    GOTO 2;
  500.                 clip_y := redraw_y;
  501.                 clip_h := redraw_h
  502.              END;
  503.              Set_Clip(clip_x,clip_y,clip_w,clip_h);
  504.              FOR i := row_begin TO row_end DO BEGIN
  505.                  ptr := locate_cell(i,freeze_col);
  506.                  IF ptr <> NIL THEN BEGIN
  507.                     prep_cell(ptr,temp);
  508.                     set_style(ptr^.format);
  509.                     row := i+1-row_begin;
  510.                     CASE find_just(ptr) OF
  511.                        VDI_Left   : Draw_Just(x_1+39,pts_in[row],
  512.                                               VDI_Left,temp);
  513.                        VDI_Center : Draw_Just(x_1+39+
  514.                                               col_width[ptr^.c,pixels] DIV 2,
  515.                                               pts_in[row],VDI_Center,temp);
  516.                        VDI_Right  : Draw_Just(vert_grid[1],pts_in[row],
  517.                                               VDI_Right,temp)
  518.                     END; { CASE }
  519.                     Text_Style(Normal)
  520.                  END
  521.              END
  522.           END;
  523.           
  524. 2:     IF (extent = WholeSheet) OR (extent = NoRowNames) THEN
  525.           IF freeze_row > 0 THEN BEGIN
  526.              clip_x := x_1+x_margin+1;
  527.              clip_y := y_1+cell_height;
  528.              clip_w := w_1-(x_margin+1);
  529.              clip_h := h_1-cell_height;
  530.              IF redraw_flag THEN BEGIN
  531.                 IF redraw_x >= clip_x THEN BEGIN
  532.                    clip_x := redraw_x;
  533.                    clip_w := redraw_w
  534.                 END
  535.                 ELSE IF redraw_x+redraw_w > clip_x THEN
  536.                    clip_w := redraw_x+redraw_w-clip_x
  537.                 ELSE
  538.                    GOTO 3;   
  539.                 clip_y := redraw_y;
  540.                 clip_h := redraw_h
  541.              END;
  542.              Set_Clip(clip_x,clip_y,clip_w,clip_h);
  543.              m := y_1+y_margin-1;
  544.              FOR i := col_begin TO col_end DO BEGIN
  545.                  ptr := locate_cell(freeze_row,i);
  546.                  IF ptr <> NIL THEN BEGIN
  547.                     prep_cell(ptr,temp);
  548.                     set_style(ptr^.format);
  549.                     k := ptr^.c-start_col+1;
  550.                     CASE find_just(ptr) OF
  551.                        VDI_Left   : Draw_Just(vert_grid[k]+1,m,VDI_Left,temp);
  552.                        VDI_Center : Draw_Just(vert_grid[k]+1+
  553.                                               col_width[ptr^.c,pixels] DIV 2,
  554.                                               m,VDI_Center,temp);
  555.                        VDI_Right  : Draw_Just(vert_grid[k+1],m,VDI_Right,temp)
  556.                     END; { CASE }
  557.                     Text_Style(Normal)
  558.                  END
  559.              END
  560.           END;
  561.                  
  562.        { draw cell contents; i.e. extent = just_data, so... }
  563. 3:     IF NOT data_clip THEN
  564.           GOTO 1;
  565.        FOR i := row_begin TO row_end DO BEGIN
  566.            { needn't blank out individual unassigned cells since this is
  567.              only called when the entire sheet has been redrawn and the
  568.              screen painted }
  569.            found := FALSE;
  570.            quit := FALSE;
  571.            ptr := data[i];
  572.            WHILE (ptr <> NIL) AND (NOT found) AND (NOT quit) DO 
  573.               IF (ptr^.c >= col_begin) AND (ptr^.c <= col_end) THEN
  574.                  found := TRUE
  575.               ELSE IF ptr^.c > col_end THEN
  576.                  quit := TRUE
  577.               ELSE
  578.                  ptr := ptr^.next;
  579.            over := FALSE;
  580.            row := i-row_begin+1;
  581.            IF found THEN 
  582.               WHILE (ptr <> NIL) AND (NOT over) DO BEGIN
  583.                  { draw the current cell LAST because it may extend beyond the
  584.                    borders of itself, and its neighbors might overwrite this
  585.                    extension; want THIS cell to have precedence! }
  586.                  IF (i <> data_row) OR (ptr^.c <> data_col) THEN BEGIN
  587.                     prep_cell(ptr,temp);
  588.                     { here we could first blank out each cell or better yet
  589.                       check if bounding cells extend into the current cell
  590.                       and then blank it out; i.e. only the current cells
  591.                       contents would be in that cell with no overflow from
  592.                       other cells. But this would really slow things down,
  593.                       and since this really only applies to labels, the
  594.                       user should't have labels bigger than their cells
  595.                       and then want numbers in adjacent cells to be
  596.                       displayed properly; i.e. he might thus get something
  597.                       like this :
  598.                                   A     |     B
  599.                                Doug Harrison is a -9.0
  600.                       rather than :
  601.                                   A     |     B
  602.                                Doug Harri         -9.0
  603.                       This only apllies when the WHOLE window is redrawn;
  604.                       DRAW_CELL does, if the cell is assigned, blank out
  605.                       the cell first, and I think this is more
  606.                       important, and it doesn't slow things down... }
  607.                     set_style(ptr^.format);
  608.                     k := ptr^.c-start_col+1;
  609.                     CASE find_just(ptr) OF
  610.                        VDI_Left   : Draw_Just(vert_grid[k]+1,pts_in[row],
  611.                                               VDI_Left,temp);
  612.                        VDI_Center : Draw_Just(vert_grid[k]+1+
  613.                                               col_width[ptr^.c,pixels] DIV 2,
  614.                                               pts_in[row],VDI_Center,temp);
  615.                        VDI_Right  : Draw_Just(vert_grid[k+1],pts_in[row],
  616.                                               VDI_Right,temp)
  617.                     END; { CASE }
  618.                     Text_Style(Normal)
  619.                  END; { IF }
  620.                  ptr := ptr^.next;
  621.                  IF ptr <> NIL THEN
  622.                     IF ptr^.c > col_end THEN
  623.                        over := TRUE
  624.               END; { WHILE }
  625.            IF block_set THEN 
  626.               IF (i >= b_s_row) AND (i <= b_e_row) THEN
  627.                  FOR j := col_begin TO col_end DO 
  628.                      IF (j >= b_s_col) AND (j <= b_e_col) THEN
  629.                         toggle_inverse(Black,i,j)
  630.        END; { FOR i }
  631.        { so the output from this is such that ALL cells in a range are
  632.          highlighted }
  633.        draw_cell(data_row,data_col,FALSE);
  634. 1: END; (* DISPLAY_DATA *)
  635.  
  636. PROCEDURE SET_UP_CELL_NAME;
  637.    BEGIN
  638.       string_a_cell(data_row,data_col,col_row);
  639.       Set_Text(new_desk_ptr,editcell,col_row,s0,5)
  640.    END; { SET_UP_CELL_NAME }
  641.    
  642. PROCEDURE WRITE_CELL_NAME;
  643.    BEGIN
  644.       Set_Text(new_desk_ptr,editcell,'     ',s0,5);
  645.       Hide_Mouse;
  646.       Obj_Draw(new_desk_ptr,editcell,Max_Depth,
  647.                0,0,screen_width,screen_height);
  648.       set_up_cell_name;
  649.       Obj_Draw(new_desk_ptr,editcell,Max_Depth,
  650.                0,0,screen_width,screen_height);
  651.       Show_Mouse
  652.    END; { WRITE_CELL_NAME }
  653.  
  654. PROCEDURE SHEET_REDRAW ( extent    : ExtentType;
  655.                          blit_flag : BOOLEAN;
  656.                          direction : BlitDirection );
  657.    { note that caller *MUST* call Begin_Update beforehand!!! }
  658.    VAR
  659.        v_slider_pos,h_slider_pos,
  660.        i,j,x,y,w,h,x2,y2,vert_pos : INTEGER;
  661.     PROCEDURE RESET_WINDOW;
  662.        BEGIN
  663.            def_sheet_area;
  664.            save_attr; { do it again in case we had to home cursor.  }
  665.                       { Can't elimiate save_attr in def_sheet_area  }
  666.                       { because other routines call it; i.e.        }
  667.                       { MOVE_SHEET, and some of the column-movement }
  668.                       { routines }
  669.            IF (extent = WholeSheet) OR (extent = NoColNames) OR
  670.               ((blit_flag) AND (direction > Right)) THEN BEGIN           
  671.               v_slider_pos := TRUNC(1000.0*(start_row-1)/(n_rows-v_entry));
  672.               Wind_Set(act_hdl,WF_VSLSize,ROUND(1000.0*v_entry/n_rows),
  673.                        0,0,0);
  674.               Wind_Set(act_hdl,WF_VSlide,v_slider_pos,0,0,0)
  675.            END;   
  676.            IF (extent = WholeSheet) OR (extent = NoRowNames) OR
  677.               ((blit_flag) AND (direction < Up)) THEN BEGIN           
  678.               h_slider_pos := TRUNC(1000.0*(start_col-1)/(n_cols-h_entry));
  679.               Wind_Set(act_hdl,WF_HSLSize,ROUND(1000.0*h_entry/n_cols),
  680.                        0,0,0);
  681.               Wind_Set(act_hdl,WF_HSlide,h_slider_pos,0,0,0)
  682.            END   
  683.        END; (* RESET_WINDOW *)
  684.  
  685.     PROCEDURE BLIT_LEFT;
  686.        BEGIN
  687.            IF o_s_col <= finish_col THEN BEGIN
  688.               x := x_1+x_margin+1;
  689.               w := w_1;
  690.               y := y_1;
  691.               h := h_1;
  692.               i := start_col;
  693.               j := 1;
  694.               WHILE i <= finish_col DO BEGIN
  695.                   IF i = o_s_col THEN BEGIN
  696.                      vert_pos := j;
  697.                      i := 500
  698.                   END
  699.                   ELSE
  700.                      i := i+1;
  701.                   j := j+1
  702.               END;
  703.               x2 := vert_grid[vert_pos]+1;
  704.               y2 := y;
  705.               Blit(screen_mfdb,screen_mfdb,x,y,x2,y2,w,h);
  706.               Paint_Rect(x,y,x2-x,h_1);
  707.               draw_sheet(extent,1,virtual_v_entry,
  708.                                 1,o_s_col-start_col,TRUE);
  709.               display_data(NoRowNames,start_row,virtual_f_row,
  710.                                       start_col,o_s_col-1)
  711.            END
  712.            ELSE BEGIN
  713.               draw_sheet(extent,1,virtual_v_entry,1,virtual_h_entry,FALSE);
  714.               display_data(extent,start_row,virtual_f_row,
  715.                                   start_col,virtual_f_col)
  716.            END
  717.        END; { BLIT_LEFT }
  718.  
  719.     PROCEDURE BLIT_RIGHT;
  720.        BEGIN
  721.            IF o_f_col >= start_col THEN BEGIN
  722.               i := o_s_col;
  723.               j := 1;
  724.               WHILE i <= o_f_col DO BEGIN
  725.                   IF i = start_col THEN BEGIN
  726.                      vert_pos := j;
  727.                      i := 500
  728.                   END
  729.                   ELSE
  730.                      i := i+1;
  731.                   j := j+1
  732.               END;
  733.               x := old_vert_grid[vert_pos]+1;
  734.               y := y_1;
  735.               w := old_vert_grid[o_f_col-o_s_col+2]-old_vert_grid[vert_pos];
  736.               h := h_1;
  737.               x2 := x_1+x_margin+1;
  738.               y2 := y;
  739.               Blit(screen_mfdb,screen_mfdb,x,y,x2,y2,w,h);
  740.               Paint_Rect(x2+w,y,w_1,h_1);
  741.               draw_sheet(extent,1,virtual_v_entry,
  742.                                 h_entry-(finish_col-o_f_col)+1,
  743.                                 virtual_h_entry,TRUE);
  744.               display_data(NoRowNames,start_row,virtual_f_row,
  745.                                       o_f_col+1,virtual_f_col)
  746.            END
  747.            ELSE BEGIN
  748.               draw_sheet(extent,1,virtual_v_entry,1,virtual_h_entry,FALSE);
  749.               display_data(extent,start_row,virtual_f_row,
  750.                                   start_col,virtual_f_col)
  751.            END
  752.        END; { BLIT_RIGHT }
  753.  
  754.     PROCEDURE BLIT_UP;
  755.        BEGIN
  756.            x := x_1;
  757.            y := y_1+y_margin+1;
  758.            w := w_1;
  759.            h := h_1;
  760.            x2 := x;
  761.            y2 := y+cell_height;
  762.            Blit(screen_mfdb,screen_mfdb,x,y,x2,y2,w,h);
  763.            Paint_Rect(x,y,w,cell_height-1);
  764.            draw_sheet(extent,1,1,1,virtual_h_entry,TRUE);
  765.            display_data(NoColNames,start_row,start_row,
  766.                                    start_col,virtual_f_col)
  767.        END; { BLIT_UP }
  768.  
  769.     PROCEDURE BLIT_DOWN;
  770.        BEGIN
  771.            x := x_1;
  772.            y := y_1+y_margin+cell_height+1;
  773.            w := w_1;
  774.            h := cell_height*(v_entry-1)-1;
  775.            x2 := x;
  776.            y2 := y-cell_height;
  777.            Blit(screen_mfdb,screen_mfdb,x,y,x2,y2,w,h);
  778.            Paint_Rect(x,y2+h+1,w_1,h_1);
  779.            draw_sheet(extent,v_entry,virtual_v_entry,1,virtual_h_entry,TRUE);
  780.            display_data(NoColNames,finish_row,virtual_f_row,
  781.                                    start_col,virtual_f_col)
  782.        END; { BLIT_DOWN }
  783.  
  784.    BEGIN { SHEET_REDRAW }
  785.        Hide_Mouse;
  786.        reset_window;
  787.        IF NOT blit_flag THEN BEGIN
  788.           draw_sheet(extent,1,virtual_v_entry,1,virtual_h_entry,FALSE);
  789.           display_data(extent,start_row,virtual_f_row,
  790.                               start_col,virtual_f_col)
  791.        END
  792.        ELSE BEGIN
  793.           Set_Clip(x_1,y_1,w_1,h_1); {current because of Work_Rect}
  794.           CASE direction OF          {in def_sheet_area}
  795.              Left  : blit_left;
  796.              Right : blit_right;
  797.              Up    : blit_up;
  798.              Down  : blit_down
  799.           END
  800.        END;
  801.        Show_Mouse;
  802.        IF Front_Window = act_hdl THEN
  803.           write_cell_name
  804.    END; { SHEET_REDRAW }
  805.  
  806.  
  807. BEGIN
  808. END.
  809.  
  810.  
  811.  
  812.