[comp.os.vms] New changes to SWING

nagy%warner.hepnet@LBL.GOV (Frank J. Nagy, VAX Wizard & Guru) (01/06/88)

Another interested user here at Fermilab has provided a better (than
my last distributed fix) set of changes to SWING which I am
distributing here.  Below is the note on these changes from the
modifier:

	This  afternoon,  I  finally  got  a chance to look at SWING
	again.  I was able to  solve  the  original  problem  -  one
	change  took  care  of  that  which  you corrected, plus the
	annoying screen shift on the first update.  One of our users
	also  uncovered  a  problem  with a system error (arithmetic
	trap) when attempting to delete a tree branch that contained
	one  or more subdirectories created outside of SWING and NOT
	SAVED.  This I was also able  to  fix  by  putting  a  limit
	(MAX_NODES)  on  a DO WHILE loop.  The following modules are
	available to you as updates in in the VMS_SHAR below: 

	    DRAW_SCREEN.FOR - correct display positioning
	    FIND_NODE.FOR   - limit 'unknown' node search
	    SWING.FOR       - update modification history 
                              (no code changes here)

	Modifications by Lin A. Winterowd of Fermilab.


= Frank J. Nagy   "VAX Guru & Wizard"
= Fermilab Research Division EED/Controls
= HEPNET: WARNER::NAGY (43198::NAGY) or FNAL::NAGY (43009::NAGY)
= BitNet: NAGY@FNAL
= USnail: Fermilab POB 500 MS/220 Batavia, IL 60510

....................... Cut between dotted lines and save ......................
$!..............................................................................
$! VAX/VMS archive file created by VMS_SHAR V-5.01 01-Oct-1987
$! which was written by Michael Bednarek (U3369429@ucsvc.dn.mu.oz.au)
$! To unpack, simply save and execute (@) this file.
$!
$! This archive was created by NAGY
$! on Wednesday 6-JAN-1988 06:40:10.84
$!
$! It contains the following 3 files:
$! DRAW_SCREEN.FOR FIND_NODE.FOR SWING.FOR
$!==============================================================================
$ Set Symbol/Scope=(NoLocal,NoGlobal)
$ Version=F$GetSYI("VERSION") ! See what VMS version we have here:
$ If Version.ges."V4.4" then goto Version_OK
$ Write SYS$Output "Sorry, you are running VMS ",Version, -
                ", but this procedure requires V4.4 or higher."
$ Exit 44
$Version_OK: CR[0,8]=13
$ Pass_or_Failed="failed!,passed."
$ Goto Start
$Convert_File:
$ Read/Time_Out=0/Error=No_Error1/Prompt="creating ''File_is'" SYS$Command ddd
$No_Error1: Define/User_Mode SYS$Output NL:
$ Edit/TPU/NoSection/NoDisplay/Command=SYS$Input/Output='File_is' -
        VMS_SHAR_DUMMY.DUMMY
