Google
 

Trailing-Edge - PDP-10 Archives - tops10and20_integ_tools_v9_3-aug-86 - tools/conbat/vag003.cbl
There are 5 other files named vag003.cbl in the archive. Click here to see a list.
IDENTIFICATION DIVISION.
*=======================
 
Program-Id.	VAG003.
 
Author. Daniel I Kazzaz
 
Date-Written.	30-Jan-85.
 
Date-Compiled.
 
Installation.	PAPER FREE SYSTEMS INC.
*-------------
*Program Title:
*-------------
*
*	System: VAXCON	DEC to VAX Conversion System
*	Module: VAG003	Command File Table Modifier
*
*
*-------------------
*Program Description:
*-------------------
*
*	VAG003 Sets up the tables for the conversion of command files
*	from the DEC-10/20 to the VAX.
*
*----------------------------
*Program Modification History:
*----------------------------
*	--Date--   Who	What
*
*----------------------------------------------------------------------
ENVIRONMENT DIVISION.
*====================

CONFIGURATION SECTION.
*---------------------

SOURCE-COMPUTER.	DECSYSTEM-10.
OBJECT-COMPUTER.	DECSYSTEM-10.


INPUT-OUTPUT SECTION.
*--------------------

FILE-CONTROL.

Select			Command-Table-FILE
	assign to	DSK
	recording mode	ASCII.

Select			Structure-Table-FILE
	assign to	DSK
	recording mode	ASCII.


select			Directory-Table-File
	assign to 	DSK
	recording mode	ASCII.

DATA DIVISION.
*=============

FILE SECTION.
*------------

fd			Command-Table-FILE
	value of id	Command-Table-FILE-ID.
 
01	Command-Table-RECORD		PIC  X(81).
 
fd			Structure-Table-FILE
	value of id	Structure-Table-FILE-ID.
 
01	Structure-Table-RECORD		PIC  X(21).
 
fd			Directory-Table-File
	value of id	Directory-Table-File-ID.

01	Directory-Table-RECORD			display-7.
	02 filler		Pic X(10).


WORKING-STORAGE SECTION.
*=======================
01	Command-Table-FILE-ID.
	05  Command-Table-File-Name	Pic  X(06) Value "T10COM".
	05  Command-Table-File-Ext	Pic  X(03) Value "TBL".

01	Structure-Table-FILE-ID.
	05  Structure-Table-File-Name	Pic  X(06) Value "MYSTRS".
	05  Structure-Table-File-Ext	Pic  X(03) Value "EXT".

01	Directory-Table-File-ID.
	05  Directory-Table-File-Name	Pic  X(06) Value "DIRECT".
	05  Directory-Table-File-Ext	Pic  X(03) Value "EXT".

*===============================================================
*	S Y M B O L    T A B L E S
*=============================================================

01	WS-COMMAND-TABLE.
    02  WS-COMMAND-TABLE-ENTRY	OCCURS 1111
				INDEXED BY WS-CMD-IDX
				ASCENDING KEY WS-COMMAND-NAME.
	05  WS-COMMAND-TBL-NAME	PIC X(10).
	05  WS-COMMAND-NAME		PIC X(10).
	05  WS-COMMAND-CHAR		REDEFINES
	    WS-COMMAND-NAME		PIC X(01)
				OCCURS 10.
	05  WS-COMMAND-FLAGS.
	    10	WS-COMMAND-NO-EQUIV		PIC 9(01).
	    10	WS-COMMAND-IGNORE		PIC 9(01).
	    10	WS-COMMAND-END-COM		PIC 9(01).
	    10	WS-COMMAND-SAME-FMT		PIC 9(01).
	    10	WS-COMMAND-FILE-NEXT	PIC 9(01).
	    10	WS-COMMAND-DATA-NEXT	PIC 9(01).
	05  WS-COMMAND-NXT-TBL	PIC X(10).
	05  WS-COMMAND-SKL-NAME	PIC X(10).
	05  WS-COMMAND-TOKEN-NAME	PIC X(05).
	05  WS-COMMAND-TOKEN-VALUE	PIC X(30).
 
*  Here are different copies of the above table
01  WS-COMMAND-WORK-AREA.
	05  WS-WORK-TBL-NAME	PIC X(10).
	05  WS-WORK-CMD-NAME		PIC X(10).
	05  WS-WORK-FLAGS.
	    10	WS-WORK-NO-EQUIV		PIC 9(01).
	    10	WS-WORK-IGNORE		PIC 9(01).
	    10	WS-WORK-END-COM		PIC 9(01).
	    10	WS-WORK-SAME-FMT		PIC 9(01).
	    10	WS-WORK-FILE-NEXT	PIC 9(01).
	    10	WS-WORK-DATA-NEXT	PIC 9(01).
	05  WS-WORK-NXT-TBL	PIC X(10).
	05  WS-WORK-SKL-NAME	PIC X(10).
	05  WS-WORK-TOKEN-NAME	PIC X(05).
	05  WS-WORK-TOKEN-VALUE	PIC X(30).


01	WS-Command-Table-Header		Display-7.
	05  Filler		Pic x(11) Value " Table Name".
	05  Filler		Pic X(12) Value "  Command".
	05  filler		Pic X(03) Value " Eq".
	05  Filler		Pic X(03) Value " Pa".
	05  Filler		Pic X(03) Value " En".
	05  filler		Pic x(03) Value " Sa".
	05  filler		Pic X(03) Value " Fl".
	05  filler		Pic X(03) Value " Da".
	05  filler		Pic X(12) Value " Next Table".
	05  filler		Pic x(12) Value " Skl Name ".
	05  filler		Pic x(07) Value "Tkn Nam".
	05  filler		Pic X(32) Value " Token Value ".


01  WS-DISP-COMMAND-ENTRY.
	05  FILLER		PIC X(1) VALUE SPACES.
	05  WS-DISP-TBL-NAME	PIC X(10).
	05  FILLER		PIC X(2) VALUE SPACES.
	05  WS-DISP-CMD-NAME		PIC X(10).
	05  FILLER		PIC X(2) VALUE SPACES.
	05  WS-DISP-FLAGS.
	    10	WS-DISP-NO-EQUIV		PIC 9(01).
	    10  FILLER			PIC X(2) VALUE SPACES.
	    10	WS-DISP-IGNORE		PIC 9(01).
	    10  FILLER			PIC X(2) VALUE SPACES.
	    10	WS-DISP-END-COM		PIC 9(01).
	    10  FILLER			PIC X(2) VALUE SPACES.
	    10	WS-DISP-SAME-FMT		PIC 9(01).
	    10  FILLER			PIC X(2) VALUE SPACES.
	    10	WS-DISP-FILE-NEXT	PIC 9(01).
	    10  FILLER			PIC X(2) VALUE SPACES.
	    10	WS-DISP-DATA-NEXT	PIC 9(01).
	    10  FILLER			PIC X(2) VALUE SPACES.
	05  WS-DISP-NXT-TBL	PIC X(10).
	05  FILLER		PIC X(2) VALUE SPACES.
	05  WS-DISP-SKL-NAME	PIC X(10).
	05  FILLER		PIC X(2) VALUE SPACES.
	05  WS-DISP-TOKEN-NAME	PIC X(05).
	05  FILLER		PIC X(2) VALUE SPACES.
	05  WS-DISP-TOKEN-VALUE	PIC X(30).


01	WS-NEW-COMMAND-TABLE.
    02  WS-NEW-COMMAND-TABLE-ENTRY	OCCURS 1111 TIMES.
	05  WS-NEW-TBL-NAME	PIC X(10).
	05  WS-NEW-CMD-NAME		PIC X(10).
	05  WS-NEW-FLAGS.
	    10	WS-NEW-NO-EQUIV		PIC 9(01).
	    10	WS-NEW-IGNORE		PIC 9(01).
	    10	WS-NEW-END-COM		PIC 9(01).
	    10	WS-NEW-SAME-FMT		PIC 9(01).
	    10	WS-NEW-FILE-NEXT	PIC 9(01).
	    10	WS-NEW-DATA-NEXT	PIC 9(01).
	05  WS-NEW-NXT-TBL	PIC X(10).
	05  WS-NEW-SKL-NAME	PIC X(10).
	05  WS-NEW-TOKEN-NAME	PIC X(05).
	05  WS-NEW-TOKEN-VALUE	PIC X(30).




*& TEMP AMT
01	WS-MAX-TBL		PIC S9(04) COMP	VALUE 1111.
01	WS-TABLE-END		Usage Index.
01	WS-TABLE-START		Usage Index.
01	WS-MAX-COMMAND		Usage Index.
01	WS-MAX-STRUCTURE	Usage Index.
01	WS-MAX-DIRECTORY	Usage Index.

01	End-of-file-flag	Pic 9(01) value 0.
	88 End-of-file		Value 1.


01 	WS-Valid-Response-Flag	Pic 9(01) value 0.
	88 Ws-Valid-Response	Value 1.