f:=Get_Info(Command_Line,"File_Name");b:=Create_Buffer("",f);
o:=Get_Info(Command_Line,"Output_File");Set(Output_File,b,o);
Position(Beginning_of(b));Loop x:=Erase_Character(1);Loop ExitIf x<>"V";
Move_Vertical(1);x:=Erase_Character(1);Append_Line;
Move_Horizontal(-Current_Offset);EndLoop;Move_Vertical(1);
ExitIf Mark(None)=End_of(b) EndLoop;Position(Beginning_of(b));Loop
x:=Search("`",Forward,Exact);ExitIf x=0;Position(x);Erase_Character(1);
If Current_Character='`' then Move_Horizontal(1);else
Copy_Text(ASCII(INT(Erase_Character(3))));EndIf;EndLoop;Exit;
$ Delete VMS_SHAR_DUMMY.DUMMY;*
$ Checksum 'File_is
$ Success=F$Element(Check_Sum_is.eq.CHECKSUM$CHECKSUM,",",Pass_or_Failed)+CR
$ Read/Time_Out=0/Error=No_Error2/Prompt=" CHECKSUM ''Success'" SYS$Command ddd
$No_Error2: Return
$Start:
$ File_is="DRAW_SCREEN.FOR"
$ Check_Sum_is=1584627796
$ Copy SYS$Input VMS_SHAR_DUMMY.DUMMY
X      subroutine draw_screen
X
X      include    'swing.cmn'
X      include    '($smgdef)'
X
XC
XC    To cope with strange terminal screen lengths
XC        19 --- > linest - 5
XC        20 --- > linest - 4
XC        23 --- > linest - 1
XC
XC
XC       Added by EH Perkins, Aug 16, 1987
XC
X
X`009integer linest
X`009common /length/ linest
X
X      integer    ii, jj, kk, smg$change_pbd_characteristics
X      integer    smg$change_rendition
X
X      call smg$begin_pasteboard_update( board_id )
X
X      call smg$paste_virtual_display( window2, board_id, 3, 1 )`009`009!LAW
X      call smg$paste_virtual_display( window1, board_id, 2, 1 )
X      call smg$paste_virtual_display( window3, board_id,
X     .                                (linest - 1), 1 )
X
X      call smg$set_display_scroll_region( window3, 1, 2 )
X
X      call pd_draw_bar( board_id )
X
X      top_line = 1
X      bottom_line = (linest - 4)
X
X      node_num = node_pointer( cur_level, cur_line )
X
X      call smg$change_rendition( window2, cur_line, cur_level*17+1,
X     .                           1, 12,
X     .                           smg$m_bold + node(node_num).rend )
X
X      if ( cur_line .gt. bottom_line ) then
X`009 top_line = cur_line - (linest - 5)
X`009 bottom_line = cur_line
X`009 call smg$move_virtual_display( window2, board_id,
X     .                                  (linest - 1) - cur_line, 1 )
X`009 else if ( cur_line .lt. top_line ) then
X`009 top_line = cur_line
X`009 bottom_line = cur_line + (linest - 5)
X         call smg$move_virtual_display( window2, board_id,
X     .                                     cur_line, 1 )
X         end if
X
X      call update_window1
X
X      call smg$end_pasteboard_update( board_id )
X
X      call smg$set_cursor_abs( window2, cur_line, cur_level*17+1 )
X
X      update = .true.
X
X      return
X      end
$ GoSub Convert_File
$ File_is="FIND_NODE.FOR"
$ Check_Sum_is=1679971356
$ Copy SYS$Input VMS_SHAR_DUMMY.DUMMY
X      logical function find_node( dir_spec, ptr )
X
X      include    'swing.cmn'
X
X      character  dir_spec*(*)
X      integer    ii, jj, ptr
X      logical    found_node
X
X      ii = len( dir_spec )
X      do while ( dir_spec(ii:ii) .eq. ' ' .and. ii .gt. 0 )
X         ii = ii - 1
X      end do
X
X      jj = 1
X      found_node = .false.
X      do while ( .not. found_node .and. jj .le. max_nodes)`009`009!LAW
X         if ( node(jj).length .ne. 0 ) then
X         if ( node(jj).spec(1:node(jj).length) .eq. dir_spec(1:ii) )then
X            found_node = .true.
X            ptr = jj
X            end if
X         end if
X         jj = jj + 1
X      end do
X
X      find_node = found_node
X
X      return
X      end
$ GoSub Convert_File
$ File_is="SWING.FOR"
$ Check_Sum_is=1870215468
$ Copy SYS$Input VMS_SHAR_DUMMY.DUMMY
X*=======================================================================
X*
X*  Title:        SWING
X*
X*  Version:      1-001
X*
X*  Abstract:     SWING is a VMS utility for displaying and manipulating
X*                VMS directory trees.
X*
X*  Environment:  VMS
X*
X*  Author:       Eric Andresen of General Research Corporation
X*
X*  Date:         24-SEP-1986
X*
X*-----------------------------------------------------------------------
X*
X*  Modified and
X*  Expanded by:  Craig Young of Hughes Aircraft Company
X*
X*  Additions:    The main addition was the FILER and all the subroutines
X*                which support it.  The DCL Command option was added to
X*                the SWING command menu.  Changes were made to subroutine
X*                Load_Nodes to support '<' and '>' as directory indica-
X*                tors, to allow the Master file directory as the root
X*                directory and to allow the START qualifier.
X*
X*  Date:         3-AUG-1987
X*
X*-----------------------------------------------------------------------
X*
X*  Modified by:`009 Frank J Nagy of Fermilab
X*
X*  Changes:`009 Modified main routine to pick up command line as foreign
X*`009`009 command, add the SWING verb and parse it with DCL so that
X*`009`009 the /START qualifier can be checked for.
X*
X*  Date:         16-AUG-1987
X*
X*-----------------------------------------------------------------------
X*
X*  Modified by:  Lin A Winterowd of Fermilab
X*
X*  Changes:      Modified  DRAW_SCREEN  to correct initial screen layout
X*                positioning error; and FIND_NODE to  limit  search  for 
X*                directory  created  outside  of  SWING  and  not  SAVED 
X*                (causing arithmetic trap on DELETE operation).
X
X      program swing
X
X      include 'swing.cmn'
X      include '($smgdef)'
X
X      integer linest
X      common /length/ linest
X
X      integer    ii, jj, istat
X      integer    ikey, old_level, old_line, isave, code, code_type
X      integer    smg$create_virtual_display
X      logical    crt, finished
X      character  key, choice*(PD_MAX_CHOICE_LEN)
X
X`009External  Swing_Tables
X`009Integer*4 Lib$Get_Foreign, Cli$Dcl_Parse, Lib$Get_Input, sts
X`009Character*255 CmdLine
X`009Integer*2 CL_Len
X
XC
XC Get the Foreign Command line, tack the verb onto the front and
XC invoke the DCL command processor on the result.
XC
X`009sts = Lib$Get_Foreign( CmdLine,, CL_Len)
X`009IF (.NOT. sts) CALL Lib$Signal( %VAL(sts))
X`009IF (CL_Len .gt. 0) Then
X`009    sts = Cli$Dcl_Parse( 'SWING '//CmdLine(1:CL_Len),
X`0091`009`009`009Swing_Tables, Lib$Get_Input)
X`009Else
X`009    sts = Cli$Dcl_Parse( 'SWING ', Swing_Tables, Lib$Get_Input)
X`009EndIf
X`009IF (.NOT. sts) CALL Exit
X
X      if ( .not. crt() )
X     .   call print_message( 'You must use a DEC CRT terminal', 1 )
X
X      call define_paste_board
X
Xc     CREATE THE WINDOWS
X
X      istat = smg$create_virtual_display(  1, 132, window1 )
X      istat = smg$create_virtual_display(  MAX_LINES, 132, window2 )
X      istat = smg$create_virtual_display(  2, 132, window3 )
X      istat = smg$create_virtual_display(  12, 25, file_window )
X      call smg$set_display_scroll_region(  file_window )
X      istat = smg$create_virtual_display(  15, 70, DCL_window )
X      call smg$set_display_scroll_region(  DCL_window )
X
X      call load_nodes
X      call define_smg_layout
X      call load_display
X      call draw_screen
X
X      proc_created = 0
X
X      do while ( .not. finished )
X
X         call smg$read_keystroke( keyboard, ikey )
X
X         call print_message( ' ', 0 )
X
X         old_line = cur_line
X         old_level = cur_level
X         old_rend = node(node_num).rend
X
X         code_type = 0
X         code = 0
X
X         if ( ikey .eq. smg$k_trm_do .or.
X     .        ikey .eq. smg$k_trm_ctrlp ) then
X            if ( avo ) then
X               call pd_get_choice( board_id, keyboard, width,
X     .                             pull_choices, choice, code )
X               code_type = code / 10
X            else
X               call print_message( 'Advanced video option required', 0 )
X               end if
X            end if
X
X         if ( ikey .eq. smg$k_trm_ctrlz .or.
X     .        ikey .eq. smg$k_trm_f10         .or.
X     .        ikey .eq. smg$k_trm_lowercase_x .or.
X     .        ikey .eq. smg$k_trm_uppercase_x .or.
X     .        ikey .eq. smg$k_trm_lowercase_e .or.
X     .        ikey .eq. smg$k_trm_uppercase_e .or.
X     .        ikey .eq. smg$k_trm_lowercase_q .or.
X     .        ikey .eq. smg$k_trm_uppercase_q .or.
X     .        ikey .eq. smg$k_trm_enter       .or.
X     .        ikey .eq. smg$k_trm_cr          .or.
X     .        code .eq. 91 ) then
X            finished = .true.
X
X            else if ( ikey .eq. smg$k_trm_up ) then
X            ii = cur_level
X            jj = cur_line - 1
X            do while( jj .ge. 1 .and. node_pointer(ii,jj) .eq. 0 )
X               jj = jj - 1
X            end do
X            if ( jj .ge. 1 ) cur_line = jj
X            call update_screen( old_line, old_level )
X
X            else if ( ikey .eq. smg$k_trm_down ) then
X            ii = cur_level
X            jj = cur_line + 1
X            do while( node_pointer(ii,jj) .eq. 0 .and.jj .le. num_lines)
X               jj = jj + 1
X            end do
X            if ( jj .le. num_lines ) cur_line = jj
X            call update_screen( old_line, old_level )
X
X            else if ( ikey .eq. smg$k_trm_right ) then
X            ii = cur_level + 1
X            jj = cur_line
X            do while( node_pointer(ii,jj) .eq. 0 .and.ii.le. MAX_LEVELS)
X               ii = ii + 1
X            end do
X            if ( ii .le. MAX_LEVELS ) cur_level = ii
X            call update_screen( old_line, old_level )
X
X            else if ( ikey .eq. smg$k_trm_left .and.
X     .                cur_level .ge. 1 ) then
X            ii = cur_level - 1
X            jj = cur_line
X            do while( node_pointer(ii,jj) .eq. 0 .and. jj .ge. 1 )
X               jj = jj - 1
X            end do
X            if ( jj .ge. 1 ) then
X               cur_level = ii
X               cur_line = jj
X               end if
X            call update_screen( old_line, old_level )
X
X            else if ( ikey .eq. smg$k_trm_lowercase_b .or.
X     .                ikey .eq. smg$k_trm_uppercase_b ) then
X            ii = MAX_LEVELS
X            cur_line = num_lines
X            do while( node_pointer(ii,cur_line) .eq. 0 .and. ii .ge. 1 )
X               ii = ii - 1
X            end do
X            cur_level = ii
X            call update_screen( old_line, old_level )
X
X            else if ( ikey .eq. smg$k_trm_lowercase_t .or.
X     .                ikey .eq. smg$k_trm_uppercase_t ) then
X            cur_line = 1
X            cur_level = 0
X            call update_screen( old_line, old_level )
X
X            else if ( code_type .eq. 1 .or.
X     .                ikey .eq. smg$k_trm_lowercase_c .or.
X     .                ikey .eq. smg$k_trm_uppercase_c ) then
X            call create_directory( code )
X
X            else if ( code_type .eq. 2 .or.
X     .                ikey .eq. smg$k_trm_lowercase_r .or.
X     .                ikey .eq. smg$k_trm_uppercase_r ) then
X            call rename_directory( 20 )
X
X            else if ( code_type .eq. 3 .or.
X     .                ikey .eq. smg$k_trm_lowercase_m .or.
X     .                ikey .eq. smg$k_trm_uppercase_m ) then
X            call rename_directory( 30 )
X
X            else if ( code_type .eq. 4 .or.
X     .                ikey .eq. smg$k_trm_lowercase_d .or.
X     .                ikey .eq. smg$k_trm_uppercase_d ) then
X            call delete_directory( code )
X
X            else if ( code_type .eq. 5 .or.
X     .                ikey .eq. smg$k_trm_lowercase_p .or.
X     .                ikey .eq. smg$k_trm_uppercase_p ) then
X            call hardcopy( code )
X
X            else if ( code_type .eq. 6 .or.
X     .                ikey .eq. smg$k_trm_lowercase_s .or.
X     .                ikey .eq. smg$k_trm_uppercase_s ) then
X            call record_structure( .true. )
X
X            else if ( code_type .eq. 7 .or.
X     .                ikey .eq. smg$k_trm_lowercase_o .or.
X     .                ikey .eq. smg$k_trm_uppercase_o ) then
X            call change_options( code )
X
X            else if ( code_type .eq. 8 .or.
X     .                ikey .eq. smg$k_trm_pf2 .or.
X     .                ikey .eq. smg$k_trm_help .or.
X     .                ikey .eq. smg$k_trm_lowercase_h .or.
X     .                ikey .eq. smg$k_trm_uppercase_h ) then
X            call help( code )
X            end if
X
X         call smg$set_cursor_abs( window2, cur_line, cur_level*17+1 )
X
X      end do
X
X      call exit_swing
X      end
$ GoSub Convert_File
$ Exit