01	WS-Answer.
	02  WS-Answer-30	Pic X(30).
	88  WS-Answer-Spaces	Value Spaces.

	02  filler		Redefines WS-Answer-30.
	    05  WS-Answer-20	Pic X(20).
	    05  filler		Pic X(10).
	02  filler		Redefines WS-Answer-30.
	    05  WS-Answer-10	Pic  X(10).
	    05	filler		Pic  X(20).
	02  filler		Redefines WS-Answer-30.
	    05  WS-Answer-6	Pic  X(06).
	    05  filler		Pic  X(24).
	02  filler		Redefines WS-Answer-30.
	    05  WS-Answer-5	Pic  X(05).
	    05  filler		Pic  X(25).
	02  filler		Redefines WS-Answer-30.
	    05  WS-Answer-1	Pic  X(01).
	    88  WS-Help		Value "?".
	    05  filler		Pic  X(29).

01	WS-Dest-Idx		Usage Index.
01	WS-Index		Usage Index.
01	WS-Display-Index	Usage Index.
01	WS-Process-Status	Pic 9(01) Value 0.
	88 Updates-Done		Value 9.

01	Ws-Table-Type		Pic x(01) Value Space.
	88 WS-Exit-Table-Type	Value Space.
	88 WS-Table-Type-Valid	Value "C","D","S"," ".
	88 WS-Table-Type-Command Value "C".
	88 WS-Table-Type-Structure	Value "S".
	88 Ws-Table-Type-Directory	Value "D".

 
01	W-STRUCTURE-TABLE.
    02  WS-Structure-Table-Entry	OCCURS 111
				INDEXED BY W-STR-IDX
				ASCENDING KEY W-STR-OLD.
	05  W-STR-OLD		PIC  X(06).
	05  W-STR-NEW		PIC  X(15).
 
01	WS-Directory-Table.
	05  WS-Directory-Table-Entry	Occurs 111
					Indexed by WS-Dir-Idx.
	    10  filler			Pic x(10).


01	Ws-Table-Found-SW	Pic  9(01) Value 0.
	88  WS-Table-Found	Value 1.

01	Ws-Command-Found-SW	Pic  9(01) Value 0.
	88  WS-Command-Found	Value 1.

01	WS-Table-Done-SW	Pic  9(01) Value 0.
	88  WS-Table-Done	Value 1.

01	Ws-Valid-Action-SW	Pic 9(01) Value 0.
	88 Ws-Valid-Action	Value 1.


01	WS-Action		Pic  X(01).
	88  Ws-Action-Add	Value "A".
	88  WS-Action-Display	Value "V".
	88  WS-Action-Change	Value "C".
	88  WS-Action-Delete	Value "D".
	88  WS-Action-Type-Valid  Value " ", "A", "V", "C", "D".


01	WS-ACTION-EXIT-SW	PIC  9(01) VALUE 0.
	88 WS-Action-Exit	Value 1.

01	WS-ACTION-Done-SW	PIC  9(01) VALUE 0.
	88 WS-Action-Done	Value 1.

01	WS-Abort-SW		Pic  9(01)  Value 0.
	88 WS-Abort		Value 1.

01	WS-Validated-SW		Pic  9(01) Value 0.
	88  WS-Validated	Value 1.

01	WS-Y-N-SW		Pic  9(01) value 0.
	88  WS-Y-N		Value 1.

01	WS-Change-Done-Sw	Pic  9(01) Value 0.
	88  WS-Change-Done	Value 1.

01	WS-Change-Field-Name		Pic  X(01).
	88  WS-CHANGE-NO-EQUIV		VALUE "A".
	88  WS-CHANGE-IGNORE		VALUE "B".
	88  WS-CHANGE-END-COM		VALUE "C".
	88  WS-CHANGE-SAME-FMT		VALUE "D".
	88  WS-CHANGE-FILE-NEXT	VALUE "E".
	88  WS-CHANGE-DATA-NEXT	VALUE "F".
	88  WS-CHANGE-NXT-TBL	VALUE "G".
	88  WS-CHANGE-SKL-NAME	VALUE "H".
	88  WS-CHANGE-TOKEN-NAME	VALUE "I".
	88  WS-CHANGE-TOKEN-VALUE	VALUE "J".
	88  WS-CHANGE-VALID		VALUE
	"A","B","C","D","E","F","G","H","I","J".



Procedure Division.


1000-main.

	Perform			2000-initialize.
	Perform			2100-Do-Updates Until Updates-Done.
	Perform			2200-Clean-up.
	Stop Run.

2000-Initialize.
* This paragragh open files and reads in the tables.

	Open 			Input Command-Table-File.
*	Open			Input Structure-Table-File
*				      Directory-Table-File.
	Set WS-Index		To 1.
	Perform			2010-Read-Cmd-Table-File
				Until End-of-File.
*	Move   			0 to End-of-File-Flag.
*	Set WS-Index		To 1.
*	Perform			2020-Read-Str-Table-File
*				Until End-of-File.
*	Move   			0 to End-of-File-Flag.
*	Set WS-Index		To 1.
*	Perform			2030-Read-Dir-Table-File
*				Until End-of-File.
	Close 			Command-Table-File.
*	Close			 Structure-Table-File
*				Directory-Table-File.


2010-Read-Cmd-Table-File.
	Read Command-Table-File	Into WS-Command-Table-Entry(WS-Index)
				At End Move 1 to End-Of-File-Flag.
	If Not End-Of-File
	    Set WS-Index	Up By 1
	  Else
            Move WS-Index	To WS-Max-Command.


2020-Read-Str-Table-File.
	Read Structure-Table-File	Into WS-Structure-Table-Entry(WS-Index)
				At End Move 1 to End-Of-File-Flag.
	If Not End-Of-File
	    Set WS-Index	Up By 1
	  Else
            Move WS-Index	To WS-Max-Structure.


2030-Read-Dir-Table-File.
	Read Directory-Table-File	Into WS-Directory-Table-Entry(WS-Index)
				At End Move 1 to End-Of-File-Flag.
	If Not End-Of-File
	    Set WS-Index	Up By 1
	  Else
            Move WS-Index	To WS-Max-Directory.

2100-Do-Updates.
*This paragraph calls for the Table name(Command, Direc or Str)
*And then dispatchs to the appropriate routine.  The real work is 
*in the 3000- routines.

	Move 0			To WS-Valid-Response-Flag.
	Perform 		2110-Collect-Table-Type
				Until WS-Valid-Response.
	If  Ws-Exit-Table-Type
	    Move 9		To WS-Process-Status
	  Else
	    Perform		3000-Table-Dispatch.


2110-Collect-Table-Type.

	Display "Which Table do you wish to Update? " With no advancing.
	Accept	WS-Answer.
	If  WS-Help
	    Display "You have five valid responses to this question:"
	    Display " ? -- Types out this messeage"
	    Display " C -- Updates the Command Table"
	    Display " D -- Updates the Directories Table"
	    Display " S -- Updates the Structures Table"
	    Display " a return will exit the program."
	 Else
	    Move WS-Answer-1	to WS-Table-Type
	    If  Not WS-Table-Type-Valid
		Display " % Not a valid response - type ? for help"
	      Else 
		Move 1		to WS-Valid-Response-Flag.


2200-Clean-up.
*	This place opens the table file for output, performs the writes,
*	and closes the file.  This updates the files every time the program
* 	is run
	Open 			Output Command-Table-File.
*	Open			output Structure-Table-File
*				      Directory-Table-File.
	Set WS-Index		To 1.
	Perform			2210-Write-Cmd-Table-File
				Until WS-Index > WS-Max-Command.
*	Set WS-Index		To 1.
*	Perform			2220-Write-Str-Table-File
*				Until WS-Index > WS-Max-Structure.
*	Set WS-Index		To 1.
*	Perform			2230-Write-Dir-Table-File
*				Until WS-Index > WS-Max-Directory.
	Close 			Command-Table-File.
*	Close			 Structure-Table-File
*				Directory-Table-File.


2210-Write-Cmd-Table-File.
	Write Command-Table-Record
				From WS-Command-Table-Entry(WS-Index)
	    BEFORE ADVANCING 1.
	Set WS-Index		Up by 1.


2220-Write-Str-Table-File.
	Write Structure-Table-Record
				From WS-Structure-Table-Entry(WS-Index)
	    BEFORE ADVANCING 1.
	Set WS-Index		Up by 1.


2230-Write-Dir-Table-File.
	Write Directory-Table-Record
				From WS-Directory-Table-Entry(WS-Index)
	    BEFORE ADVANCING 1.
	Set WS-Index		Up by 1.


3000-Table-Dispatch.
	Move 0			To WS-Table-Done-SW.
	If  Ws-Table-Type-Command
	    Perform		3010-Update-Command-Table
				Until WS-Table-Done
	  Else
	    If  Ws-Table-Type-Structure
		Perform		4000-Update-Structure-Table
				Until WS-Table-done
	      Else
		If  WS-Table-Type-Directory
		    Perform	4500-Update-Directory-Table
				Until Ws-Table-Done
		  Else
		    Display "A table type was added, but not into"
		    Display "3000-Table-dispatch routine".

3010-Update-command-Table.
	Move 0			To WS-Table-Found-SW.
	Perform			3011-Collect-Cmd-Table-Name
				Until WS-Table-Found.
	If  WS-Work-Tbl-Name = Spaces
	    Move 1		to WS-Table-Done-SW
	  Else
	    Move 0		to WS-Valid-Action-SW
	    Move 0		To Ws-Action-Done-SW
	    Perform		3015-Do-Action Until
				Ws-Action-Done.

3011-Collect-Cmd-Table-Name.
	Move 0			To WS-Table-Found-SW.
	Set WS-Index		To 1.
	Display "Table Name > " with no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display "Enter the name of the command table.  The topmost"
	    Display "level (monitor commands) is simply 'MAIN'.  Each"
	    Display "command which needs a subsequent table is referenced"
	    Display "in the TOP level.  All subsequent commands (add, display,"
	    Display "change and delete) will operate on the level you specify."
	    Display " "
	    Display "Enter a return to proceed to another table or exit"
	  Else
	    Move  WS-Answer-10		To WS-Work-Tbl-Name
	    If  WS-Answer-Spaces
		Move 1			To WS-Table-Found-SW
	      Else
		set ws-table-start	To 1
		Perform			3012-Compare-Table Until
					WS-Table-Found or
					WS-Index > WS-Max-Command
		If  Not WS-Table-Found
		    Display "Table not present, do you wish to add it?"
		    Move 0		To WS-Validated-SW
		    Perform		3600-Validate
	 	    If  WS-Validated
			Move 1		To WS-Table-Found-SW
			Move WS-Max-Command	
					To WS-Table-Start,
					   WS-Table-End,
					   WS-Cmd-Idx
			Subtract 1	From WS-Table-End
			Move "A"	To WS-Action
			Perform		3040-Add-Command.

3012-Compare-Table.
	If  WS-Work-Tbl-Name = WS-Command-Tbl-Name(WS-Index)
	    move 1		To WS-Table-Found-SW
	    Move WS-Index	To Ws-Table-Start
	    Perform		3013-Find-end Until
				WS-Index > WS-Max-Command
				or WS-Work-Tbl-Name Not = 
				   WS-Command-Tbl-Name(WS-Index)
	    Set WS-Table-End	Down by 1
	  Else
	    Set			WS-Index up by 1.


3013-Find-End.
	SET WS-Index		Up by 1.
	Move WS-Index		To WS-Table-End.


3015-Do-Action.
	Move 0			To WS-Valid-Action-SW.
	Perform			8200-Collect-Action
				Until  WS-Valid-Action.
	If  WS-Action Not = Spaces
	    Perform		3020-Dispatch-Action
	  Else
	    Move 1		To WS-Action-Done-SW.


3020-Dispatch-Action.
	Move 0			to WS-Action-Exit-SW.
	If  WS-Action-Display
	    Perform		3030-Display-Command
	  Else
	If  WS-Action-Add
	    Perform		3040-Add-Command
				Until  WS-Action-Exit
	  Else
	If  WS-Action-Change
	    Perform		3200-Change-Command
				Until  WS-Action-Exit
	   Else
	If  WS-Action-Delete
	    Perform		3300-Delete-Action
				Until  WS-Action-Exit.

3030-Display-Command.
* Display always display's an entire Command Table
* It relies on Table Start and Table end to be initialized
* by the table search routine.
	Display			WS-Command-Table-Header.
	Perform			8100-Display-Command-Line
				Varying WS-Display-Index
				From WS-Table-Start
				By 1
				Until WS-Display-Index > WS-Table-End.

3040-Add-Command.
* This routine asks for command name, verifies that it does not
* exist, then asks for the fields.  An "@" indicates an abort.
	Move 0			To Ws-Command-Found-SW.
	Perform			3500-Get-Command-Name.
	If  WS-Work-Cmd-Name = Spaces
	    Move 1		to WS-Action-Exit-SW
	  Else
	    Perform		3550-Search-For-Command
	    If  WS-Command-Found
		Display " This command already exists, either"
		Display " enter a new name or enter change to"
		Display " alter the current entry"
	      Else
		Perform		3041-Collect-Fields
		If  Not WS-Abort
		    Perform		3800-Move-Table.

3041-Collect-Fields.
	Move 0			To WS-Abort-SW.
	Move 0			To WS-Valid-Response-Flag.
	Perform			3045-Collect-No-Equiv
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3047-Collect-Ignore
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3049-Collect-End-Com
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3051-Collect-Same-Fmt
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3053-Collect-Data-Next
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3055-Collect-File-Next
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3057-Collect-Nxt-Tbl
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3059-Collect-Skl-Name
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3061-Collect-Token-Name
				Until WS-Valid-Response.
	If Not WS-Abort
	    Move 0		To WS-Valid-Response-Flag
	    Perform		3063-Collect-Token-Value
				Until WS-Valid-Response.


3045-Collect-No-Equiv.
	Display "No Equiv Flag > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display "Enter a 1 if this command has no equivalent on the VAX."
	    Display "Enter a 0 or space or return to process it."
	  Else
	    If  WS-Answer = "@"
		Move 1		To WS-Valid-Response-Flag
		Move 1		To WS-Abort-SW
	      Else
		If  WS-Answer = "1" or "0" or " "
		    Move 1	To WS-Valid-Response-Flag
		    Move WS-Answer-1
				To WS-Work-No-Equiv
		  Else
		    Display " % Invalid response type ? for help".


3047-Collect-Ignore.
	Display "Partial Match > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display "Enter a 1 to allow a partial match on this keyword."
	    Display "Enter a 0 or space or return to force an exact match."
	  Else
	    If  WS-Answer = "@"
		Move 1		To WS-Valid-Response-Flag
		Move 1		To WS-Abort-SW
	      Else
		If  WS-Answer = "1" or "0" or " "
		    Move 1	To WS-Valid-Response-Flag
		    Move WS-Answer-1
				To WS-Work-Ignore
		  Else
		    Display " % Invalid response type ? for help".


3049-Collect-End-Com.
	Display "End of Command Flag > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display "Enter a 1 if the command can end at this point."
	    Display "Enter a 0 or space or return if not."
	  Else
	    If  WS-Answer = "@"
		Move 1		To WS-Valid-Response-Flag
		Move 1		To WS-Abort-SW
	      Else
		If  WS-Answer = "1" or "0" or " "
		    Move 1	To WS-Valid-Response-Flag
		    Move WS-Answer-1
				To WS-Work-End-Com
		  Else
		    Display " % Invalid response type ? for help".


3051-Collect-Same-Fmt.
	Display "Search Table Flag > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display "Enter a 1 if terminator forces a search of this table."
	    Display "Enter a 0 or space or return if not."
	  Else
	    If  WS-Answer = "@"
		Move 1		To WS-Valid-Response-Flag
		Move 1		To WS-Abort-SW
	      Else
		If  WS-Answer = "2" or "1" or "0" or " "
		    Move 1	To WS-Valid-Response-Flag
		    Move WS-Answer-1
				To WS-Work-Same-Fmt
		  Else
		    Display " % Invalid response type ? for help".


3053-Collect-Data-Next.
	Display "Data Next Flag > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Enter a 0, space or return if no data is expected."
	    Display " Enter a 1 if Data is definitely expected next."
	    Display " Enter a 2 if Data may or may not follow."
	  Else
	    If  WS-Answer = "@"
		Move 1		To WS-Valid-Response-Flag
		Move 1		To WS-Abort-SW
	      Else
		If  WS-Answer = "2" or "1" or "0" or " "
		    Move 1	To WS-Valid-Response-Flag
		    Move WS-Answer-1
				To WS-Work-Data-Next
		  Else
		    Display " % Invalid response type ? for help".


3055-Collect-File-Next.
	Display "File Next Flag > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Enter a 0, space or return if no file is expected."
	    Display " Enter a 1 if a file name is definitely expected next."
	    Display " Enter a 2 if a file name may or may not follow."
	  Else
	    If  WS-Answer = "@"
		Move 1		To WS-Valid-Response-Flag
		Move 1		To WS-Abort-SW
	      Else
		If  WS-Answer = "2" or "1" or "0" or " "
		    Move 1	To WS-Valid-Response-Flag
		    Move WS-Answer-1
				To WS-Work-File-Next
		  Else
		    Display " % Invalid response type ? for help".


3057-Collect-Nxt-Tbl.
	Display "Next Table > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Enter the next table (state) to branch to"
	    Display " when finished with this command."
	  Else
	    Move 1		To WS-Valid-Response-Flag
	    Move WS-Answer-10	To Ws-Work-Nxt-Tbl
	    If  WS-Answer = "@"
		Move 1		To WS-Abort-SW.


3059-Collect-Skl-Name.
	Display "Skeleton Command Name > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Enter the skeleton command name for this"
	    Display " command."
	  Else
	    Move 1		To WS-Valid-Response-Flag
	    Move WS-Answer-10	To Ws-Work-Skl-Name
	    If  WS-Answer = "@"
		Move 1		To WS-Abort-SW.


3061-Collect-Token-Name.
	Display "Token Name > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Enter the Token name for this portion of the"
	    Display " command."
	  Else
	    Move 1		To WS-Valid-Response-Flag
	    Move WS-Answer-5	To Ws-Work-Token-Name
	    If  WS-Answer = "@"
		Move 1		To WS-Abort-SW.


3063-Collect-Token-Value.
	Display "Token Value > " With no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Enter the Token Value for this portion of the"
	    Display " command."
	  Else
	    Move 1		To WS-Valid-Response-Flag
	    Move WS-Answer-30	To Ws-Work-Token-Value
	    If  WS-Answer = "@"
		Move 1		To WS-Abort-SW.


3200-Change-Command.
	Move 0			To Ws-Command-Found-SW.
	Perform			3500-Get-Command-Name.
	If  WS-Work-Cmd-Name = Spaces
	    Move 1		to WS-Action-Exit-SW
	  Else
	    Perform		3550-Search-For-Command
	    If  Not WS-Command-found
		Display "% This command not found please retype"
		Display "  or hit return to exit"
	      Else
		Display 	WS-Command-Table-Header
* the following also moves the command to the work area
		Move WS-Cmd-Idx	To WS-Display-Index
		Perform		8100-Display-Command-Line
		Move 0		to WS-Change-Done-Sw
		Move 0		To WS-Abort-SW
		Perform		3250-Collect-and-Do-Change
				Until WS-Change-Done
		If  Not Ws-Abort
		    Perform	8101-Move-and-Display
		    Move 0 	To WS-Validated-SW
		    Perform	3600-Validate
		    If  WS-Validated
			Move WS-Command-Work-Area
				To WS-Command-Table-Entry(WS-Cmd-Idx).


3250-Collect-and-Do-Change.
	Display "Field to change > " with no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display "Enter one of the following:"
	    Display " A - No Equivalent Flag"
	    Display " B - Partial Match "
	    Display " C - End of Command Flag "
	    Display " D - Search Table Flag "
	    Display " E - File Next Flag "
	    Display " F - Data Next Flag "
	    Display " G - Next Table Name "
	    Display " H - Skeleton Command Name "
	    Display " I - Token Name "
	    Display " J - Token Value "
	    Display " @ - to abort changes "
	    Display " ? - to print this message "
	    Display " space or return when done with changes "
	  Else
	    Move WS-Answer-1	to WS-Change-Field-Name
	    If  WS-Answer-1 = Spaces
		Move 1		To WS-Change-Done-SW
	      Else
	    If  WS-Answer-1 = "@"
		Move 1		To WS-Abort-SW
				     WS-Change-Done-SW
	      Else
		If WS-Change-Valid
		    Perform		3260-Dispatch-Change.


3260-Dispatch-Change.
	Move 0			To WS-Abort-SW.
	Move 0			To WS-Valid-Response-Flag.
	If  WS-Change-No-Equiv
	    Perform			3045-Collect-No-Equiv
				Until WS-Valid-Response.
	If  WS-Change-Ignore
	    Perform		3047-Collect-Ignore
				Until WS-Valid-Response.
	If  WS-Change-End-Com
	    Perform		3049-Collect-End-Com
				Until WS-Valid-Response.
	If  WS-Change-Same-Fmt
	    Perform		3051-Collect-Same-Fmt
				Until WS-Valid-Response.
	If  WS-Change-Data-Next
	    Perform		3053-Collect-Data-Next
				Until WS-Valid-Response.
	If  WS-Change-File-Next
	    Perform		3055-Collect-File-Next
				Until WS-Valid-Response.
	If  WS-Change-Nxt-Tbl
	    Perform		3057-Collect-Nxt-Tbl
				Until WS-Valid-Response.
	If  WS-Change-Skl-Name
	    Perform		3059-Collect-Skl-Name
				Until WS-Valid-Response.
	If  WS-Change-Token-Name
	    Perform		3061-Collect-Token-Name
				Until WS-Valid-Response.
	If  WS-Change-Token-Value
	    Perform		3063-Collect-Token-Value
				Until WS-Valid-Response.


3300-Delete-Action.
	Move 0			To Ws-Command-Found-SW.
	Perform			3500-Get-Command-Name.
	If  WS-Work-Cmd-Name = Spaces
	    Move 1		to WS-Action-Exit-SW
	  Else
	    Perform		3550-Search-For-Command
	    If  Not WS-Command-found
		Display "% This command not found please retype"
		Display "  or hit return to exit"
	      Else
		Display 	WS-Command-Table-Header
* the following also moves the command to the work area
		Move WS-Cmd-Idx	To WS-Display-Index
		Perform		8100-Display-Command-Line
		Move 0		to WS-Change-Done-Sw
		Move 0		To WS-Abort-SW
		Move 0	 	To WS-Validated-SW
		Perform		3600-Validate
		If  WS-Validated
		    Perform	3800-Move-Table.


3500-Get-Command-Name.
	Display "Enter Command Name > " with no advancing.
	Accept  WS-Answer.
	If  Ws-Help
	    Display  "This is the command (or portion thereof)"
	    Display  "which is to be processed at this point"
	    Display  "All options available at this point should"
	    Display  "be visible during the display command."
	  Else
	    Move WS-Answer-10	to WS-Work-Cmd-Name.

3550-Search-For-Command.
	Perform			3555-Search-Table
				Varying WS-Cmd-Idx from WS-Table-Start
				By 1 Until
				WS-Cmd-Idx > WS-Table-End
				or
				WS-Work-Cmd-Name < WS-Command-Name(WS-Cmd-Idx)
				or
				WS-Work-Cmd-Name = WS-Command-Name(WS-Cmd-Idx).
	If WS-Work-Cmd-Name = WS-Command-Name(WS-Cmd-Idx)
	   Move 1		to WS-Command-Found-SW.

3555-Search-Table.
	If WS-Work-Cmd-Name = WS-Command-Name(WS-Cmd-Idx)
	   Move 1		to WS-Command-Found-SW.


3600-Validate.
	Move 0			to WS-Y-N-SW.
	Perform			3610-Get-Y-N Until WS-Y-N.

3610-Get-Y-N.
	Display "Is this correct (Y or N) ? " with no advancing.
	Accept WS-Answer.
	If  WS-Help
	    Display " Type Y to make change effective"
	    Display "      N to abort change  "
	    Display "      ? to get this message"
	  Else
	    If  WS-Answer-1 Not = "Y" and WS-Answer-1 Not = "N"
		Display "% Only Y or N are allowed, ? will "
		Display "  display a short help message"
	      Else
		Move 1		To WS-Y-N-SW
	   	If  Ws-Answer-1 = "Y"
		    Move 1	To WS-Validated-SW.


3800-Move-Table.
	set ws-dest-idx		To 1.
	Perform			3850-Move-Lines Varying Ws-Index From 1
				by 1 until WS-Index = WS-Cmd-Idx.
	If  Ws-Action-Add
	    Move WS-COMMAND-WORK-AREA to
				WS-New-Command-Table-Entry(WS-Cmd-Idx)
	    Add 1		to WS-Dest-Idx
	    Add 1		to WS-Table-End
	    Add 1		to WS-Max-Command
	  Else
	    If  WS-Action-Delete
		Subtract 1	From WS-Max-Command
		Subtract 1	From WS-Table-End
		Add 1		To WS-Cmd-Idx.
	Perform 		3850-Move-Lines Varying
				WS-Index from WS-Cmd-IDX by 1
				Until WS-Dest-Idx > WS-Max-Command.
	Move WS-New-Command-Table
				To WS-Command-Table.

3850-Move-Lines.
	Move WS-Command-Table-Entry(WS-Index) 
				To WS-New-Command-Table-entry(WS-Dest-Idx).
	SEt WS-Dest-Idx		Up by 1.


4000-Update-Structure-Table.
*Dummy paragraph - For now.
	Move 1			to Ws-Table-Done-SW.


4500-Update-Directory-Table.
*Dummy paragraph - For now.
	Move 1			to Ws-Table-Done-SW.


8100-Display-Command-Line.
	MOve WS-Command-Table-Entry(WS-Display-Index)
				To WS-Command-Work-Area.
	Perform			8101-Move-and-Display.

8101-Move-And-Display.
	Move WS-Work-Tbl-Name		To WS-Disp-Tbl-Name.
	Move WS-Work-Cmd-Name		To WS-Disp-Cmd-Name.
	Move WS-Work-No-Equiv		To WS-Disp-No-Equiv.
	Move WS-Work-Ignore		To WS-Disp-Ignore.
	Move WS-Work-End-Com		To WS-Disp-End-Com.
	Move WS-Work-Same-Fmt		To WS-Disp-Same-Fmt.
	Move WS-Work-File-Next		To WS-Disp-File-Next.
	Move WS-Work-Data-Next		To WS-Disp-Data-Next.
	Move Ws-Work-Nxt-Tbl		To WS-Disp-Nxt-Tbl.
	Move Ws-Work-Skl-Name		To WS-Disp-Skl-Name.
	Move Ws-Work-Token-Name		To WS-Disp-Token-Name.
	Move Ws-Work-Token-Value	To WS-Disp-Token-Value.
	Display				WS-Disp-Command-Entry.


8200-Collect-Action.
	Display "Action Type > " With No Advancing.
	Accept WS-answer.
	If  Ws-Help
	    Display "Enter one of the following:"
	    Display "  A - to add a new entry "
	    Display "  V - to view or display an entry "
	    Display "  C - to change an entry "
	    Display "  D - to delete (or remove) an entry"
	    Display "  ? - to give you this message"
	    Display "  space or return to exit "
	  Else
	    Move WS-Answer-1 	To WS-Action
	    If  WS-Action-Type-Valid
		Move 1		To Ws-Valid-Action-SW
	      Else
		Display "% Invalid option type ? for help".