Trailing-Edge
-
PDP-10 Archives
-
FORTRAN-10_Alpha_31-jul-86
-
revhst.mac
There are 24 other files named revhst.mac in the archive. Click here to see a list.
TITLE REVHST 11(4543) Revision History for the FORTRAN compiler
SUBTTL Authors: DCE/TFV/EGM/SRM/EDS/CKS/AHM/CDM/RVM/PLB/TJK/AlB/MEM/JB 9-Jul-86
;Previous Authors (before V6):
; DONALD LEWINE/DAL/FI/HPW/DBT/NEA/MD/JNT/DCE/SJW/JNG/RDH/TFV/EGM
;COPYRIGHT (c) DIGITAL EQUIPMENT CORPORATION 1981, 1986
;ALL RIGHTS RESERVED.
;
;THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY BE USED AND COPIED
;ONLY IN ACCORDANCE WITH THE TERMS OF SUCH LICENSE AND WITH THE
;INCLUSION OF THE ABOVE COPYRIGHT NOTICE. THIS SOFTWARE OR ANY OTHER
;COPIES THEREOF MAY NOT BE PROVIDED OR OTHERWISE MADE AVAILABLE TO ANY
;OTHER PERSON. NO TITLE TO AND OWNERSHIP OF THE SOFTWARE IS HEREBY
;TRANSFERRED.
;
;THE INFORMATION IN THIS SOFTWARE IS SUBJECT TO CHANGE WITHOUT NOTICE
;AND SHOULD NOT BE CONSTRUED AS A COMMITMENT BY DIGITAL EQUIPMENT
;CORPORATION.
;
;DIGITAL ASSUMES NO RESPONSIBILITY FOR THE USE OR RELIABILITY OF ITS
;SOFTWARE ON EQUIPMENT WHICH IS NOT SUPPLIED BY DIGITAL.
TWOSEG
Comment \
***** Begin Revision History *****
124 ----- ADDED MAIN ENTRY SYMBOL MRP0 FOR SINGLE SEGMENT COMPILER
/HPW
125 ----- ADDED BUGOUT COMPLIER DIAGNOSTIC SWITCH /DBT
126 ----- FIXED ERROR TRAP TO CLEAR FIRST PART DONE
127 ----- CHANGED SIZE OF POOL
130 ----- MOVE APR TRAP INITIALIZATION TO BE RESET AFTER
EACH PROGRAM
131 ----- CHANGED BIT POSITION OF EOCS BIT IN FLAG REGISTER
132 ----- PUT BOUNDS SWITCH BACK IN
133 ----- CHANGE NXTFIL TO A SUBROUTINE WHICH WILL OPEN THE INPUT
FILE AS WELL AS BUILD THE OPEN BLOCK. PHAZ1 CAN THEN CALL PHAZCO
AND THEN NXTFIL SO THAT THE "+" COMPIL CONSTRUCTION
WILL WORK
134 ----- FIX ABSENT SPEC (PRESENT SWITCH)
BEING TREATED AS PRESENT SPEC. E.G. /SWT,X=X
TREATED AS *.*/SWT,X=X
135 ----- CATCH THE OCCURRENCE OF "=" COMMAND LINE
IE. NO INPUT FILES AT ALL
136 ----- CALCULATE THE MAXIMUM CORE REQUIRED FOR THE LIST
OF INPUT FILES AND STORE IN BGSTBF. PHAZ1 WILL RESERVE
THIS AMMOUNT OF CORE WHEN THE FIRST FILE IS OPENED
137 ----- PUT ERROR MESSAGES IN NEW FORMAT
138 ----- PUT IN FTTENX SUPPORT
***** Begin Version 4A *****
230 DRIVER(14) ----- ALLOCATE VARIABLE DIMENSIONS PASSED
ACT1(99) ----- AS ARGUMENTS.
231 ERROUT(32) ----- CHANGE WARNING 77 (DO INDEX)
232 ACT1(100) ----- FIX PROCESSING OF RECORD NUMBER IN BLDUNIT
233 PEEPOP(71) ----- FIX PEEPOP OF JUMP INSTRUCTION
234 PNROPT(144) 14167 FIX PROPAGATION OF LIBRARY FUNCTION
CALLS WITH CONSTANT ARGUMENT.
235 STA3(56) ----- NAMELIST PROBLEMS
ASHELP(3) 1-ITEMS NOT ALLOWED IN COMMON
ACT1(101) 2-SOMETIMES NOT ALLOCATED
3-NOT CREFED PROPERLY
236 OUTMOD(63) 14654 EQUIVALENCE PROBLEM
237 REGAL2(127) ----- REGISTER ALLOCATION FAILS
240 PH3G(229) 14569 REGISTER ALLOCATION PROBLEM
241 OUTMOD(64) ----- FIX HISEG BLOCK FOR BIG LOW SEG
242 CODETA(1) 15010 ALLOW CONTINUE AS OBJECT OF
SKSTMN(92) A LOGICAL IF STATEMENT.
243 GCMNSB(67) 14916 FIX OPTIMIZER (INT COMP ERROR)
244 GCMNSB(68) 14940 FIX OPTIMIZER (FINDTHESPOT TO MOVE
COMMON EXPRESSIONS).
245 PEEPOP(72) 15039 CORRECT MOVEMENT OF JRST ADDRESS TO INCLUDE
THE INDEX AND INDIRECT BITS.
246 PH3G(230) 15209 FORCE PRELOADS ON BRANCHES IN LOOPS
247 LISTOU(54) 15349 CHANGE FORMAT LABEL REFERENCES TO P (FROM F)
250 REGAL2(128) 15356 DON'T ALLOCATE REG WHEN ALCRETREGFLG ON
251 PEEPOP(73) 15652 DON'T OPT OUT LABELED INDIRECT JRST
252 DEFPT(116) 14967 CHECK NODES FOR FUNNY OPRCLS IN SELECTIT
253 PEEPOP(74) 15425 DON'T OPT OUT MOVE FOLLOWING PUSHJ OR DIVIDE
OF AC-1
254 STREGA(202) 15425 FORGET WHAT WAS IN 0 WHEN BOOLEAN FUNCTIONS ALLOCATE
THE RETURN VALUE TO 0
255 STA3(57) 15432 CHECK THE DO LOOP TERMINATION LABEL FOR
BEING ON THE DO STATEMENT ITSELF.
256 CGDO(134) 15493 DON'T COUNT ENTRY LABELS FOR STATEMENT FUNCTIONS
257 PEEPOP(75) 15511 ELIMINATE REDUNDANT ADDI SUBI PAIRS
260 SKSTMN(93) ----- ADD DOT FOR MATERILIZING INDEX AROUND FUNCTION CALLS
261 STREGA(203) 15772 WHEN COMPILING WITH /DEBUG:LABELS, DO NOT
PEEPOP(76) OPTIMIZE REGISTER USAGE BETWEEN
TABLES(154) STATEMENTS
262 COMMAN 15710 CORRECT LOOPS ON ENTER FAILURES
263 PHA2(108) 15865 FIX STACK VALUE SAVED
264 OPGNTA(119) 15974 FIX COMPLEX DIVIDE TO MEMORY ON KI
265 ACT1(102) 15946 ADD WARNING FOR MULTIPLY INITIALIZED
ERROUT(33) VARIABLES IN DATA STATEMENTS
ASHELP(4)
266 PH3G(231) 15952 FIX AN OPTIMIZER MOVEMENT BUG
267 REGAL2(129) ----- FIX SIDE EFFECT OF 250 IN RELATIONALS
270 STREGA(204) 16013 CLEAR REGSTATE FOR VARIABLES IN INPUT NAMELIST
271 COMMAN ----- CHANGE COMMAN TO SEARCH C AND SCNMAC
272 ACT1(103) ----- CHANGE 265 TO NOT CHECK ARRAYS
273 DATAST(43) 16361 HANDLE NEGATIVE DIMENSIONS RIGHT IN DATA STATEMENTS
274 REGAL2(130) 16050 ALLOCATE SAVES FOR 0-1 IN FUNCTION CALLS
AFTER ALLOCATING UNDER CALL
275 CNSTCM(65) ----- CHECK FOR UNDERFLOW RIGHT
276 TSTR(45) ----- REDUCE NEGATIVE MULTIPLICATIONS CORRECTLY
277 PH3G(232) 16112 FIX FLIPCODES TO CALL LEAFLOOKER WITH THE
REGS WE REALLY WANT SUBSTITUTED
300 STREGA(205) ----- FIX 270
301 CMPLEX(127) 16154 REMEMBER THAT FUNCTION CALLS CLOBBER 0 AND 1
STREGA(206) SO DON'T USE PROLOG VALUES IN THEM
302 REGAL2(131) 16181 CATCH ALL CASES OF NOT REMEMBERING REG CONTENTS FOR
BOOLEAN EXPRESSIONS WHICH MAY NOT BE COMPLETELY EXECUTED
303 DRIVER(15) 16369 CATCH ALL CASES OF DIMENSIONED VARIABLES
OCCURRING WITHOUT INDICES
304 REGAL2(132) 16441 CLOBBER BOTH REGISTER STATES ON A DOUBLE
TO SINGLE TYPE CONVERSION
305 PEEPOP(77) 16518 FIX PEEPOP TO CHECK FOR INDEXING WHEN ELIMINATING
REDUNDANT MOVE FROM MOVEM-XXXX-MOVE
306 CGSTMN(124) 16156 FIX CALL/OPEN TO DO FORMAL ARRAYS INDIRECTLY
307 DRIVER(15) 16611 CHANGE ORDER OF CLEANUP TO FIX PYROTECHNICS
310 STREGA(207) 16602 CHANGE ORDER OF OPEN/CLOSE REGISTER ALLOCATION
311 STREGA(208) 16665 ALLOCATE IOLIST REGS ONLY FOR NON-DATA ITEMS
312 GNRCFN(31) 16668 CHECK MIN AND MAX FUNCTIONS FOR LESS THAN 2 ARGUMENTS
313 STA1(62) 16666 HANDLE DIALOG W/O = RIGHT
314 DATAST(44) QAR FIX DATA STATEMENT DO LOOPS OF - NUMBERS
315 DEFPT(117) 16667 FIX ARRAYREFS WITH CONST SS DEFINITION POINT
316 PH3G(233) QAR FIX 277 RIGHT
317 LISTOU(55) QAR FIX 247 RIGHT
***** Begin Version 4B ***** 26-Aug-75
320 STA2(41) 16787 CATCH COMMON /X/A(5)B(5) AS ERROR
321 TSTR(46) 17005 SCAN FOR INDUCTION VARIABLE IN OPEN/CLOSE WHEN /OPT
322 IOPT(48) 16688 CHECK FOR DISJOINT IOLISTS BEFORE COLLAPSING
323 CGDO(135) 16729 CHANGE NAME OF TEMPS USED TO SAVE REGS
DOALC(106) IN FUNCTION PRO/EPI-LOGUE FROM .XXXNN
TO .A00NN TO AVOID CONFLICT.
324 STA3(58) 16750 CLEAN UP SYMBOL TABLE ENTRIES AFTER
BAD STATEMENT FUNCTION.
325 ACT0(52) 17044 CHECK FOR OVERFLOW OF STK CAUSED BY LONG
ARGUMENT LISTS, AND REMEDY SITUATION.
326 REGAL2(133) 17086 FIX REGISTER TARGETING FOR ASSIGNMENT STATEMENTS
WITH AND/OR NODES AND FUNCTION CALLS.
327 GRAPH(117) 16688 PREVENT OPTIMIZER FROM DYING ON
PROGRAMS WITH POTENTIALLY INFINITE LOOPS
330 GRAPH(118) 17150 ENSURE THAT THE OPTIMIZER DOES NOT
CONSIDER ENTRY STATEMENTS TO BE INACCESSIBLE
331 P2S2(51) 17091 FIX PROPAGATION OF NEGATION FOR SPECIAL
OPERATOR: RAISE TO AN ODD CONSTANT INTEGER
POWER CANNOT ABSORB A NEGATE FROM BELOW.
332 DOALC(107) 17045 FIX ASSIGN STATEMENTS WITHIN DO LOOPS
LEAFLOOKER(234)
333 GRAPH(119) 17045 FIX UP CODE GENERATED FOR ASSIGNED GO TO
STATEMENTS WITHIN DO LOOPS.
334 F72BNF.SYN 17420 CORRECT FORMAT OF DO STATEMENT (ADD LINEND)
335 INOUT(36) 17377 FIX FATLERR SO THAT IT DOES NOT DESTROY
THE CONTENT OF NAME FOR LEXICA.
336 STA0(46) 17259 CHECK FOR I/O LIST WITH NAMELIST
ERROUT(34) DIRECTED I/O
337 OUTMOD(65) 17305 ROUND UP IMMEDIATE REAL CONSTANTS
CGEXPR(71) BEFORE LISTING THEM
340 GCMNSB(69) 16989 DO NOT ALLOW CALL TO MATCHER TO
CHANGE VALUE OF PHI - OPTIMIZER BUG
341 REGAL2(134) 17770 FIX REGISTER ALLOCATION FOR EXPONENTIATION
INSIDE FUNCTION
342 LISTNG(10) 17876 MAKE LONG UNCLASSIFIABLE STATEMENTS WORK
LEXICA(14) PROPERLY - SEVERAL MINOR PATCHES
343 DRIVER(17) 17636 FIX END OF STATEMENT PROCESSING
SO THAT THE LINE NUMBER IS CORRECT.
344 CMPLEX(128) 17768 FIX PROPAGATION OF FNCALL FLAG
TO A NEG/NOT NODE.
345 P2S2(52) 17554 FIX COMMON SUBS INVOLVING EXPONENTIATION
TO EVEN POWERS SOMETHING WITH A NEG FLAG
346 TSTR(47) 17928 PASS OUT RETURN INFORMATION TO OUTER DO LOOPS
347 PH3G(235) 17545 IN GLOBAL REGISTER ALLOCATION, PREVENT
BAD PRELOADS CAUSED BY LOGICAL IF'S.
350 PH3G(236) 17545 COMMON SUBS MUST ALSO CAUSE PRELOADS
OF REGISTERS ON OCCASION - FIX THIS.
351 LISTNG(11) FIX EDIT 342 PROPERLY
352 PH3G(237) 18007 FIX EDIT 266 FOR CASE WITH ONE MATERIALIZATION
353 PH3G(238) 18004 FIX TWO CALLS GENERATING BAD CODE
354 TSTR(48) 18015 BAD CODE INVOLVING REDUCTION IN STRENGTH
355 SRCA(49) 18132 CORE MANAGEMENT INSUFFICIENT FOR LARGE
DATA STATEMENT
356 LISTOU(56) 18105 MAKE MAIN. GLOBAL SYMBOL FOR MAIN PROGS.
357 COMMAN 18191 FIX OPEN ERROR REPORTING
360 CGDO(136) 18243 FIX RETURN STMNT AT END OF DO LOOP
361 GRAPH(120) 18451 FIX GO TO END OF DO LOOP
362 LEXSUP(8) 18245 FIX UP ARGUMENT BLOCK TYPES FOR
GLOBAL(75) LOGICAL AND OCTAL AND DOUBLE OCTAL CONSTANTS
363 STREGA(209) 18269 CHECK A1NOTFLG BEFORE REMEMBERING REG CONTENTS
364 OUTMOD(66) 18251 CORRECT EQUIVALENCE PROCESSING
365 LEXICA(15) 18857 TAKE CARE OF FORM FEEDS BETWEEN ROUTINES
366 LEXSUP(9) 18210 SAVLINE CANNOT CLOBBER NAME
LEXICA(16) X=.123EQ.A AND X=1.1HABC ARE ILLEGAL
367 CGSTMN(125) 18239 WRITE(U) GENERATES WRONG CODE
370 GCMNSB(70) 17938 REMOVE [244] REAL FIX IS IN REDUCE (TSTR)
TSTR(49) FIX CODE MOTION FOR .R VARIABLES
371 COMSUB(255) 18471 FIX CSE FOR STRAIGHT CASE IN MATCHER
372 GRAPH(121) 18314 FIX ASSIGN GO TO INSIDE LOOPS
373 REGAL2(135) 18242 CORRECT REGISTER ALLOCATION FOR LARGE
ASSIGNMENT STATEMENTS
374 GRAPH(122) ----- FIX MIS-SPELLED MACRO NAME
375 PNROPT(145) 18450 USE .O INSTEAD OF .R FOR DP TEMPORARY
376 CGWRIT(126) 18398 FIX WRITE STMNT WITH DEBUG SET
377 REGAL2(136) 18476 FIX REG ALLOCATION FOR COS(X)*A(I)
400 PH3G(239) 18704 FIX LOGICAL IF BEFORE NESTED LOOPS
401 GCMNSB(71) 17813 FIX A(I)=B(I)+B(I)+1.0
***** Begin Version 5 ***** 7-May-76
ACT1 (104) ARRXPN (52) CANNON (25) COMSUB (256V)
GCMNSB (72) OPTMAC PH3G (240V) PHA2 (109)
PNROPT (146) TSTR (50) VER5 (1)
402 STA2(42) 18917 RESTORE FLGREG PROPERLY AFTER INCLUDE
403 STREGA(210) 18961 BAD REG ALLOCATION FOR I=I/J
404 GOPTIM(53) 18869 MAKE ASSOCIATE VARIABLE LIST CORRECTLY,
PH3G(240) AND DON'T LET THEM LIVE IN REGISTERS
405 COMSUB(256) 18967 FIX A(P(I)) IN IOLIST
406 IOPT(49) 18978 FIX CHAR(K(I,J)) IN IOLIST
407 VERSION 5, 25-JUN-76
GRAPH (123) STA1 (63) ADD ERR= ON OPEN/CLOSE
410 GLOBAL(76) QA568 MAKE DTABPTR GLOBAL FOR BLDDIM
ACT1(105)
411 CMPLEX(129) 19537 DON'T SWAP ARGS FOR MAX OR MIN IF
FIRST ARG IS NEGATIVE
412 CMPLEX(130) VER5 NODE WITH ARG1 = DOUBLE ARRAY REF FOR
KA10 MUST HAVE COMPLEXITY AT LEAST 3
REGAL2(137) VER5 USE SUBSCRIPT REG FOR DOUBLE ARRAY REF
VALUE EXCEPT ON KA10
413 CNSTCM(66) ----- DON'T USE FADL IN INTDP IF NOT ON KA10
414 ACT1(106) QA625 FIX .I OFFSET SHARING SO ONLY SHARES
DIM2 .I IF DIM1 SAME
415 ACT1(107) 18964 DON'T DESTROY SYMBOL TABLE ENTRY FOR
FORMAL FUNCTION WHEN ENTRY STATMNT
SEEN WITH THE FUNCTION AS A PARAM.
416 GCMNSB(73) QA650 FIX MOVCNST SO HASH ENTRY IGNORED ON
NEXT PASS IF .R+X CAN'T BE MOVED AS .O
417 STA3(58) QA637 FIX BAD STATEMENT FUNCTION FROM
CLOBBERING THINGS ON CLEANUP IN 324
420 STA3(59) QA637 AFTER BAD ST FN, CLEAN UP THE NAME
SO THAT IT DOES NOT CAUSE TROUBLE LATER
421 PNROPT(147) QA651 DON'T PROPAGATE .O IF CAME FROM .R
422 LISTNG(12) 18493 IMBEDDED NULLS CAUSE LOW LEVEL LOOPING
423 ACT1(108) QA709 FIX PATCH 414: DIMNUM IS 1-RELATIVE
424 STA1(64) QA690 ERROR IF DIRECTORY= NOT LITERAL OR ARRAY
NAME IN OPENCLOSE
425 PHA2(110) QA714 CALL ZTREE TO CLEAR DEFPTS IF
OPTIMIZATIONS DISCONTINUED IN OPTERR
426 CMPLEX(131) 18816 SET FNCALLSFLG FOR IMPLICIT FN CALLS,
DOALC(108) SO 0,1, AND 16 ARE KNOWN TO BE CLOBBERED
427 COMSUB(257) 18871 FIX COMSUBS IN IOLISTS
430 P2S2(53) 18876 MAKE ARITH IF NODES ABSORB NEGS RIGHT.
431 PH3G(241) 19121 MATERIALIZE VARIBLES THAT HAVE BEEN
ALLOCATED TO REGISTERS DURING A
DOUBLY-NESTED DO LOOP CORRECTLY.
432 REGAL2(138) 19037 FIX CONVERSION OF LOGICAL ARRAY REF
433 DOXPN(81) 19130 MAKE DO I=10,1 EXECUTE ONCE
434 P2S1(60) 19211 CHECK FUNCTION CALL CONTAINING DO INDEX
AS A PARAMETER AFTER CONSTANT FOLDING.
435 IOPT(50) 18964 FIX IO LISTS WITH VARIABLE INCREMENT
436 OUTMOD(67) 19427 CATCH EQUIVALENCE VIOLATION WHEN
BUILDING EQUIVALENCE CLASSES.
437 GCMNSB(74) QA771 DON'T LET DOTOHASGN MOVE .O=EXPR IF
.O CAME FROM .R
VER5(2) MARK SUBSUMING .O IF SUBSUMEE .O CAME
FROM .R IN DOTOFIX
440 GCMNSB(75) QA771 DON'T NEXTUP .O IF CAME FROM .R IN
MOVCNST
441 REGAL2(139) 19231 FIX REGISTER ALLOCATION FOR A D.P.
ARRAYREF AS A FN CALL PARAMTER.
442 COMSUB(258) 19233 MAKE THE DELETION OF HASH ELEMENT
WORK IF ELEMENT IS FIRST IN ITS LIST
443 GRAPH(124) QA656 WARNING + OPT STOPPED IF DISCOVER
ILLEGAL DO NESTING IN LNKEXTND
ERROVD ADD WARNING MESSAGE E140
ERROUT(37)
444 PH3G(242) 19484 FIX TO 246 - DON'T FORCE PRELOAD OF
COMPILER VARIABLES IF GOTO ENCOUNTERED.
445 P2S1(61) 19632 USE FEWER LOCALS ON STACK DURING
RECURSIVE CALLS TO P2SKARITH
446 STREGA(211) 20652 BAD CODE FOR I=I*3 AND I=I**7 (QAR753)
447 UTIL(85) 19547 NEGATIVES PROPAGATED TOO MUCH IN FORTG
450 COMSUB(259) QA784 DON'T NEXTUP ARRAYREF IF INSIDE IOLIST
451 ERROUT(35) 19610 CORRECT SPELLING IN ERROR MESSAGE
452 COMMAN(452) 19610 NUL: CAUSES PROBLEMS AS OUTPUT DEV
453 DEFPT(118) 19695 DON'T MAKE DO BE DEFPT OF ALL VARS
MODIFIED INSIDE THE LOOP.
454 PH3G(243) 19699 DON'T PLACE PRELOADS 1 STATEMENT TOO
LATE WHEN PLACING AFTER A DO LOOP.
455 GCMNSB(76) QA784 CAN'T MOVE EXPRESSIONS OUT OF IMPLIED DO
IF INSIDE LOGICAL IF
456 GCMNSB(77) QA784 FIX FINDTHESPOT SO CALLER TELLS IT WHERE
TO STOP
ADD NEW ROUTINE FINDPA FOR GLOBMOV AND
DOTOHASGN
CALL FINDTHESPOT WITH 2ND PARAM IN
GLOBMOV AND DOTOHASGN
COMSUB(260) GIVE GLOBMOV ENTIRE HASH ENTRY IN CMNMAK
FOR FINDPA
MOVA(26) CALL FINDTHESPOT WITH 2ND PARAM = TOP IN
HAULASS
TSTR(51) CALL FINDTHESPOT WITH 2ND PARAM = TOP IN
REDUCE
457 REGAL2(140) 19805 TRY HARDER NOT TO REQUEST A REG IN
REGAL2 UNLESS WE REALLY NEED IT - MIGHT
RUN OUT EARLY.
460 ACT1(109) 19477 CHANGE DIMENSION PROCESSING TO BE
ERROUT(36) MORE THOROUGH AND LESS APT TO EXIT EARLY
461 LISTOU(57) 19477 DETECT WHEN PROGRAM IS TOO LARGE
ERROVG(1) ADD E142
ERROUT(38)
462 DRIVER(18) 19960 FIX MRP1 TO LEAVE SREG<LEFT> WITH THE
SAME VALUE IT FOUND IN IT
463 UTIL(86) 19989 FIX IMPLIED DO'S WHOS INITIAL VALUE OR
STEP SIZE COME FROM AN OUTER AOBJN DO.
464 LISTOU(58) QA754 ADD LINE-NUMBER/OCTAL-LOCATION MAP IF
PHA3(50) 780 MACRO LISTING NOT REQUESTED
GLOBAL(77) ADD 3 GLOBALS FOR LINE-HANDLING
465 PNROPT(148) 20657 CLEAR INDVAR BEFORE CALLING REDUCE FOR
STATEMENTS BEFORE THE DO LOOP; WE MIGHT
FIND SOME REDUCTIONS OTHERWISE (!!!).
466 PNROPT(149) VER5 DELETE CODE TO ZERO DEFPTS BETWEEN
LENTRY & TOP (REMOVE 465 AND MORE)
467 IOFLG(9) VER5 TAKE OUT FORSWI.REQ
INOUT(37) REQUIRE FTTENX.REQ
LISTNG(13)
STA2(43)
MAIN(29) REQUIRE FT1SEG.REQ
470 OUTMOD(68) 20744 MAKE SURE THE HIGH SEG STARTS AT LEAST
A PAGE ABOVE THE END OF THE LOW SEG.
471 STREGA(212) 20309 LHS A LOGICAL EQUIVALENCED VAR MAY
GENERATE BAD CODE
472 OUTMOD(69) 20494 INCORRECT EQUIVALENCE PROCESSING
WHEN LAST ELEMENT OF GROUP IN COMMON
473 OUTMOD(70) 20478 SCALARS AND ARRAYS LISTING TOO WIDE
474 OUTMOD(71) 20479 OUTPUT CRLF AFTER LAST COMMON BLOCK NAME
475 IOPT(51) 20813 DON'T COLLAPSE ELISTS THAT WE SHOULDN'T
476 IOFLG(10) QA754 MAKE MAPFLG FROM STATFLG IN FLGREG
COMMAN(476) 780 MAKE /MAP A SWITCH TO SCAN
LISTOU(59) MAKE LINE NUMBER/OCTAL LOCATION MAP
PHA3(51) OPTIONAL UNDER /MAP SWITCH
477 LEXSUP(10) QA831 MAKE MESSAGE NAMLEX'S MORE READABLE
500 TSTR(52) 20818 DON'T SEE IF A NODE IS AN I/O STATEMENT
UNLESS IT'S A STATEMENT.
501 TSTR(53) 21113 DON'T REDUCE .O'S IN OUTER DO LOOPS.
502 PH3G(244) 20463 SORT SAVED VS NON-SAVED REGS CORRECTLY
IN FLIPCODES; FAKE ITMCT ALSO
COMMAN(502) VER5 REMOVE XLIST'S FOR FTTENEX
503 STREGA(213) 19976 FOR A(I) = FUNC. CALL, DON'T LEAVE I
IN REG 1 WHEN CALCULATING LH FIRST.
504 REGAL2(141) QA815 FIX EDIT 412 TO NOT ALLOW FETCHES OF
COMPLEX NUMBERS INTO AN AC WHICH IS
ALSO THE INDEX REG. NEGATED FETCHES
USE TWO INSTRUCTIONS (EVEN ON KI'S),
AND NEGFLG'S CAN SNEAK IN MUCH LATER.
505 VER5(3) QA815 IN DOTORFIX DON'T MOVE .R INIT IF IT'S
ALREADY IN THE CORRECT PLACE
506 LISTNG(14) 10056 LINESEQUENCED FILES KILL LOW LEVEL BUFFERING
507 GCMNSB(100) ----- FIX EDIT 440 TO ALLOW NEXTUP OF .O WHICH
CAME FROM .R IN MOVCNST IF MOM IS
ARITHMETIC
510 CMPLEX(132) ----- DON'T TEST ALCRETREGFLG IN DATAOPR NODES
511 ERROUT(39) ----- FIX E37,E79,E100 TO AGREE WITH ERROVD
FIX AND MOVE E140 FROM [443]
FIX SPELLING IN E74
ERROVD(2) FIX E140
512 COMMAN(512) ----- MAKE /MAP FROM [476] CALLED /LNMAP SINCE
/MAP/LMAP ARE LOAD COMPIL SWITCHES
513 GCMNSB(101) QA771 IN MOVCNST WHEN .O IS CREATED, PASS UP
ORFIXFLG FROM ANY .O BEING SUBSUMED
CHANGE [507] TO FREE VARAIBLE T IN MOVCNST
514 GCMNSB(102) QA806 IN MOVCNST IF NARY INSURE .R IS 1ST ARG
SINCE [V5] CODE ASSUMES .R + X
515 VER5(4) QA815 REMOVE "TEMP [EXPRUSE] _ 1" IN DOTORFIX
***** Begin Version 5A ***** 7-Nov-76
516 COMMAN(516) 21215 FIND FILES WITH BLANK EXTENSIONS IN SFDS
517 COMMAN(517) 21238 MAKE SFD'S IN COMMAND STRINGS WORK.
520 COMSUB(261) 21271 PROHIBIT NEGATIONS IN RELATIONAL COMSUBS
521 STA1(65) QA900 FIX PARAMS TO FATLEX IN OPENCLOSE
522 STREGA(214) 20819 CHECK NEGFLGS FOR ARRAYREFS IN IOLISTS
523 COMMAN(523) QA1038 FIX DEFAULT FLAG SETTINGS FOR SCAN:
SWITCHES COUNT FROM LEFT NOT RIGHT
524 COMSUB(262) QA876 PUT BACK ARRAY REF IN STPRECLUDE SO HASH
ENTRY TAKEN OUT OF TREE
CALL STPRECLUDE BEFORE CMNMAK SO CAN
HASH SKEWED TREE WITH NEG FLAGS
UNCHANGED
525 VER5(5) QA949 DO CORRECT TYPECNV IN DOTOFIX ONLY IF
NECESSARY
526 GCMNSB(103) QA1035 IN CHKDOM IF FNARY AND NO MATCH ON
"FUNC(ARRAYREF), PUT BACK ARRAYREF
SO HASH TBL ENTRY NOT IN TREE
527 STREGA(215) 20317 BAD CODE FOR ASSOCIATE VARS IN COMMON
530 P2S2(54) 21606 BAD CODE FOR DOUBLE PRECISION SPECOPS
WHICH GENERATED FSC INSTRUCTIONS
531 STA1(66) 20323 GIVE WARNING WHEN SUBROUTINE PARAMETER
ERROUT(40) IS USED AS ASSOCIATE VARIABLE
532 STREGA(216) 20323 FIX CODE GENERATION FOR AN ARRAY ELEMENT
CGSTMN(127) USED AS AN ASSOCIATE VARIABLE
533 STA2(44) 21796 INCLUDE STMNT DESTROYS LOCS 4400-4402
534 STA3(60) 21817 INTERNAL COMPILER ERRORS IN FORTB CAUSED
BY BADLY STRUCTURED STATEMENT FUNCTIONS
535 GRAPH(125) 21809 INACCESSIBLE CODE WITH ZERO LINE NUMBER
536 LEFTFM(23) ADD RCHAR TO ERR NAME PLIT
537 LISTNG(15) 21811 BAD PRINTING OF ERROR CONTINUATION LINE
540 STA2(45) 22191 BAD COMMON STMNT GIVES ICE
541 LISTNG(16) ----- -20 ONLY: CLEAR LASTCHARACTER IN READTXT
AFTER ^Z SEEN SO MORE TTY: INPUT MAY
BE DONE
542 EXPRES(32) 22147 MAKE A NOT IMPLY TYPE LOGICAL ALWAYS.
543 SRCA(50) ----- FIX BINARY SEARCH FOR LIBRARY NAME
544 FIRST(127) 10290 FIND STMNT NODE TOO SMALL - EXPAND IT
545 REGAL2(142) 22096 FUNCTION VALUES MUST GO INTO REALLY FREE REGS
546 STREGA(217) 22030 FIX PROBLEMS WITH OPERATIONS WHICH CLOBBER
FOLLOWING REGISTER (IDIV)
547 LEXICA(17) 21280 (QAR863) FIX INITIAL TAB IN COLUMN 6 TO
GO TO COL 7 ON AN INITIAL LINE OR COL
6 IF A CONTINUATION LINE
550 REGAL2(143) 21824 FIX REG ALLOCATION FOR BIG EXPRESSION
551 TABLES(155) 21826 FIX TYPE CONVERSION DURING CODE GENERATION
552 REGAL2(144) 21826 GENERATE BETTER CODE FOR TYPE CONVERSION
OF ARRAY REFERENCE
553 P2S2(55) 21826 TYPE CONVERSION MAY BE NECESSARY IF LOGICAL
OPERATION ABOVE IT IS LIQUIDATED
554 REGAL2(145) 22324 AND NODE WITH THE NEGATION OF A FUNCTION
CGEXPR(72) CALL BELOW IT GIVES BAD CODE
555 LISTOU(60) 22281 FIX LINE NUMBER/OCTAL MAP WITH ENTRY POINTS
556 LISTNG(17) ----- PUT /L IN HEADING OF PAGE IF OCTAL MAP REQUESTED
557 COMMAN(557) ----- CATCH WILD PPN OR SFD AS ERROR
560 COMMAN(560) ----- -20 ONLY: HANDLE PPNS IN THE COMMAND LINE CORRECTLY
561 LISTNG(18) 10429 ALLOW CONTINUATION LINES AFTER PAGE
LEXICA(18) MARKS AND FORM FEEDS
562 PNROPT(150) 22540 IOLISTS IN OPTIMIZATIONS MAY KILL REG 0
563 GNRCFN(32) 22541 SPURIOUS ERRORS IF FIRST ARG TO LIB FN
IS OF UNACCEPTIBLE TYPE
564 CGSTMN(130) 22693 MAKE CGREAD == CGWRIT: GENERATE FIN CALL
ON UNFORMATTED WRITE WITH NO IOLIST
565 GRAPH(126) 21810 EXTENDED RANGE DO LOOPS GIVES BAD GRAPH
566 COMSUB(263) 22701 BAD COMSUBS WITH MANY NOT FLAGS
AND SHAPE SKEW
567 ACT1(110) 22284 EXTERNAL STMNT NOT REMEMBERED AT ENTRY POINTS
570 STA3(61) 22703 BAD STMNT FN GIVES ICE (FN(2,3))
571 FIRST(130) 22378 ADD IDUSECNT DEFINITION
TABLES(156) ADD ARALINK DEFINITION
ACT1(111) FIX V5 OPT THAT SHARES 2ND OFFSET OF FORMAL
ARRAY IF 1ST DIMS = SO ALL WILL WORK IF
ARRAY SUBSEQUENTLY TYPED DIFFERENT #
WORDS THAN WHEN SHARING 1ST DONE
DRIVER(19) DEFINE & CALL CLERIDUSECNT AT END OF MRP1
572 ACT1(112) 21825 CHECK IMPLIED DO INDEX FOR ALREADY ACTIVE
(FROM ENCLOSING IMPLIED OR REAL DO)
573 DBUGIT ----- NEW REQUIRE FILE TO HOLD DBUGIT FLAG
IOFLG(11) REMOVE "BIND DBUGIT="
DRIVER(20) REQUIRE DBUGIT.REQ
INOUT(40)
LEXICA(19)
LEXSUP(11)
574 SRCA(51) ----- REWRITE BINARY SEARCH IN SRCHLIB TO WORK
AFTER EDIT 543
575 DEFPT(119) 22820 REWRITE ZAPLEVEL TO PREVENT STACK OVERFLOW
FOR VERY LARGE BRANCHING PROGRAM.
576 GRAPH(127) 22796 FIX LINE NUMBER GIVEN FOR INFINITE LOOP
577 TSTR(54) 22352 DO LOOP WITH A CALL STATEMENT INSIDE MUST
MATERIALIZE LOOP VARIABLE IF IT IS IN COMMON
600 REGAL2(146) 22990 MORE EFFICIENT STACK USAGE IN FORTE
601 ACT1(113) Q20-26 FIX EDIT 572 TO CHECK IMPLIED DO INDEX
IN DATA STATEMENTS FOR ALREADY ACTIVE
FROM ENCLOSING IMPLIED DO
602 COMSUB(264) 22700 OPTIMIZED IOLISTS WITH SKEWED EXPRESSIONS
MAY GENERATE ELISTS INCORRECTLY
603 ACT0(53) 23442 ADD * AS INITIAL CHAR FOR LABEL CONSTANT
604 OUTMOD(72) 23425 FIX LISTING OF COMMON BLOCK SO THAT WE
DO NOT GET AN EXTRA CARRIAGE RETURN
605 TSTR(55) 23478 BAD CODE WITH /OPT FOR ASGMNT STMNT WITH
LHS LIKE A(I/2) OR A(I**5)
606 CNSTCM(67) 22795 SOME OVERFLOWS DURING CONSTANT FOLDING
NOT DETECTED AND POOR CODE GIVEN.
607 GLOBAL(100) 22685 MAKE NEW GLOBAL NEDZER TO INDICATE IF
ZERO-ARG-BLOCK NEEDED
CGDO(137) SET NEDZER IN CGSBPRGM TO "0-A-B NEEDED"
CGSTMN(131) SET NEDZER IN CGEND, CGSTOP & CGPAUS TO
"0-A-B NEEDED"
PHA3(52) GENERATE 0-A-B ONLY IF NEEDED
610 P2S2(56) 23333 BAD CODE FOR COMSUB WITH NEG FLAG
REPLACES EDIT 345.
611 OPGNTA(120) 23662 IMMEDIATE SIZE COMPLEX CONSTANTS CAUSE
TROUBLE FOR CODE GENERATION.
612 IOPT(52) 23263 INITIALIZE ARRCOUNT IN IOCLEAR (THIS
COMPLETES EDIT 406).
613 CGDO(140) QA2114 IGNORE INDIRECT BIT IN FORMAL FUNCTION
TARGET IN ENTRY PROLOGUE
614 LISTOU(61) 23760 OUTPUT ONLY NON-BLANK LINES ON /LNMAP
615 PH3G(245) 23116 BE CAREFUL WITH LABELS WHEN PRELOADING
616 STREGA(218) 22345 I/O LIST UNDER REGISTER SCARCITY GIVES ICE
617 UTIL(87) QA2121 ONLY TRY TO SUBSTITUTE THE SUBSCRIPT OF
AN ARRAYREF IF IT ISN'T A CONSTANT
620 COMSUB(265) 23720 D.P. ARRAY REF IN IO LIST CAUSES PROBLEMS
DURING OPTIMIZATION (IOLSCLS NODE PTRS)
621 LISTNG(19) QAR2120 ACCOUNT FOR PAGE MARKS AT END OF FILE.
***** Begin Version 5B *****
622 CMPLEX(133) 11020 ICE WITH COMPLEX ARRAY REFERENCE
623 MOVA(27) ----- FIX QUALIFY TO CALL ONLIST ONLY IF THE
DOCHNGL EXISTS (IE, WE'RE NOT IN AN
IOLIST: THIS IS NECESSARY TO USE A
BLIS10 NEWER THAN 7B(222)
624 ERRTB3 QA2166 REORDER RADIX 10 AND RELOC 400000
625 STREGA(219) 23122 FIX LHINREGALC TO SET INREGFLG WHEN
SETTING TARGTAC TO THE REG ON THE
LH OF THE ASSIGNMENT STATEMENT.
626 EXPRES(33) 23169 DON'T ALLOW FUNCTION NAMES OR ARRAY
NAMES WITHOUT A PARENTHESIZED
ARGUMENT LIST TO BE USED IN
EXPRESSIONS IN FUNCTION OR
SUBROUTINE ARGUMENT LISTS.
627 ACT1(114) 23755 GET VARIABLY-DIMESNIONED ARRAYS RIGHT
WHEN THE FIRST TWO (OR MORE)
SUBSCRIPTS ARE CONSTANT AND THE
DIMENSION STATEMENT APPEARS BEFORE
THE D.P. OR COMPLEX STATEMENT.
630 IOPT(53) 10962 FIX ISOLATE TO CATCH ALL IOLISTS
THAT CANNOT BE MADE INTO SLISTS
OR ELISTS. THIS INCLUDES CASES
LIKE A(-I), A(3*(I-1)), ETC.
THIS EDIT REMOVES EDITS 406 AND
612, WHICH ONLY CAUGHT SOME CASES.
631 VER5(6) 10962 TEACH VER5 HOW TO ZERO OUT DEF POINTS
ON IOLISTS.
632 ALCBLO(58) 24245 WHEN CLOBBERING A REG, DON'T CLEAR
VARINREGFLG IN THE SYMBOL TABLE IF
THE VARIABLE IS ALSO IN ANOTHER REG.
633 DOXPN(82) 24236 FIX EDIT 433 TO NOT CLOBBER A CONSTANT
TABLE ENTRY.
634 PH3G(246) 11277 PRELOAD VARIABLES IF THEY ARE FIRST USED
IN AN ASSIGNMENT STATEMENT THAT IS THE
OBJECT STATEMENT OF A LOGICAL IF.
635 ACT1(115) 24868 MAKE DATALIST RETURN -1 IF IT GETS E66,
SO CALLER WON'T BELIEVE RETURN VALUE
IS A LINKED LIST AND BLOW UP.
636 FIRST(131) 23066 DON'T DUMP LABELS TO THE REL FILE IF
OUTMOD(73) WE DON'T KNOW THEIR VALUE. THIS
LISTOU(62) HAPPENS IF LABLADJ DECIDES THAT THE
LABEL IS UNREFERENCED AND DELETES IT.
637 GRAPH(128) 24802 IF SOME STATEMENTS DON'T GET
POSTDOMINATORS, FIX GRAPH SO THEY
DO INSTEAD OF GIVING INF LOOP MESSAGE
AND STOPPING OPTIMIZATION. ALSO
MAKE INACCESSIBLE CODE ALGORITHM
LOOK AT PREDOMINATORS TO FIND MORE
CASES. THIS FIXES EDIT 327.
640 GCMNSB(104) 24971 FIX DOTOHASGN TO CHECK TO SEE IF .O
ASSIGNMENT IS IN AN IMPLIED DO, NOT
IF .O USAGE IS.
641 PH3G(247) 25010 LOGICAL IF STATEMENT WITH CALL STATEMENT
AS RESULT GIVES REGISTER ALLOCATION PROBLEMS
IF IT DIRECTLY PRECEDES A DO LOOP
642 LEXICA(20) 11409 SPURIOUS PAGE HEADING MAY BE GIVEN IF FORM
FEEDS OCCUR IN INPUT PROGRAM
643 GCMNSB(105) 25201 DO NOT ALLOW ARRAY REF TO BECOME PART OF
TWO POTENTIAL COMMON SUB-EXPRESSIONS
644 COMSUB(266) 25390 IN LINE FUNCTIONS WITH NEG FLAGS - BAD CSE
645 LISTOU(63) 25249 EXTRA LINES PER PAGE IN LISTING IF ENTRY
OUTMOD(74) POINTS PRESENT .
646 LISTOU(64) 25250 SUBROUTINE SIXBIT NAME SHOULD NOT BE LOC 0
647 MOVA(28) 25315 ARRAYS IN HASH TABLE NEED SPECIAL TREATMENT
IN REDEFPT - ICE OTHERWISE
650 LISTOU(65) 25247 MAKE LISTINGS NICER FOR DP AND STRING CONSTANTS
651 IOPT(54) 25062 IO LIST DEPENDENCIES WITH .O VARS
652 ALCBLO(59) NONE FIX CHKOTHREGS (EDIT 632) TO HANDLE
DOUBLE WORD VARIABLE CASE
653 F72BNF.SYN 25441 UNIT NUMBER FOR FIND STATEMENT SHOULD
BE ANY ARRAY REFERENCE
654 COMMAN(654) 25297 SWITCHES IN BAD COMMAND LINE ARE TOO STICKY
655 COMMAN(655) 25338 EMPTY REL FILE WITH SYNTAX SWITCH
656 COMMAN(656) 25246 PROTECTION FAILURES NOT REPORTED
657 INOUT(41) 11554 /DEB/OPT WARNING MESSAGE KILLS FLAG
DRIVER(21) REGISTER SO NO LISTING FILE GIVEN
660 OPTMAC(1) 11427 IF(FN(I))GOTO 10 GIVES BAD CODE IF I IS
PH3G(248) LIVING IN REGISTER.
661 PNROPT(151) 24100 DO NOT THROW AWAY LABELED STATEMENT
662 PH3G(249) 25245 INACCESSIBLE DO LOOP CAN GIVE ICE
663 ACT1(116) 25643 FIX ENTRY POINTS WITH FORMAL FUNCTIONS
664 GCMNSB(106) QAR118 NEG FLAG ON SKEWED EXPR SPELLS BAD CODE
665 GCMNSB(107) QAR118 B/C(I) CANNOT BE CSE FROM A/B/C(I)
666 DATAST(45) 25572 DATA (A(I), I=10,1,-1) LOSES DUE TO
NEGATIVE INCREMENT - FIX THIS.
667 LISTNG(20) 25664 PAGE MARK AT END OF BUFFER WITH ONE FOLLOWING
LEXICA(21) NULL WORD (LAST IN BUFFER) NOT TREATED RIGHT
670 LEXICA(22) 25571 CONTINUATION LINE MUST HAVE
BLANK CHARS IN LABEL FIELD.
671 P2S1(62) NVT DEF PTS NEED TO BE SWAPPED WHEN
DEFPT(120) THE ARGUMENTS ARE SWAPPED
672 REGAL2(147) 25725 NOT FLAG ON ARRAY REF CAN GIVE PROBLEMS
673 DRIVER(22) 25984 REPORT ILLEGALLY NESTED DO LOOPS CORRECTLY
674 FIRST(132) 11803 INCREASE NESTING LEVEL FOR DO LOOPS
GLOBAL(101) FROM 32 TO 79, DO CLEANUP IN GLOBAL,
CGDO(141) ADD TEST FOR LARGER STACK OVERFLOW,
ERROVG(2) AND ADD ERROR MESSAGE TO ERROVG
ERROUT(41) AND ERROUT.
675 LEXICA(23) 26049 RUBOUT IN SOURCE PROG MAY GIVE INTERNAL
ERRORS IN ROUTINE LEXICA - FIX IT
676 COMMAN(676) 11931 CHANGE RESET TO BE RESETUUO
677 IOFLG(12) 25573 ADD A DEBUG:PARAMETER SWITCH
DRIVER(23) this causes the compiler to
LISTNG(21) generate code at entry points to
CGDO(142) check the number of parameters
OPGNTA(121) passed. forots edit 755 must be added
COMMAN(677) at the same time as 677.
700 OPTMAC(2) ----- REMOVE EHSIZ DECLARATION (AFTER EDIT 674)
701 COMSUB(267) 22582 2 ** .R CANNOT BECOME .R ** 2
702 OUTMOD(75) ----- LISTING OF SUBPROGRAMS IS SLOPPY
703 OUTMOD(76) ----- LISTING OF SCALARS AND ARRAYS CAN
GIVE BLANK PAGE IN LISTING
704 COMMAN(704) 26390 FIX DEFAULT BUFFER SIZE (IF DEVSIZ FAILS)
705 LISTOU(66) 26442 MAKE NAME FROM PROGRAM STATEMENT BE
AN ENTRY POINT FOR MAIN PROGRAM.
706 GCMNSB(108) 27170 OPTIMIZER GIVES BAD CODE FOR BIG
EXPRESSION INVOLVING DO LOOP INDEX
707 SRCA(52) 27153 REDUCE JOBFF WHEN FREEING SPACE UP
710 DRIVER(23) 12299 FIX EDIT 657 TO INITIALIZE DEBOPT
711 CGSTMN(132) 26754 PUT OUT FIN CALL WITH ENCODE/DECODE
TO RECLAIM FREE SPACE
712 DRIVER(25) 26490 ILLEGALLY NESTED LOOPS CAN GIVE ICE
WHEN TRYING TO PRINT ERROR MESSAGE!
713 LEXICA(24) 26658 <CR><CR><EOB><LF> KILLS LEXICA
WHEN PROCESSING COMMENT LINE
714 PNROPT(152) 26498 BAD CONSTANT PROPAGATION (CHOSEN BAD)
715 COMSUB(268) 12743 NOT FLAG IN COMSUB GIVES BAD CODE.
716 FIRST(133) 26409 SUBROUTINES WITH ALTERNATE LABEL
ACT0(54) RETURNS CAUSE GLOBAL REGISTER ALLOCATION
GRAPH(129) PROBLEMS. PASS ON THE INFORMATION SO
PH3G(250) THAT THE LOOPS CAN BE TREATED PROPERLY
717 LEXICA(25) 26560 GIVE MEANINGFUL ERROR MESSAGE ON
ACT1(117) REDEFINITION OF PARAMETER VARIABLE
720 PHA2(111) 27830 POOR CODE GENERATED FOR ASSIGN GO TO
STMNT WITH NO LIST (OPTIMIZED ONLY)
721 STREGA(220) ----- A=A*B SHOULD INVALIDATE REGISTER FOR A
(IN CASE SOME OTHER VAR LIVES THERE)
722 STA2(46) 28072 ADD /NOCREF SWITCH TO INCLUDE STATEMENT
723 COMMAN(723) ----- ADD /NOWARN: SELECTIVITY TO COMPILER
INOUT(42) SWITCH LIST. CODE IS MAINLY IN COMMAN
ERROVA(1) (TO PROCESS THE SWITCH AND MODIFIERS)
ERROVC(1) AND IN INOUT (WHERE THE MESSAGE IS
ERROVD(3) PRINTED BY FATLERR).
ERROVR(1)
ERROVG(3)
724 TABLES(157) ----- PREVENT ICE WITH N-ARY LOGICAL TREES
725 OPTMAC(3) 27403 CHANGE CSTMNT BEFORE CALLING NEXTUP
COMSUB(269)
726 DOALC(109) 28283 FIX CODE FOR DOUBLE PRECISION (KA) AND
COMPLEX PARAMETERS FOR STATEMENT FUNCTION
727 STA3(62) 13247 LOGICAL IF WITH TWO LABELS CAN CAUSE
BAD BLOCK STRUCTURE (INCORRECT LABEL COUNT)
730 CMPLEX(134) 28275 BAD REGISTER ALLOCATION FOR A=AMIN(A,EXPR)
731 IOPT(55) 28246 BAD CODE FOR CSE IN I/O LIST (COMMON VAR)
732 ERROVC(2) ----- DEFINE SAVSTMNT FOR EDIT 731 (NON-OPT)
733 TABLES(158) ----- THE "NOT" OF AN EXPRESSION WHICH
GOPTIM(54) RESOLVES TO A CONSTANT AT COMPILE TIME
HAS PROBLEMS USING THE OPTIMIER.
734 LISTOU(67) ----- AFTER EDIT 650, DP CONSTANTS CAN GET
PRINTED EVEN WITH CAMXX INSTRUCTIONS!
735 OUTMOD(77) 28528 OUTPUT HEADINGS ONLY WHEN NECESSARY
736 GCMNSB(109) ----- BAD CODE FOR -(.R0-KONST) WITH V5/OPT
737 LEXSUP(12) ----- ADD THE .NEQV. OPERATOR
740 PH3G(251) 13537 ALLOCATE REGISTERS FOR UNIT=ARRAY(I,J)
IN OPEN AND CLOSE STATEMENTS
741 ERROUT(42) ----- ADD WARNING MESSAGE WHEN WE FIND
INOUT(43) AN ARRAY DECLARED USING THE "/" TO
ACT1(118) SPECIFY UPPER AND LOWER BOUNDS.
COMMAN(741) ALSO CLEAN UP THE ERROR MODULES SO
ERROVA(2) THAT WE CAN ADD ERROR MESSAGES MORE
ERROVC(3) EASILY IN THE FUTURE WITHOUT HAVING
ERROVD(4) TO MAKE CHANGES TO EACH MODULE
ERROVG(4)
ERROVR(2)
F72BNF.SYN
742 LEXICA(26) ----- CHANGE STOP/PAUSE CONSTANT FROM
STA0(47) OCTAL TO DECIMAL CONSTANT (MAX 6 CHARS)
743 IOPT(56) ----- FIX UP EDIT 651 TO BE NOT SO AMBITIOUS.
KEEP THE OPTIMIZATION IF POSSIBLE.
744 STREGA(221) 28463 DOUBLE WORD ARRAY IN SLIST/ELIST MAY
USE AN ODD-NUMBERED REGISTER TWICE.
745 STA0(48) ----- ACCOMODATE LONG ARG LISTS (.GTR. 124)
746 LEXSUP(13) 13673 ALLOW FORMAT LABELS TO BE ASSIGNED TO
VARIABLES IN ASSIGN STATEMENTS
747 ERROUT(43) ----- MAKE ALL ERROR MESSAGES LOWER CASE
ERROVC(4) ALSO DO SOME CLEANUP WORK IN THE
ERROVD(5) ERROR MESSAGE ROUTINES
ERROVG(5)
ERROVR(3)
UNEND(4)
COMMAN(747)
750 TFV 3-Jan-80 ------
Remove DEBUG:PARAMETER switch from compiler (edit 677) and
from FOROTS (edit 755)
Routines:
CGDO(143) COMMAN(750) DRIVER(26) IOFLG(13)
LISTNG(22) OPGNTA(122)
751 DCE 4-Feb-80 -----
Change the way the LOOKAHEAD table is formatted and used. Make
action routines occupy a field rather than a bit (for expansion).
Enhance MASK so that it is faster and better, and able to handle
the new format. Fix up LEFT72 in many ways - error detection and
reporting, action routine handling, etc. This also makes edit 741
work properly!
Routines: LEFT72(23), FAZ1(34)
752 EGM 12-Feb-80 13736
If fatal errors are generated during compilation, discard the .REL file.
Routines: COMMAN(752), INOUT(44)
753 EGM 12-Feb-80 29028
Check the IO list implied loop initial value for .O variables when
removing .O assignment nodes.
Modules: IOPT(57)
754 EGM 15-Feb-80 29120
Make I/O dependency check work when common sub nodes are involved.
Modules: UTIL(88)
755 EGM 20-Feb-80 13884
Allow lower case in INCLUDE/NOLIST/NOCREF for F20 version
Modules: STA2(47)
756 DCE 3-Mar-80 -----
Addition to edit 751 so that more action routines can be used
Modules: FAZ1(35)
757 EGM 7-Mar-80
Add extra checks and a new register allocation routine to free up the
last free register pair for a node which is targetted for that pair.
Modules: REGAL2(148)
***** Begin Version 6 *****
760 TFV 1-Jan-80 -----
Add new OPEN arguments, FORMAT descriptors, and keywords for
I/O control lists
Modules:
ACT0(55) ACT1(119) CGSTMN(133) COMMAN(760)
DEFPT(121) FIRST(134) FMTLEX(2) FORMAT(31)
PHA2(112) STA0(49) STA1(67) STREGA(222)
TABLES(159) UNEND(5)
761 TFV 1-Mar-80 -----
Add /GFLOATING support and remove KA support (KA10FLG)
Modules:
ARRXPN(53) CANNON(26) CGDO(144) CGEXPR(73)
CGSTMN(134) CMPLEX(135) CNSTCM(68) COMMAN(761)
DATAST(46) DEBUG(37) DOXPN(83) EXPRES(34)
FIRST(135) FLTGEN(2) DRIVER() GLOBAL(102)
GNRCFN(33) IOFLG(14) LISTNG(23) LISTOU(68)
OPGNTA(123) OPTAB(2) OUTMOD(78) P2S1(63)
P2S2(57) PNROPT(153) SKSTMN(94) STA1(68)
TABLES(160) VLTPPR(45)
762 EGM 18-Apr-80 -----
Split COMMAN.MAC in two; COMMAN.MAC contains FTNCMD, and a new module,
REVHST.MAC, contains the revision history and .JBVER symbols.
Modules:
COMMAN(100) REVHST(762)
763 EGM 24-Apr-80 13913
Cause optimizer to consider ENTRY formals during definition point
determination
Modules:
DEFPT(122)
764 EGM 24-Apr-80 29279
Do not alloacate a register for an immediate array ref I/O list item
Modules:
STREGA(223)
765 DCE 13-May-80 -----
Add error message for future code (Expression illegal in output list).
Module: ERROUT(44)
766 DCE 13-May-80 -----
Add error message for illegal use of an array.
Modules:
ERROUT(45), INOUT(45), STA0(50), COMMAN(NEW)
767 DCE 20-May-80 -----
Rewrite much of the command scanner for clarity, bug fixes, etc.
Fix bug with /GFL if GFL microcode not present; redo /GFL processing.
Add /F77 switch (future use); also add secondary switch word.
Modules:
COMMAN(101) - Rewrite and clean up
LISTNG(24) - Add /F77 to heading, fix up /GFL
IOFLG(15) - Create secondary switch word F2, add F77
FIRST(136) - Move GFL flag into F2; redefine GFLOAT
DRIVER(27) - Remove GFLOATING microcode test (put into COMMAN)
GLOBAL(103) - Add F2, secondary switch word; remove GFMCOK
770 EGM 20-May-80 29339
Make the code to move simple assignments out of DOs work. This also
allows detection of uninitialized variables from assignments that
appeared in DO loops.
Modules:
MOVA(29)
771 EGM 29-MAY-80 14108
Fix yet another case of mistaken STATEMENT FUNCTIONS causing the
compiler to die.
Modules:
STA3(63)
772 EGM 5-Jun-80 29516
Generate fatal error when variable used as an adjustable dimension is
later found to be dimensioned itself.
Modules:
DOXPN(84)
773 EGM 12-Jun-80 14234
Keep expressions such as X+.R and Y=.R from moving outside the DO
loop after reduction in strength.
Modules:
TSTR(56)
774 EGM 12-Jun-80 14244
For READ *,K,(X(L,K),L=1,2), keep expressions involving K from being
common subed and moved off the I/O stmnt node. Addition to edit 731.
Modules:
IOPT(58)
775 EGM 17-Jun-80 10-29566
Make sure .O propagation walks all the stmnt. nodes on the second and
subsequent passes.
Modules:
PNROPT(154)
776 EGM 20-Jun-80 10-29609
Eliminate ICE during register substitution for statements of the
form IF()CALL ....
Modules:
PH3G(252)
777 EGM 27-Jun-80 -----
Eliminate bogus syntax error when parsing I/O unit spec. which is an
array reference. Example: READ(I(1),20)K. Edit 751 must be installed
for this error to occur.
Modules:
ACT0(56)
1000 EGM 27-Jun-80 10-29620
Flag error if no name appears on a PROGRAM statement
Modules:
STA2(48)
1001 EGM 30-Jun-80 -----
Rework product build command files. Eliminate references to obsolete
software and make handling of SCAN, WILD, and HELPER easier.
Modules:
COMMAN(102)
1002 TFV 1-Jul-80 ------
Add a new structure EVALTAB for the lookup of argtype codes
for argblock entries
Modules:
CGDO(145) CGSTMN(135) DEBUG(40) TABLES(161)
1003 TFV 1-JUL-80 ------
Add global symbol ..GFL. to REL block if compiled /GFLOAT.
Use binds for processor and compiler ids in REL block
Modules:
LISTOU(69) OUTMOD(79)
1004 TFV 1-Jul-80 ------
Fix library function handling to choose the 'Dxxxxx' or 'Gxxxxx'
routines for DP based on /GFLOAT
Modules:
EXPRES(35) GNRCFN(34)
1005 TFV 1-Jul-80 ------
Fix OPENCLOSE to handle unit specs without the unit=
Modules:
ERROUT(46) STA1(69)
1006 TFV 1-Jul-80 ------
Remove copies of KISNGL from CGEXPR.BLI and OUTMOD.BLI putting
one copy in UTIL.BLI (where it belongs). Fix immediate real
constants printed in listings. Give warning for constant
overflows. Add code for specops (p2mul, p2div, p21mul) for
real and DP numbers.
Modules:
CGEXPR(74) CNSTCM(69) FLTGEN(100)
OUTMOD(80) UTIL(89)
1007 EGM 6-Aug-80 10-29681
Prevent PUTBAK from clobbering random words and pointers when attempting
to do common sub replacement for a DATACALL I/O list node.
Modules:
IOPT(59)
1010 EGM 12-Aug-80 10-29839
Allow definition point detetction to happen for NAMELIST elements.
Modules:
DEFPT(123)
1011 DCE 7-Sep-80 -----
Allow TESTREPLACEMENT in implied loops (fix edit 577)
Modules:
TSTR(57)
1012 DCE 7-Sep-80 -----
REDUCE needs to be careful about non-integer SPECOPs.
Modules:
TSTR(58)
1013 DCE 14-Oct-80 -----
If end-of-statement causes syntax error, get error msg right.
Modules:
INOUT(46)
1014 TFV 27-Oct-80 Q10-04556
Allow list directed rereads, making reread just like ACCEPT, TYPE, etc.
Modules:
STA1(70)
1015 TFV 27-Oct-80 Q10-04743
FMT= is not optional for type, accept ,reread, etc.
Modules:
STA1(71)
1016 TFV 27-Oct-80 Q10-04759
Report names for misspelled OPEN/CLOSE parameters
Modules:
STA1(72)
1017 TFV 27-Oct-80 Q10-04733
Fix IOSTAT processing in OPEN/CLOSE
Modules:
STA1(73)
1020 TFV 27-Oct-80 Q10-04575
Add synonms for PDP-11 FORTRAN compatibility to OPEN/CLOSE.
INITIALSIZE= - FILESIZE=
NAME= - DIALOG=
TYPE= - STATUS=
Also fix ERR= processing. Only allow ERR=label.
Modules:
STA1(74)
1021 TFV 27-Oct-80 Q10-04502
Fix E0, E2, and E3 to read found when expecting ... (Remove 'a'.)
Modules:
ERROUT(47)
1022 TFV 27-Oct-80 ------
Preserve bit patterns for octal and literal assigned to real under
GFLOATING. Rounding the DP value to SP destroys the pattern.
Modules:
PNROPT(155)
VLTPPR(46)
1023 DCE 6-Nov-80 -----
Fix optimizer so that we get ELISTS and SLISTS again. Reduction
in strength for variables of type INDEX was not happening.
Modules:
TSTR(59)
1024 SRM 21-NOV-80 -----
Fix REGCLOBB to handle assignments of the form: REAL='literal'
when compiling /gfl. REGCLOBB had assumed that if the first
half of a literal was in an AC the second half must be in an
adjacent AC. Edit 1022 changed this for /gfl, by not "converting"
literals to real.
Modules:
ALCBLO(60)
1025 TFV 21-Nov-80 ------
Fix conversion of reals to logical under GFLOATING.
Just taking the high order word losses.
Modules:
CNSTCM(70)
1026 DCE 24-Nov-80 -----
Poor checking for I/O dependeicies in I/O lists (bad routine name)
Modules:
SKSTMN(95)
1027 DCE 25-Nov-80 -----
Add various definitions for V7 DO loops
Modules:
TABLES(162)
1030 TFV 25-Nov-80 ------
Fix GFLOATING DP to INT conversion (use GFIX not GFIXR).
Also leave an edit history for the ERR=label fix to OPENCLOSE
Modules:
CNSTCM(71) STA1(75)
1031 TFV 25-Nov-80 ------
Fix ABS for GFLOATING constants. Use DABS since low word has significance
When folding relationals, chose low or high word of each constant
based on VALTP1 since octals are not converted to real under GFLOATING.
Modules:
CNSTCM(72) P2S1(64)
1032 EDS 1-Dec-80 10-30251
When processing DATA statements free up the space used by constant
sets, constant options and repeat lists.
Modules:
STA1(76)
1033 DCE 4-Dec-80 -----
Expand size of DO node to include DOZTRLABEL
Modules:
FIRST(137)
1034 DCE 4-Dec-80 -----
Do Def points better for F(G(X)) - X may change...
Modules:
DEFPT(124)
1035 DCE 10-Dec-80 -----
Put out count for calls to .IOLST - add COUNTARGS routine.
Modules:
CGSTMN(136)
1036 DCE 31-Dec-80 QAR-1348
Fix edit 1007 to make ALL backpointers availible - even those
in innermore loops. This makes insertion of the IOLSTCALL
node correct in the more obscure cases.
Modules:
IOPT(60)
1037 EDS 29-Dec-80 10-30396
Initialize LOGICAL variables in assignment statements when
dependent on relational expression.
Modules:
CGEXPR(75)
1040 EDS 8-Jan-81 20-15381
Fix EXPRTYPER to step through NEGNOT nodes when deciding
if type conversion nodes are needed.
Modules:
VLTPPR(47)
1041 DCE 14-Jan-81 -----
Fix I/O Optimizer bug where ((A(I),I),J=1,2) does not know
that A(I) can depend on I (in a READ statement)
Modules:
IOPT(61)
1042 TFV 15-Jan-81 ------
Prohibit list directed encode/decode.
Modules:
STA1(77)
1043 EGM 19-Jan-81 20-15466
Add 'Consecutive arithmetic operators illegal' warning.
Modules:
COMMAN(103), ERROUT(48), EXPRES(36), INOUT(47)
1044 EGM 20-Jan-81 20-15467
Add fatal error 'XXXXXXX type declaration out of order'
for the case where executable code preceeds such a statement.
Modules:
DRIVER(28), CODETA(3), ERROUT(49)
1045 TFV 20-Jan-81 -------
Fix OPENCLOSE so ERR= literal, etc. doesn't break label processing.
NONIOINIO and LOOK4LABELS were not being reset.
Module:
STA1(78)
1046 EGM 23-Jan-81 --------
Replace edit 1040 to handle all cases of negated DP .boolean. DP.
Module:
VLTPPR(48)
1047 EGM 22-Jan-81 Q10-05325
Add support for TOPS-10 execute only.
Modules:
EXOSUP(1), COMMAN(104), MAIN(30), DRIVER(29), PH2S(31),
PHA2(113), PH3G(253), P3R(50), PHA3(53), LISTNG(25), UNEND(6)
Plus all the .CMD files and .CTL files
1050 EGM 6-Feb-81 --------
Fix incorrect graph for a program containing an arithmetic IF where all
3 branchs go to the same label. Also, in that case, retain the IF
expression if there are any function calls in it.
Module:
SKSTMN(96)
1051 EGM 9-Feb-81 --------
Global register allocator does not always note that a DO loop index has
been globally allocated. Also, do not do global allocation on a loop
containing alternate returns from routines.
Module:
PH3G(254)
1052 EGM 9-Feb-81 --------
Correct graph for extended range range brach out of inner DO to
main code, to terminus of inner DO.
Module:
GRAPH(130)
1053 EDS 11-Feb-81 --------
Make FORTRA a global symbol.
Module:
COMMAN(105)
1054 DCE 12-Feb-81 -----
Fix bug with common subs and non-existant parent pointer (/OPT only)
Module:
P2S2(58)
1055 DCE 24-Feb-81 -----
Fix bug in HAULASS where assignment stmnts moved when they shouldn't
Module:
MOVA(30)
1056 DCE 3-Mar-81 -----
Stick type conversion node beneath .NOT. node when necessary
to prevent awkward register allocation problems to odd registers.
Module:
EXPRES(37)
1057 EDS 10-Mar-81 Q20-01410
Check the initial value and upper limit when looking for the index
variable in I/O optimizations.
Module:
TSTR(60)
1060 DCE 6-Apr-81 -----
Fix bug with const*negative-power-of-two (constant folding)
Module:
PNROPT(156)
1061 DCE 15-Apr-81 -----
Add warning for # used in random access.
Modules:
ERROUT(50),COMMAN(106),INOUT(50),ACT0(57)
1062 EDS 15-Apr-81 10-30950
Fix special case of SPECOP producing incorrect code. The case
of I=-1*I**2 should not be computed to memory.
Module:
MEMCMP(30)
1063 DCE 23-Apr-81 QAR5631
Add error detection for jumps into loops with no exits.
Modules:
GRAPH(131) ERROUT(51) ERROVD(6)
1064 EDS 28-Apr-81 Q20-01483
Replace edit 1037. Incomplete code generated for logical
assignment statement. Bad code generated during optimization.
Modules:
CGEXPR(76) REGAL2(149)
1065 EGM 13-May-81 Q10-05053
Replace SCAN specific error macros with parallel ones tailored for
FORTRAN. Eliminates ICEs after errors, and strange ? FTNXXX prefixs.
Module:
COMMAN(107)
1066 EGM 13-May-81 Q10-05202
Eliminate LINE:xxxxx in error messages where not pertinent.
Modules:
DRIVER(30) ERROUT(52) ERROVC(5) ERROVD(7)
ERROVG(6) ERROVR(4) GRAPH(132) INOUT(51)
PHA2(114)
1067 EDS 13-May-81 31074
Do not allow register 1 to be made available for a statement if
common subexpressions have already been allocated in it.
Module:
STREGA(224)
1070 CKS 14-May-81
(turned into 1453)
1071 CKS 22-May-81
Remove TAPEMODE from OPEN/CLOSE parameter plit
Modules: STA1(79)
1072 CKS 22-May-81
Remove %Consecutive arithmetic operators illegal until it can be
put under flagger switch
Modules: EXPRES(38)
1073 DCE 22-ay-81 -----
Fix ORERROR so that REAL+ gives reasonable error msg.
Modules: FAZ1(36)
1074 SRM 27-May-81
Fix problems with folding logical IF's that have A1NOTFLG set.
The NOT was being ignored for REAL and DP expressions.
Modules: P2S2(59)
PNROPT(157)
1075 EGM 28-May-81 --------
Add GFL equivalent functions for IDINT and SNGL.
Module: GNRCFN(35)
1076 TFV 8-Jun-81 ------
Allow list-directed reads and writes without an iolist.
Modules:
CGSTMN(138) STA0(54) STA1(81)
1077 AHM 8-Jun-81 -----
Put in missing JFCL after GETPPN uuo in GETPPN routine.
Modules:
BLIO(1)
1100 EDS 9-Jun-81 20-31141
Add new error messages and make a statement label
definition entry even if an ENF error (E91) should occur.
Modules:
LEXSUP(16) ERROUT(53)
1101 EGM 12-Jun-81 QAR10-05209
ELiminate bad placement of CSSE initialization when expression
containing CSSE immediately follows a DO loop.
Module:
GCMNSB(110)
1102 CKS 18-Jun-81 -----
Make .not.(-(-(.not x))) work. NOTOFNEG and NEGOFNOT were not
noticing the NEGFLG and NOTFLG returned by the expression under them.
Modules:
P2S2(60)
1103 EGM 23-Jun-81 QAR20-01439
Eliminate bad code for LOGICAL=double-word assignments. Also,
make REAL=COMPLEX as efficient as the code intended.
Module:
VLTPPR(50)
1104 EGM 25-Jun-81 --------
Eliminate bad code during optimization constant propagation. Negs
in assignments were not being carried with the constants.
Modules:
PNROPT(159)
1105 DCE 26-Jun-81 -----
Addition to edit 1063. For nested loops, be sure that the loop
label keeps a correct label count within LABLADJUST.
Modules:
PHA2(115)
1106 EGM 29-Jun-81 --------
Correction to edit 1103. Restrict the REAL=COMPLEX check to only
COMPLEX variables (not for instance, functions) to agree with what
the register allocator expects. Eliminates bad code.
Module:
VLTPPR(51)
1107 TFV 14-Jul-81 ------
Give an error for the illegal constants 0H and ''. They are prohibited
by the 77 standard. The compiler used to build 0H as a word of nulls
and '' as a a word of spaces followed by a word of nulls.
Modules:
ERROUT(56) LEXICA(30)
1110 EGM 15-Jul-81 --------
Addition to edit 773. Do not consider implied DOs, when modifying the
'variables changed in the DO' list.
Module:
TSTR(61)
1111 EDS 15-Jul-81 10-31190
Fix optimizer bug so that ((A(J,K),J=1,2,I),K=1,2,I) with I in
common does not create a common subexpression which is only used
once. The CSE would be allocated to a register and ALCIOLST
would re-allocate the register.
Module:
IOPT(63)
1112 DCE 17-Jul-81 -----
Fix edit 1063 so that graphing does the right thing by local label
counts for nested DO loops with inner references to outer labels.
Module:
GRAPH(134)
1113 CKS 17-Jun-81 -----
Fix code motion bug; don't put a CSE calculation after a statement
which has more than 1 successor. (A statement with more than 1
successor has no "after".) To do this, for any statement that has
more than 1 successor, set ACC bits for each variable that the
statement modifies in the statement's postdominator and each successor.
Modules:
DEFPT(125)
1114 CKS 22-Jun-81
Set up R2 in STA0, prevents random "?FTNNIO Namelist directed I/O
with I/O list" messages
Modules:
STA0(45)
1115 EGM 30-Jul-81 --------
Rework /NOWARn selectivety for expandibility and maintainibility.
Supercedes edit 723, alters edits 741,766,1061,1063.
Modules:
COMMAN(109) INOUT(52) ERROVA(3) ERROVC(6)
ERROVD(8) ERROVG(7) ERROVR(6)
1116 JLC 26-Aug-81
Rework FLTGEN to be more correct, and compatible with FLIRT.
Modules:
FLTGEN(101)
1117 EGM 26-Aug-81 --------
Eliminate fixed high seg origin and other restrictions for TOPS-10 EXO.
Modules:
COMMAN(110) MAIN(31) EXOSUP(2)
1120 AHM 9-Sep-81 Q10-06505
Fix edit 735 by always clearing a flag so that the
"EQUIVALENCED VARIABLES" header is produced again.
Module:
OUTMOD(86)
1121 EGM 9-Sep-81 --------
Add GETTABs to determine full path and device for GETSEGs
Modules:
COMMAN(111) GLOBAL(113)
1122 EDS 22-Sep-81 10-31589
Fix PRIMITIVE to detect invalid complex expressions.
Module:
EXPRES(40)
1123 AHM 24-Sep-81 Q20-01650
Make IOSTAT= work for arrays, formals and registers.
Modules:
STREGA(226) CGSTMN(140)
1124 AHM 24-Sep-81 Q20-01651
Make the compiler realize that IOSTAT= and ASSOCIATEVARIABLE= alter
formals so that they are stored at subprogram epilogue.
Module:
STA1(84)
1125 DCE 24-Sep-81 -----
Fix up local label counts one more time so that we can better
detect jumps into loops. Catch the more obscure cases.
Module:
GRAPH(135)
1126 AHM 24-Sep-81 Q20-01654
Remove last vestiges of CALL DEFINE FILE support.
Modules:
LEXICA(34) GOPTIM(55) DEFPT(126)
1127 AHM 24-Sep-81 ------
Change erroneous (and potentially dangerous) use of IDTARGET
to TARGADDR in ARRNARGBLK.
Module:
CMPLEX(139)
1130 AHM 25-Sep-81 Q20-01647,Q20-01648
Fix bad Y field reference in PEEP02 by changing
PEEPPTR[0,PBFSYMPTR] to PEEPPTR[0,PBFADDR].
Also insert missing dot before PEEPPTR[1,PBFSYMPTR]
in macro PRVNONEQNXT.
Module:
PEEPOP(78)
1131 AHM 25-Sep-81 Q20-01671
Check for storing before the first word of an array in DATA
statements since we already check for storing after the last word.
Module:
DATAST(52)
1132 AHM 25-Sep-81 Q10-06347
Change E150 (edit 1061) to refer to REC= as well as '.
Also, make the entries in the DUMDUM plit in ACT1 have mixed case.
Modules:
ACT0(61) ACT1(127) ERROUT(63)
1133 TFV 28-Sep-81 ------
Add /STATISTICS flag for in-house performance measurement. It is
disabled in the released V6.
Modules:
COMMAN(113) GLOBAL(115) IOFLG(16)
LISTNG(26) OUTMOD(87) SRCA(53)
UNEND(7)
1134 EGM 1-Oct-81 10-31654
Eliminate bad code produced for READ/WRITE/FIND with both a subscripted
record unit number and record number, where a record number subscript
has been left in an AC prior to the I/O statement. Also expand edit
376 to include FIND.
Module:
CGSTMN(142)
1135 RVM 15-Oct-81
Make conversion from DOUBLE PRECISION to COMPLEX do rounding.
Module:
OPGNTA(127)
1136 AHM 19-Oct-81
Make graphing know about END= and ERR= for lots of I/O statements.
Also make global label ref counts correct for END=/ERR=.
Modules:
ACT1(128) GRAPH(136)
1137 DCE 20-Oct-81 -----
Fix looping optimizer for inaccessible DO stmnt with jumps
into the loop.
Modules:
GRAPH(137)
1140 DCE 21-Oct-81 -----
Same as 1137, but for nested inaccessible loops where only the inner
loop has an entrance (outer loop does not get HASENT set).
Modules:
GRAPH(138)
1141 EGM 27-Oct-81 10-31686
Produce diagnostic when more than 24 significant digits in an octal
constant.
Module:
LEXICA(36)
1142 EGM 28-Oct-81 Q10-06254
Eliminate ICE for an IO list complex enough to require more than 63
registers (64 single precision array references, for example).
Module:
STREGA(229)
1143 AHM 13-Nov-81
More of edit 1136 to make "data transfer" statements work as well as
"device control" statements. Delete code in IODOXPN that incremented
the reference count for labels used in END= and ERR= in "data
transfer" statements. BLDKEY now references those labels correctly.
Module:
DOXPN(88)
1144 EGM 11-Nov-81 Q10-06632
Eliminate obscure problems and ICEs when optimizing, and hash table
is such that the last hash entry found in the table for a loop is for
an array ref, and the actual expression using that array ref now points
to the hash table. eliminates unwanted calls to NEWCOPY.
Module:
GCMNSB(111)
***** Begin Version 6A *****
1145 EGM 7-Dec-81 10-31836
Eliminate bad code produced when the register allocator is forced to
target an arithmetic expression computation to memory, after the
complexity pass has targeted the expression to the function return
register. Also make sure that nodes computed to memory are not
expected to have also left the proper result in the AC used for the
computation.
Module:
REGAL2(153)
1146 EGM 5-Jan-82 20-17060
Report correct ISN when giving errors for EQUIVALENCE conflicts.
Module:
OUTMOD(97)
1147 EGM 5-Jan-82
Eliminate bogus error message and ICE for RETURN^Z.
Module:
DRIVER(36)
1150 DCE 16-Feb-82 20-17292
When optimizing, one may get incorrect error messages if there
are ASSIGN statements to labels which occur within loops.
The error message will always be: Illegal Transfer into loop...
Modules:
FIRST(154) STA0(70) GRAPH(139)
1151 EGM 25-Mar-82 20-17494
Report ?Program too large for COMMON 512P or larger
Module:
OUTMOD
1152 EGM 29-Mar-82 10-32187
Check all OPEN/CLOSE parameters for possible register substitution
when doing global register allocation. Expansion of edit 740.
Module:
PH3G
1153 EGM 3-Jun-82 20-17625
Programs containing many I/O statements that compiled under previous
versions may now run out of memory. Augment edit 760 to release syntax
list items when they are no longer needed.
Modules:
ACT1 STA0 STA1
(Note: This edit was not put into version 7. It was supplanted
by V7 edit 1550. SRM)
1154 EGM 3-Jun-82 10-32488
Correct bad code generated for I=-(.NOT.(boolean)). Prevent compute to
memory happening for expression node if neg/not driven up.
Module:
MEMCMP
(Note: This edit was not put into version 7. The problem had
already been fixed by V7 edit 1426. SRM)
1155 EGM 9-Jun-82 20-17790
Allow declarartion semantics checking to continue checking items after
the first error occurs.
Module:
ACT1
1156 EGM 10-Jun-82 None
Eliminate stack overflow when trying to print out error that expression
is too complex.
Module:
EXPRES
(Note: This edit was not put into V7. It was fixed by V7
edit ???. SRM)
1157 EGM 11-Jun-82 20-17871
Alter error message FTNMVC to indicate that there are more or less
data items than constants in a DATA statement.
Modules:
DATAST ERROUT ERROVR
1160 EGM 14-Jun-82 20-17877
Correct edit 752 and make sure .REL files are discarded when any
fatal errors occur during a compile command. Also make 20 code
skip .REL file generation when systax checking as the 10 code does.
Modules:
COMMAN INOUT UNEND IOFLG
1161 EGM 25-Jun-82 10-32686
Prevent bad code when optimizer has globally allocated a var to live in
a reg, and assignments to the reg occur that involve use of the reg on
the RH such that the calc cannot occur directly to the reg (does not
clobber reg state entry).
Module:
STREGA
1162 PY 29-Jun-82 None
Allow ^Z as first character of source typed from the TTY. Make
^Z give free CRLF on TOPS-20. Also replace obsolete RDTXT JSYS
with TEXTI. Clear freelist pointers in case first call to LEXICAL
generates an error. Clear .JBFF through .JBREL so TTY input will
not appear to have line sequence numbers.
Modules:
DRIVER LEXICA LISTNG
1163 TGS 1-Jul-82 20-17540
If /DEBUG:INDEX is specified, bypass optimization that substitutes
a regcontents node using the function return register for the left-
hand side of an assignment statement to the function variable.
Module:
DOALC
1164 EGM 12-Jul-82 20-17819
Eliminate possibility of certain nested DO loops throwing the grapher
into a loop.
Module:
GRAPH
1165 CDM 29-Sept-82 SPR: 10-33034
2ND argument to ADDLAB had to be corrected in routine POPT11.
[This was fixed by edit 1635 in V7.]
Module:
PEEPOP
1166 CDM 9-Dec-82 10-33208
Enlarge RDCLST by 1 element to 19, since BLISS starts counting at
0, not 1.
1167 TFV 11-Jan-83 20-18247
Fix LOOKELEM2 to check E1/E2LISTCALLs to see if the count or
increment depend upon previous iolist elements. Fix CONTVAR
code for E1/E2LISTCALLs and make it handle arrayrefs properly.
***** Begin Version 7 *****
1200 DCE 28-APR-80 NONE
Establish revision history for version 7
Module:
REVHST(1200)
1201 DCE 19-JUN-80 -----
Add new keywords - CHARACTER, ELSE, ENDIF, THEN, INQUIRE, INTRINSIC,
SAVE.
Module:
CODETA(4)
1202 DCE 1-JUL-80 -----
Add substantial code for expressions on output lists. The main
work is in ACT1 where several new low-level routines are introduced.
The BNF also needs to be changed, so many of the low-level routines
need to be recompiled as well.
Modules:
F72BNF(1) - Change the BNF for expressions on output lists
ACT1(120) - Add semantics processing routines for the same
EXPRES(39) - NOLPAR action routine to assist
CMPLEX(136) - To allocate constants
STA0(51) - Add appropriate calls to LISTIO
STA1(80) - Add appropriate calls to LISTIO
Modules recompiled: CODETA,FAZ1,STA2,STA3
1203 DCE 24-Nov-80 -----
More work for I/O lists. Change the entire approach (largely due to
complex constants). Add substantial code to EXPRES where we have
interwoven I/O lists.
Modules:
F72BNF(2) - Change I/O lists to use NOTEOL and GIOLIST
ACT1(121) - Changes to CCONST (especially for GFL)
EXPRES(40) - Put I/O list processing in with expression parsing
GLOBAL(104) - Make CONTROL type come out as LOGICAL for arg list
STA0(52) - Change calls to LISTIO
Modules recompiled: CODETA,FAZ1,STA2,STA3
1204 DCE 25-NOV-80 -----
Begin work on zero trip loops. Modify the trip count calculation
to conform to F77 standard. Preserve F66 behavior under F66 switch.
Module:
DOXPN(85)
1205 DCE 20-Mar-81 -----
Make the F66 and F77 switches available - make F77 the default.
Module:
COMMAN(108)
1206 DCE 20-Mar-81 -----
More work on zero trip loops. Add code generator to jump around
a potential zero trip loop, add code to produce final loop value
for both real and implied (ELIST) loops.
Modules:
OPGNTA(124) - DOZJMP code generator
CGDO(146) - Real DO loop code
CGSTMN(137) - ELIST code
1207 DCE 3-Apr-81 -----
Work on I/O optimizations and the materialization of final loop
values when an ELIST/SLIST is generated by the optimizer. Catch
all the new dependencies introduced by the FORTRAN standard.
Modules:
IOPT(62),SKSTMN(97)
1210 DCE 6-Apr-81 -----
For ELISTs, do regsubstitution into the assignment statements
created to establish final loop values.
Modules:
UTIL(90)
1211 DCE 29-Apr-81 -----
Do complexity analysis for final loop value assignments (ELISTS).
Module:
CMPLEX(137)
1212 TFV 29-Apr-81 ------
Add compile time data structures for CHARACTER data. Replace LITERAL
with HOLLERITH where appropriate.
Modules:
ACT1(122) ALCBLO(61) DATAST(47) ERROUT(53)
FIRST(140) GLOBAL(105) LEXSUP(14) PNROPT(158)
TABLES(163) VLTPPR(49)
1213 TFV 20-May-81 ------
Add character declaration syntax and semantics. Fix BLDDIM to compute
array size, array offset, and factors in characters for character data.
Add code to handle IMPLICIT CHARACTER*n.
Modules:
ACT0(58) ACT1(123) DRIVER(31) FIRST(141)
GLOBAL(106) LEXICA(28) STA2(49) STA3(64)
ASHELP(5)
1214 CKS 20-May-81 ------
Add IF-THEN-ELSE
Modules:
LEXICA(27) CODETA(5) STA3(65) STA2(50)
ERROUT(54) GLOBAL(107) DRIVER(32) ACT1(124)
1215 DCE 22-May-81 -----
Fix MASK to handle more BNF possibilities (especially exprs in I/O lists).
Modules:
FAZ1(37)
1216 DCE 28-May-81 -----
Add F77 SLIST and ELIST (zero trip) entries into TABLES.
Modules:
TABLES(165)
1217 DCE 28-May-81 -----
All null argument lists in CALL statements.
Modules:
STA0(53), ACT0(59)
1220 DCE 2-Jun-81 -----
Allocate registers for assignment statements to DO variables,
and temps for fn calls as I/O elements.
Modules:
STREGA(225)
1221 CKS 4-Jun-81 -----
ASCII literals are funny since the new expanded literal node format.
Too much code uses hardwired offsets into the node. Use symbols
instead.
Modules:
FIRST(142), LEXICA(29), LEXSUP(16)
1222 CKS 8-Jun-81
Make CONST1 equal LIT1 by moving CONST1 and CONST2 down a word.
Much code depends on CONST1 and LIT1 being equal.
Modules:
FIRST(143)
1223 DCE 9-Jun-81 -----
Make special calls to FOROTS for F77 ELISTS and SLISTS.
Modules:
CGSTMN(139)
1224 CKS 12-Jun-81 -----
Fix LITSIZ calculation; make it independent of the size of the literal
node header. Have the listing routine output the whole asciz literal,
not just the first 2 words.
Modules:
LEXSUP(18) LISTOU(71) STA2(51)
1225 CKS 17-Jun-81 -----
Converted to edit 1113.
1226 SRM 19-Jun-81
Changed order of search in REGCONTAINING so that if variable
is in both AC 0 and another AC it will return the other one.
Modules:
ALCBLO(62)
1227 CKS 22-Jun-81
Define CONST2L to be left half of CONST2, change CW4L in CGDO to
CONST2L.
Modules:
FIRST(145) CGDO(147)
1230 CKS 22-Jun-81
Converted to edit 1114.
1231 CKS 23-Jun-81
Remove edit 1226. It results in double word quantities in (N,N+1)
being "found" in (N+1,N+2).
Modules:
ALCBLO(63)
1232 TFV 24-Jun-81
Fix ALLSCAA and ALCCON to handle character data and character
constants. Output character data to the .REL file; output the
descriptors to the low seg for dummy args, to the high seg for
non-dummy arg character data. Add CHDECL to test whether a character
declaration or an implicit character declaration was scanned in FORTB.
If not, don't walk the symbol table to generate high seg descriptors.
Also add a new section to the .LST file for character data. List
character variable and array names, descriptor locations, location and
character position for the start of the data, and the length of the
data.
Modules:
ACT0(60) GLOBAL(108) OUTMOD(81) P3R(51)
PH3G(255) REQREL(1) STA2(52)
1233 CKS 25-Jun-81
Make optional comma in "READ(1), X" work again. The problem is
complex; see comments in STA0. Add action routine OPTCOMMA,
slightly change expected shape of syntax tree in RWBLD, BLDIO1,
BLDEDCODE.
Modules:
F72BNF(8) STA0(56) STA1(82)
1234 CKS 1-Jul-81
Removed.
1235 CKS 1-Jul-81
Add action routine ERREOL to type an error message for "TYPE *,".
Without this routine, that statement does not parse or generate code,
but does not get an error message either. NOTEOL is called, decides
that no IO list is present, and returns failure expecting the parser
to go on to another alternative. There is no alternative in the TYPE
statement's production.
Modules:
F72BNF EXPRES(41)
1236 SRM 15-July-81
Made DATAST treat initialization of numeric variables with
character constants like initialization of numeric variables
with hollerith
Modules:
DATAST(50)
1237 CKS 20-Jul-81
Change text of error message E75 to 'entry illegal in range of block IF
or DO loop'
Modules:
ERROUT(57)
1240 CKS 28-Jul-81
Add BPADD macro. BPADD(BYTE-POINTER,NUM) is BYTE-POINTER incremented
NUM times. Generates an ADJBP instruction.
Modules:
TABLES(167)
1241 CDM 29-Jul-81
Add Version 7 Instrinsic functions to compiler tables in
GNRCFN. Also added more functions to be generic, and changed
1 line to correctly get /GFLOATING dotted names for functions
in MAKLIBFN (in GNRCFN).
Modules:
GNRCFN(36) GLOBAL(110)
1242 CKS 29-Jul-81
Allow initialization of character variables in DATA statements
Modules:
DATAST(51) RELBUF(31) ERROUT(58) ERROVR(5)
ACT1(126)
1243 CKS 30-Jul-81
Add lexeme CONCAT, the // concatenation operator
Modules:
LEXNAM(1) EXPRES(42) TABLES(168) LEXSUP(20)
1244 CKS 2-Aug-81
Make EXPRES parse substring references and concatenation expressions
Modules:
EXPRES(43) LEXICA(31) ERROUT(59)
1245 TFV 3-Aug-81 ------
Add ISHISEGADDRESS to symbol table entries. Character data descriptors
are HISEG locations; bad code was being generated. Fix allocation for
temporaries. ALCTEMP becomes ALCAVARS; ALCTMPS becomes ALCQVARS.
Change LEXICA to build nHccc as a HOLLERITH constant and 'ccc' as a
CHARACTER constant. Fix OPENCLOSE to convert character constant args
to HOLLERITH for now. Cleanup remainder of code from edit 1232.
Modules:
ACT0(60) ACT1(126) DOALC(110) FIRST(146)
GLOBAL(111) LEXICA(32) LEXSUP(19) LISTOU(72)
OUTMOD(82) P3R(51) PH3G(255) REQREL(1)
STA1(83) STA2(52) TABLES(169) VER5(7)
1246 CDM 3-Aug-81 ---
Edited SUBPROGLIST so that inline function names are not output to
listings.
MODULES: OUTMOD(81)
1247 CKS 6-Aug-81
Modify classifier to recognize substring assignments. Add SUBASSIGN
semantic routine to parse them and call MULTIASGN.
Modules:
LEXICA(33) CODETA(6) STA0(57)
1250 CKS 7-Aug-81
Modify the semantic routines to support character arrays. Have ARRXPN
put in an explicit + node to add the constant part of the subscript
expression in rather than put it in TARGET so an index calculation can
add it at runtime. Have ADJGEN call ADJC1. and ADJCG. instead of ADJ1.
and ADJG. Have BLDDIM generate a .I temp for ADJCx. to fill in with
the first dimension multiplier. Change PROAR. to PROTA. so it can be
modified to support CHARACTER arrays.
Modules:
ACT1(125) ARRXPN(54) DOXPN(86)
1251 CKS 7-Aug-81
Add code generation template for char array index calculation.
Change IBP to ADJBP in instruction op table.
Fix typeout of address as name+offset to handle highseg addresses
Modules:
CGEXPR(77) OPGNTA(125) OPTAB(3) LISTOU(73)
1252 CDM 10-Aug-81
Added inline generic functions with unique dotted names (which users
can't accidentaly call). Also edited MAKLIBFN so that CMPLX for
1 or 2 arguments works.
Modules:
GLOBAL(112) CNRCFN(37) TABLES(170)
1253 CKS 11-Aug-81
Do register allocation for character arrayrefs. Complexity is the same
as numeric arrayrefs but don't ADDREGCANDIDATE the subscript. Add
ALCCHARRAY to do register allocation. ALCCHARRAY knows that the
index register will be clobbered by the ADJBP. It also allocates a .Q
temp to hold the descriptor resulting from the ADJBP. Modify REA to
not common-sub a scalar subscript of a character array. Teach ARGGEN
about the format of character array ref nodes.
Modules:
CGDO(148) CMPLEX(138) COMSUB(271) REGAL2(150)
1254 CKS 15-Aug-81
Make MULTIASGN convert char=char assignments to CALLs of CHASN. or
CONCA. Check that numeric and character data aren't assigned to each
other (but allow numeric='char const').
Modules:
STA0(58) ERROUT(60) VLTPPR(52)
1255 TFV 17-Aug-81 ------
Fix LOGEXPRESSION and VLTPPR to handle character relationals. Turn
them into library calls to CH.xx (EQ, NE, GT, GE, LT, LE). Fix
expression processing to turn character constants into holleriths in
numeric expressions and prohibit all other combinations of numeric
and character data.
Modules:
EXPRES(44) VLTPPR(53)
1256 CKS 8-Sep-81
The concatenation lexeme breaks common statements of the form
COMMON / / X
where the // denotes blank common. Modify the COMMONGROUP
production to allow a concatenation lexeme as well as slash
lexemes. Modify COMMSTA to read the new tree format.
Modules:
LEFT72(24) F72BNF(9) STA2(53)
1257 TFV 10-Sep-81 ------
Fix LITOR6DIGIT to convert character constant args to hollerith.
This fixes STOP/PAUSE 'foo'.
Module:
STA0(59)
1260 CKS 14-Sep-81
Prohibit character expressions in ASSIGN, computed and assigned GOTO,
and arithmetic, logical, and block IF statements.
Modules:
STA0(60) STA3(66)
1261 CKS 22-Sep-81
Allow character variables in COMMON and EQUIVALENCE.
Modules:
LISTOU(74) OUTMOD(83) STA3(67)
1262 CKS 22-Sep-81
Allow character substrings in EQUIVALENCE.
Modules:
ERROUT(62) ERROVR(6) EXPRES(45) F72BNF(10)
FIRST(147) OUTMOD(84) STA3(70)
1263 TFV 22-Sep-81 -------
Fix edit 1260 to allow the degenerate cases IF('ccc') ....;
GOTO (100,200,300), 'ccc'. These are certainly odd but legal
in Version 6.
Modules:
STA0(61) STA3(71)
1264 CDM 24-Sept
Added NOP type conversion functions (ie REAL(REAL)) and added
more functions to tables.
Modules:
EXPRES(46) GLOBAL(113) GNRCFN(38) OUTMOD(85)
P2S1(65)
1265 CKS 28-Sep-81
Add code to support character args in IO statements
Modules:
CGSTMN(141)
1266 TFV 5-Oct-81 ------
Add code to copy 1 or 2 words of descriptor for character formal
at subroutine entrance. Don't copy it back on subroutine exit.
Module:
CGDO(149) OPGNTA(126)
1267 AHM 6-Oct-81 ------
Define stub routines INQUSTA, SAVESTA and INTRSTA for the INQUIRE,
SAVE and INTRINSIC statements so we don't get undefined symbols
when linking.
Modules:
STA1(85) STA2(54) STA3(72)
1270 CDM 6-Oct-81
Added error/warning messages E169, E170, and made call to inline
type convert intrinsic function work for octal arguments /OPT.
Modules:
ERROUT(63) EXPRES(47) GLOBAL(116) PNROPT(160)
SRCA(54) TABLES(171)
1271 CKS 9-Oct-81
Add optional comma in DO statement
Modules:
F72BNF(11) LEXICA(35) STA3(73)
1272 RVM 15-Oct-81
Convert REAL constants from DOUBLE PRECISION, even if the
constant is part of a MOVEI.
Modules:
OUTMOD(88)
1273 CDM 15-Oct-81
Do not change function into inline if it has octal arguments.
(problem was with /OPT)
Module:
P2S1(66)
1274 TFV 16-Oct-81 ------
Rewrite NXTTMP to handle multiple word .Qnnnn variables. Also
rewrite ALCQVARS to output the .Qnnnn symbols to the .REL file
and to reserve the right amount of space for the .Qnnnn variables.
Modules:
ALCBLO(64) DOALC(111) GLOBAL(117) LISTOU(75)
OUTMOD(89) REGAL2(151) REGUTL(22) STREGA(227)
1275 CDM 20-Oct-81
Simple add to MAKLIBFN to check for library functions with no
arguments being illegal.
Module:
GNRCFN(42)
1276 DCE 21-Oct-81 -----
Only materialize final loop value if /F77
Module:
CGDO(150)
1277 CKS 21-Oct-81
Make GOTO I (10,20) parse as assigned GOTO with the optional comma
before the statement number list omitted rather than as an assigned
GOTO to a subscripted variable.
Modules:
F72BNF(12) STA0(62)
1400 CKS 21-Oct-81
Allow functions with null argument lists.
Modules:
EXPRES(48) ACT1(129) CGDO(151)
1401 AHM 22-Oct-81
Functionality for base level 1 of extended addressing.
Reworked the argument list generators ARGGEN and IOPTR.
Modified all code patterns that derive addresses to use XMOVEI
instead of MOVEI, especially subroutine calls, assigned GOTO,
subroutine prologue/epilogue code and array element address
generation. Defined XMOVEI in the macro listing opcode table
and OPDEFed it for debugging the compiler until DDT gets it.
Modules:
CGDO(152) CGSTMN(143) GFOPDF(1) OPGNTA(128)
OPTAB(4) TABLES(171)
1402 CKS 23-Oct-81
Allow declaration statements to be labeled. Do not allow such
labels to be referenced.
Modules:
FIRST(148) DRIVER(33) LEXSUP(21) STA3(74)
1403 AHM 26-Oct-81
Add support for "$" in symbols to routine RADIX50. Needed for
extended addressing development.
Module:
RELBUF(32)
1404 AHM/TFV 26-Oct-81 ------
Fix ALCIOCALL to agree with ALCIOLST in that IOLIST elements which
live in AC0 must be stored into a temp.
Module:
STREGA(228)
1405 DCE 27-Oct-81 -----
Defer label processing when necessary (do not do it twice!)
Module:
DRIVER(34)
1406 TFV 27-Oct-81 ------
Add handling for compile-time-constant character descriptors.
They are called .Dnnnn variables. They have an OPRCLS of
DATAOPR and an OPERSP of VARIABLE. Either one word (byte
pointer only) or two words (byte pointer and length) are
generated based on the flag IDGENLENFLG. One word .Dnnnn
variables are used for SUBSTRINGs with constant lower bounds and
non-constant upper bounds. The routine NEWDVAR generates them,
and HSDDESC outputs the descriptor to the hiseg of the .REL
file. Also create the macro BPGEN to generate byte pointers that
are output to the .REL file.
Modules:
FIRST(149) GLOBAL(118) LISTOU(76) OUTMOD(90)
P3R(52) PH3G(256) SRCA(55) TABLES(174)
UTIL(91)
1407 CKS 27-Oct-81
Fix BLDIOLSCLS so character constants put out DATACALLS not SLISTS
Modules:
ACT1(130)
1410 CKS 28-Oct-81
Support optional commas in COMMON and DATA. The commas in
COMMON A,/B/C
DATA A/1/, B/1/
are both optional.
Modules:
F72BNF(13) ACT0(62) ACT1(131) STA1(86)
1411 RVM 31-Oct-81
Edit 1272 caused the macro code listed for files compiled
with GFLOATING to be bad, but only if there was no object
file requested. This occured because the compiler knew
that ALCCON did not convert constants if there was to be no
REL file, and so would convert the constants when producing
the list file. Edit 1272 caused constants to be converted
twice, and thus equal zero.
Modules:
CGEXPR(78)
1412 CKS 4-Nov-81
Allow statement functions and common blocks to have the same name
Modules:
ACT1(132)
1413 CDM 4-Nov-81
Made changes to make the assignment of argument nodes use the
ARGUMENTLIST structure, and enlarged the header in that structure
to 3 words from 2. Also in STREGA made code not reference undefined
areas of nodes.
Modules:
ACT1(133) DOXPN(87) EXPRES(49) STA0(63)
STA3(75) STREGA(230) TABLES(173)
1414 RVM 6-Nov-81
Make CNVNODE preserve the bit patterns for logical expressions
compared to reals under gfloating. This fixes an bug that caused
IF (REAL .GT. LOGIC) STOP
to be evaluated incorrectly, particulary under /OPT.
Module:
VLTPPR(54)
1415 RVM 9-Nov-81
Preserve the bit pattern for logical constants that are propagated
under GFLOATING. This fixes the same type of problem as in edit
1414 when the logical expression is a constant that has been
propagated.
Module:
PNROPT(161)
1416 CKS 9-Nov-81
Add character substring references in DATA statements. Also
allow subscript and substring expressions to contain **.
Modules:
ACT1(134) ARRXPN(55) DATAST(53) F72BNF(14)
ERROUT(65)
1417 RVM 10-Nov-81
The wrong code template was used for conversion from LOGICAL to
GFLOATING and from CONTROL to GFLOATING. The template RLGF was
used, and thus the compiler would generate code to convert REAL
(9 bit exponent) to GFLOATING (12 bit exponent) and scramble
bits. The correct template is RLDP.
Module:
OPGNTA(129)
1420 RVM 11-Nov-81
Fix EXPRTYPER to really change the type of character constants
used with numeric expressions to HOLLERITH. The assignment
statements that were supposed to do this each had an extra dot
in front of the variable being assigned.
Module:
VLTPPR(55)
1421 CKS 11-Nov-81
Allow statement function definitions with zero parameters
Modules:
ACT0(63) F72BNF(15) STA3(76)
1422 TFV 12-Nov-81 ------
Change FUNCGEN and REFERENCE for character functions. They have
an extra argument for the result to be returned. It is the
first argument and has the descriptor for the result copied in
at function entry. The result is stored back by the character
assignments in the function body. Character functions do not
use AC0 and AC1, so ALCRETREGFLG is not set. Change CGEPILOGUE
so that character results are not moved into AC0.
Modules:
ACT1(135) CGDO(153) CMPLEX(140) EXPRES(50)
REGAL2(151)
1423 CKS 19-Nov-81
Don't allow character functions to initialize the function name in
a DATA statement.
Modules:
ACT1(136) ERROUT(66)
1424 RVM 19-Nov-81
Precede the formats in the object program by a count of the number
of words in the format (in other words, make formats look like
BLISS-10 PLIT's). This is needed for assignable formats.
Modules:
OUTMOD(91) LISTOU(77)
1425 CDM 28-Nov-81
Add @ to refernce of variable from STK; @.T1[ELMNT1]
Simplify REFERENCE in EXPRES so that it calls another function MAKEFN
to build function nodes. This uses less stack space, since REFERENCE
is recursive, and the compiler was running out of space.
Modules:
STA3(77) EXPRES(51)
1426 SRM 30-Nov-81
Do not do operations to memory if there is a NEGFLG or NOTFLG
in the statement node. (Fixes test program BB2502.FTP.)
Module:
MEMCMP(32)
1427 CKS 2-Dec-81
Fix MAKESUBSTR to correctly set the default upper bound in A(I)(:).
Modules:
EXPRES(52)
1430 CKS 10-Dec-81
Range check substring bounds in DATA statements and complain if they're
out of range.
Modules:
COMMAN(115) DATAST(54) ERROUT(67)
1431 CKS 15-Dec-81
Add substrings
Modules:
CGEXPR(79) EXPRES(54) P2S1(67) TABLES(175)
CMPLEX(141) GLOBAL(119) P2S2(61) UTIL(92)
COMSUB(272) OPGNTA(130) REGAL2(154)
1432 RVM 13-Dec-81
Implement assigned formats. In ACT1, allow integer variables
to be values of the FMT= keyword in I/O statements, and fix
wrong error messages given when an asterisk or a name is
incorrectly given as the value of a keyword. In CGSTMN, make
IOFORMAT produce the proper type of FOROTS I/O argblock for
assigned formats, and do away with the generation of format
size words, except in the case of arrays used as formats.
Modules:
ACT1(137) CGSTMN(144)
1433 RVM 14-Dec-81
Rewrite LSTFORMAT to print as much format text per line as possible,
instead of listing format text one word at a time. Also, suppress
listing nulls in format text.
Module:
LISTOU(78)
1434 TFV 14-Dec-81 ------
Finish up edit 1422. Fix MAKEFN in EXPRES so it will handle
intrinsic character functions (i.e. the CHAR function). Add a
routine CHARGLIST to convert non-character function argument blocks
to character function argument blocks. This fixes the cases where a
function statement is followed by a character or implicit character
statement that changes the type of the function. Generate
descriptors for character functions declared in external statements.
The first word of the descriptor has the IFIW bit lit and has the
address of the function. This will allow character functions to be
passed as arguments to subprograms. (They must be declared external
in each subprogram.) Eventually they will be called via a PUSHJ
P,@descriptor. Also fix multi-entry character functions. The entry
points must all be of type character and must have the same length
declared for them. Only one descriptor is used for all the entry
points.
Modules:
ACT0(64) ACT1(138) ERROUT(69) EXPRES(53)
GNRCFN(43) LISTOU(79) OUTMOD(92) STA2(78)
STA3(78)
1435 RVM 14-Dec-81
CNTKEYS is now smart enough to handle namelists correctly, so do
not subtract one from its count in REDORWRIT.
Module:
CGSTMN(145)
1436 SRM 16-Dec-81
Add global flag CHARUSED and set it if see: //, ( : ), intrinsic
function with character arg or value, character array element ref.
Modules:
GLOBAL(120) EXPRES(55) ARRXPN(56) GNRCFN(44)
1437 CDM 16-Dec-81
Changed various routines for argument rel block checking. Added
/DEBUG:PARAMETERS switch (again) to compiler.
Modules:
CGDO(154) COMMAN(116) DRIVER(35)
GLOBAL(121) IOFLG(17) OUTMOD(93)
1440 SRM 16-Dec-81
Fixed day-one bug in CONTFN. It did not have cases for
OPRCLS's greater than SPECOP.
Modules:
UTIL(93)
1441 SRM 16-Dec-81
Fixed a bug in IOLIST folding in the check for functions
with possible side effects. It was folding lists like:
A, F(X)
and not folding:
F(X), A
It should be the reverse.
Modules:
SKSTMN(98)
1442 RVM 17-Dec-81
Modify BLDFORMAT and KORFBLD to allow INTEGER variable format
specifiers even without the FMT= keyword.
Module:
ACT1(139)
1443 RVM et al. 17-Dec-81
ALLFORM never thought that there could be backwards references to
format statements, and so never set up the SNSTATUS field. With
ASSIGNed FORMATs, there can be backwards references.
Module:
OUTMOD(93)
1444 CKS 18-Dec-81
Allow substring refs in the IO lists of READ statements
Modules:
ACT1(140)
1445 SRM 20-Dec-81
Increased stack size from 500 to 2100 to enable us to
compile FM045.FOR in the validation tests.
This allows us to support 58 levels of nested parens.
( The 500 word stack supports 11 levels of nesting.
Each 100 words of stack increases the level of nesting
supported by about 3. )
Modules:
COMMAN(117) GLOBAL(122)
1446 AHM 22-Dec-81
Made MULTIASGN return the address of the created statement node
so that calling routines that punt on negative return values
always get something positive when things went OK. This bug was
detected when character assignment statements in logical IFs
returned 1B0 in VREG causing LOGICALIF to not link the IF
statement into the statement list. Also, MULTIASGN was cleaned
up slightly.
Module:
STA0(64)
1447 CDM/CKS 30-Dec-81
In DOTOPROPAGATE, simple change:
IF () AND () AND () THEN
to
IF () THEN IF () THEN IF () THEN
so that the last clause is not evaluated unless the first two are
true. Was getting an illegal memory read for reading beyond what
actually existed for a continue statement.
Module:
PNROPT(162)
1450 CKS 30-Dec-81
Detect the error in EQUIVALENCE (A(1),A(2))
Modules:
OUTMOD(95)
1451 CKS 30-Dec-81
Fix HSDDESC to handle character variables in COMMON
Modules:
OUTMOD(96)
1452 CKS 4-Jan-82
Do not turn A(1:2) into a .D variable if A is a formal parameter.
Modules:
P2S1(68)
1453 CKS 14-May-81 (formerly 1070)
In LEXSUP, replace @BACKLINE<LEFT> with .BACKLINE<LEFT>, only you
have to say (.BACKLINE<LEFT>)<FULL> to get BLISS to generate correct
code.
Modules:
LEXSUP(15)
1454 RVM 4-Jan-82
Make assigned formats work optimized. Do not allocate formats
until after optimization is done. The optimizer thinks it can
freely use label table entries for its own use, but if formats
have already been allocated, useful information is lost. As a
cleanup, merge the routines ALLFORM and DMPFORMAT into one
routine, called DUMPFORMAT, which both allocates formats and
dumps them to the .REL file.
Modules:
OUTMOD(98) PH3G(257) P3R(53)
1455 TFV 5-Jan-82 ------
Add handling for character statement functions. They have an
extra argument. It is the first and is the descriptor for the
result. The character statement function is turned into either
a call to CHSFN. (the subroutine form of CHASN.) or a call to
CHSFC. (the subroutine form of CONCA.). CHSFC. is used if the
character expression has concatenations at its top level, CHSFN.
is used for all other character expressions.
Modules:
CGDO(155) DOALC(112) OUTMOD(99) SKSTMN(155)
STA0(79) STA3(79)
1456 CKS 11-Jan-81
Variables in input lists aren't flagged as being stored into, and
get listed wrong in the CREF. This is because EXPRESS now parses
input lists and output lists both, and just calls NAMREF. Make it
call NAMSET instead for variables which occur at the top level in
input lists. Add IOINPT bit to recognize input statements.
Modules:
CODETA(7) EXPRES(56) IOFLG(18)
1457 RVM 12-Jan-82
Fix BLDFORMAT to allow INTEGER variable format specifiers in
ENCODE/DECODE statements (Edit 1442 did not quite accomplish
this). Also, fix a poor error message that implies that name
lists are legal format specifiers in ENCODE/DECODE statements.
Module:
ACT1(141)
1460 SRM 18-Jan-82
If character data is used, do not optimize.
( This restriction will be removed later. )
Modules:
ERROUT(70) MAIN(32) COMMAN(118) GLOBAL(123)
1461 CKS 20-Jan-82
Add variable name to "Can't store numeric constant in character
variable" error message.
Modules:
DATAST(55) ERROUT(71)
1462 DCE 21-Jan-82 -----
Fix F77 bug where reduction in strength can cause DO loop variables
to not get assigned a final value. Prevent test replacement in all
cases if F77 selected.
Modules:
TSTR(62)
1463 CKS 22-Jan-82
Modify FATLERR's sixbit printer to not output trailing spaces
Modules:
INOUT(53)
1464 RVM 26-Jan-82
Implement the INTRINSIC statement and modify the EXTERNAL statement
to conform the the FORTRAN 77 Standard when compiling /F77. For the
INTRINSIC statement, add the needed BNF and the semantic routine. For
the EXTERNAL statement, fix the semantic routine to change an intrinsic
routine declared in an EXTERNAL statement to a user routine under /F77.
Also, modify the semantic routine to discover more than the first
error on the line. In ACT1, modify an error message that needs to
know about the INTRINSIC statement.
Modules:
ACT1(142) CODETA(8) F72BNF(16) STA3(80)
1465 CKS 1-Feb-82
Modify the parsing of READ and WRITE statement keyword lists to
support expressions as UNIT and FMT specifiers. This involves
adding a lexical state to check for "LETTERS=" so that we can
tell whether to call EXPRESS to read a unit expression or whether
to scan a keyword.
Modules:
ACT0(65) ERROUT(72) F72BNF(17)
LEXICA(37) STA0(66)
1466 CDM 1-Feb-82
Changes for argument checking for user subprograms and statement
functions.
Modules:
ACT1(143) CGDO(156) ERROUT(72)
EXPRES(57) FIRST(150) GLOBAL(124)
INOUT(54) LISTNG(27) REQREL(3)
STA0(67) STA3(81)
1467 CDM 1-Feb-82
Added parsing for the SAVE statement.
Modules:
CODETA(9) ERROUT(74) F72BNF(18)
FIRST(151) IOFLG(19) STA2(56)
1470 CKS 2-Feb-81
Make EXPRESS quit reading an expression when it sees tic (') when
looking for an operator. A tic when looking for an operand is still
the start of a character constant. Make KEYSCAN handle
READ (unit'record).
Modules:
ACT0(66) EXPRES(58) LEXNAM(3) LEXSUP(22)
1471 RVM 5-Feb-82
Implement compiler support for internal files. In, OPGNTA, add code
skeletons needed to call FOROTS for internal file I/O. In STA0, add
checks for such illegal uses of internal files as unformatted I/O to
an internal file. Also in STA0, store in the IORECORD field of any
I/O statement that references an array as an internal file a pointer
to an expression node that gives the number of characters in the array.
In CGSTMN, generate the code for the calls to FOROTS to do the I/O,
as well as the needed argument blocks. In particular, the FOROTS
arg OTSKEDSIZ now holds the total number of characters in an array
used as an internal file. In ERROUT, add an error message to be used
to report problems with internal file I/O. In ACT1, make the macro
SIZOFARRAY into a GLOBAL ROUTINE.
Modules:
ACT1(144) CGSTMN(146) ERROUT(75) OPGNTA(131)
STA0(68)
1472 AHM 7-Feb-82
Make REDORWRIT generate an OTSKREC keyword for all the possible
cases that the REC= variable was not a CHARACTER array.
Module:
CGSTMN(147)
1473 SRM 8-Feb-82
Set CHARUSED in NAMREF and NAMSET when a character variable is used.
Module:
ACT1(145)
1474 TFV 8-Feb-82 ------
Add support for concatenations as character expressions. Change
REA in COMSUB to walk down the argument list for a concatenation
looking for common sub expressions. Write P2SKCONC to perform
the skeleton optimization for a concatenation. Decide if the
concatenation is fixed length and change the OPERSP field to
CONCTF. Fold all concatenation subnodes into one concatenation
node.
Modules:
CGEXPR CMPLEX COMSUB DOALC ERROUT OPGNTA P2S1
REGAL2 RELBUF STREGA
1475 RVM 8-Feb-82
Correct problem of an ALCUNIT inserting a STORECLASS node over a
character array ref used as a unit expression. Character array
references already are allocated into a temporary, and thus do
not need a STROECLASS node. The solution to the problem is for
ALCUNIT to call ALCCHARRAY instead of ALCTVARR. As a guard
against further trouble, give an internal compiler error if
ALCTVARR is called on a character array refernce. As a
consequence of this edit, ALCCHARRAY becomes a global routine.
Modules:
REGAL2(155) STREGA(231)
1476 RVM 8-Feb-82
Change the name of INEXTSGN to USERFUNCTION.
Modules:
EXPRES(59) FIRST(152) STA3(82)
1477 CKS 10-Feb-81
Detect error when real array used as UNIT specifier.
Modules:
STA0(69)
1500 SRM 11-Feb-82
Issues the warning about /OPT ignored for character from
MRP2S rather than from MAIN. ( If it were in MAIN, we would
have to load the message in every overlay. )
Modules:
PH2S(32) MAIN(33) ERROVC(7)
1501 RVM 16-Feb-82
Change the meanings of the INEXTERN and USERFUNCTION bits.
INEXTERN is now lit for any routine name that appears in an
INTRINSIC or EXTERNAL statement. INEXTERN is the bit that
should be tested to see if this routine name can be used as the
argument to a routine. USERFUNCTION means that this function is
a user function or is an intrinsic function that has been made
into an user function. This definition makes these attributes
less confusing, and corrects some lurking bugs where someone did
not know to test both bits in order to tell if a routine name
could be used as an argument.
Modules:
EXPRES(60) FIRST(153) STA3(83)
* All compiler edits after this point will no longer be assigned local *
* edit numbers. They will use the OCTAL global edit number in the *
* BINDs of the local version number symbols at the module head instead. *
1502 AHM 11-Mar-82
Make NAMGEN divide the size of a character array by the size
of a character array element so that the size field in a
NAMELIST block is in number of array elements. Also make it
not divide character array factors by anything so that they
are in units of bytes. NAMGEN was dividing by 2 in both cases
because DBLFLG was set. Finally, change the array size and
offset fields to occupy separate words of the NAMELIST block
for extended addressing.
Module:
CGSTMN
1503 AHM 11-Mar-82
Cancel part of edit 1250 by making array bounds checking call
the routine PROAR. (again). The name had been PROTA. for a
while, but different names were not necessary, after all.
Change the format of dimension information blocks for extended
addressing support. Rejustify some routines in DEBUG.
Modules:
ARRXPN DEBUG
1504 AHM 12-Mar-82
Implement the /EXTEND and /NOEXTEND switches in the command
scanner for extended addressing. Define the field name
EXTENDFLAG and boolean macro EXTENDED to test the switch
setting. Display "/EXT" in the listing file header if /EXTEND
is given. Also declare a global called BIGARY which holds the
size of the smallest array that goes into the .LARG. psect for
/EXTEND.
Modules:
COMMAN DRIVER GLOBAL IOFLG LISTNG
1505 AHM 12-Mar-82
Make all symbol definitions (entries into the IDTAB table)
fill in the IDPSECT field for the psect of a symbol.
Modules:
ACT0 ACT1 ARRXPN CGDO CMPLEX DEBUG DOALC
DOXPN EXPRES FIRST GCMNSB GNRCFN LEXICA STA0
TSTR
1506 AHM 14-Mar-82
Make DEBUG use ZOUTBLOCK to output line number labels, instead
of using its own buffers. Delete call to ENDISNRLBLK in
ZENDALL since ENDISNRLBLK went away.
Modules:
DEBUG LISTOU
1507 AHM 14-Mar-82
Remove immediate arguments from FOROTS argument block
generation. Call ALOCONST in CMPIOLST, CMPIOCALL, CMPE1LIST
and CMPE2LIST, CMPUNIT and CMPDECENC during the complexity
walk. Delete IOIMMED and ELISTINCR and make all their callers
use IOPTR instead.
Modules:
CGSTMN CMPLEX STREGA
1510 RVM 14-Mar-82
Implement assumed-size arrays. In F72BNF, allow an asterisk as
an array bounds. In TABLES, define the flag ASSUMESIZFLG to
identify assumed-size arrays. In ERROUT, add error messages for
misuse of assumed-size arrays. In ACT1, modify BLDDIM to build
the dimension tables for assumed-size arrays, and to check for
an attempt to use an assumed-size array in an I/O list. In STA0,
put check against the use of an assumed-size array as a format or
unit specifier in an I/O statement.
Modules:
ACT1 ERROUT F72BNF STA0 TABLES
1511 CDM 17-Mar-82
Additions for SAVE statement error processing and rel block
output. Call in PHA3 must be uncommented to call routine to
output the rel block.
Modules:
ACT1 ERROUT GLOBAL IOFLG OUTMOD PHA3
RELBUF REQREL STA2 STA3
1512 AHM 22-Mar-82
Add new subroutine for symbol output to the REL file. It will
output wither type 2 (RSYMBOL) or type 1070 (RLONGSYMBOL) REL
blocks depending on the setting of /EXTEND.
Modules:
DEBUG LISTOU OUTMOD RELBUF REQREL
1513 RVM 22-Mar-82
Fix problems with forming the STE for the dotted name of a library
function used as an argument to a subroutine. REFERENCE in EXPRESS
was not copying type information and other attributes to the dotted
STE. The routine MAKLIBFN also contains code to form dotted names,
but unlike REFERENCE, MAKLIBFN does this correctly. The solution
is to take the code that makes dotted names out of MAKLIBFN, make
that code into a global routine called MAKDOTTEDNAME, and to have
MAKLIBFN and REFERENCE call MAKDOTTEDNAME. Also in this edit,
change the wording of an error message, set the global flag CHDECL
if MAKDOTTEDNAME sees an intrinsic character function, and set
INEXTERN for the dotted name if INEXTERN was set for the original
undotted name. (HSCHD is never called if CHDECL is false, and
HSCHD depends on INEXTERN being set for character functions passed
as arguments.)
Modules:
ERROUT EXPRES GNRCFN
1514 RVM 22-Mar-82
Disallow formal arguments as INTRINSIC functions.
Modules:
ACT1 ASHELP STA3
1515 RVM 23-Mar-82
Make it illegal to declare a generic name intrinsic, if there
is not a specific intrinsic function of the same name. For
example, INTRINSIC LOG is illegal, because there is no function
named LOG. But, INTRINSIC REAL is OK, because although REAL is
a generic function, there is a function named REAL.
Module:
STA3
1516 CKS 23-Mar-82
IOFORMAT was incorrectly assuming that it can only be called with
scalars. It can be called with arbitrary expressions. Also, do
complexity and register allocation for format expressions.
Modules:
CGSTMN STREGA
1517 CKS 24-Mar-82
Fix SUBASSIGN to check for end-of-statement after the RHS expression
in substring assignments.
Modules:
STA0
1520 DCE 25-Mar-82
Fix constant allocation in ELISTS so that (A(I),1234,I=1,10) does
allocate the constant 1234 when optimized.
Modules:
CMPLEX
1521 CDM 26-Mar-82
Added routines needed for argument checking. Several calls to
routines in MRP3 (PHA3) must be uncommented to output the rel blocks.
Modules:
PHA3 RELBUF REQREL
1522 TFV 29-Mar-82
Fix error diagnostic for length star variables and arrays.
Length star is legal for dummy arguments. Change P2SKSUBSTRING
to give the substring bound out of range error for upper bound
less than lower bound, and for lower bound less than 1. Also
combine the two substring bound errors into one error. Remove
E177 (cant concat error).
Modules:
ERROUT ERROVC ERROVD ERROVG ERROVR OUTMOD P2S1
TABLES
1523 RVM 29-Mar-82
Implement an extension which makes the EXTERNAL statement
optional for a user function name when the program unit that
tries to pass that user function name as an argument also calls
the function directly. This edit provides some degree of
compatibility with other DEC compilers and the compilers of
other vendors. Making EXTERNAL optional is accomplished by
setting the INEXTERN and USERFUNCTION bits in the STE of any
user function when the function is passed as an argument. Note
that this edit does not make the INTRINSIC statement optional.
We have always allowed a program unit to have a variable as the
same name as a library function called in that program unit.
Making INTRINSIC optional would break this.
Module:
EXPRESS
1524 RVM 31-Mar-82
Don't turn on the indirect bit of an argument block entry for
an argument of type dummy character function.
Module:
CGDO
1525 AHM 28-Apr-82
Various changes for psected REL files. Suppress generation of
the type 3 HISEG block. Generate type 24 psect header blocks
for each psect. Put in a type 17 .REQUEST FORLIB:FORLIB block
for development to read in a private FORLIB that is psected
instead of being TWOSEG. Turn off KS bit in the type 6 name
block when compiling /EXTENDED.
Modules:
LISTOU OUTMOD RELBUF REQREL
1526 AHM 28-Apr-82
Pave the way for psected rel files by converting all calls to
ZOUTBLOCK for outputting RCODE (type 1) rel blocks to call
ZCODE instead. Use the proper relocation counter to allocate
space for each psect instead of always using HILOC to tell
ZOUTBLOCK what address is being output. Start HILOC at 0
instead of 400000 (or larger for large lowsegs) and add 400000
(from the global HIORIGIN) to any value that addresses the
hiseg when the value is written out. Add the SNPSECT field to
hold the psect of label table entries. Make LABDEF and GENLAB
set the field and make DUMPSYMTAB and ROURLABEL use it.
Modules:
CGDO FIRST GLOBAL LEXICA LEXSUP LISTOU
OUTMOD RELBUF REQREL SRCA UNEND
1527 CKS 29-Apr-82
Allow constant expressions as array bounds, string sizes, and
parameter values. Also add Fortran-77 parameter semantics,
that is, convert the parameter value to match the type of the
parameter variable. Allow parameter statements before and after
type declaration statements.
Modules:
ACT0 CODETA LEXICA SKSTMN STA2
ACT1 ERROUT OUTMOD STA1
1530 TFV 4-May-82
Add fields for CONCTV processing. They are IOLSTATEMENT in
IOLSCLS nodes, IOLMARK and IOMARK in I/O statments and ARGMARK
in argument list nodes. IOLMARK, IOMARK, and ARGMARK are
pointers to the argument list for CHMRK. and CHUNW. calls.
IOLSTATEMENT points to the parent I/O statement for an IOLSCLS
node. Finally remove GETCORE macro and replace it in-line in
SKSTMN (the routine GETCORE in LISTNG does a CORE UUO).
Modules:
ACT1 FIRST FORMAT GLOBAL INPT IOPT LEXICA
SRCA SKSTMN TABLES
1531 CDM 4-May-82
Changes for SAVE statement processing after code review.
Modules:
EXPRES GLOBAL RELBUF STA0 STA2 STA3
1532 AHM 7-May-82
Fix edit 1151 by making PROCCOM check whether TCOMSIZ is
greater than 5*2**18 bytes for ? Program too long message.
Module:
OUTMOD
1533 TFV 13-May-82
Modify register aloocation and code generation for CONCTV nodes.
Add the routines FINDMARK and GENMARK to allocate the argument
lists for CHMRK./CHUNW. calls.
Modules:
CGDO CGEXPR CGSTMN OPGNTA REGAL2
1534 CKS 17-May-82
Fix output of character constants in the listing. Use uparrow
format instead of sending the control character directly.
Modules:
OUTMOD
1535 CDM 17-May-82
Optimize CHAR(constant) and ICHAR(constant) to be constants.
Enlarge OPERSP field (and other related ones) to be 5 bits
instead of 3 bits wide.
Modules:
ACT0 P2S1 TABLES UTIL
1536 CKS 19-May-82
Allow DATA statements to be freely mixed with type specification
statements and PARAMETER statements.
Modules:
CODETA
1537 AHM 20-May-82
Prepend some innocuous entries to the BPLH UPLIT so that bad
negative character addresses propagated from users trying to
extend common blocks backward don't get junk listings of the
byte pointers.
Module:
OUTMOD
1540 AHM 21-May-82
Don't output a default psect index block before calling
BUFFOUT, since it will flush the main rel buffer before
flushing the local fixup rel buffer. LINK is said to destroy
the current default psect index in arbitrary ways, so the
index should be set immediately before the local fixups.
Module:
RELBUF
1541 DCE 25-May-82 -----
Add several new peephole optimizations for consecutive (identical)
instructions of the MOVE class (MOVEI, MOVSI, MOVNI, MOVEM).
Module:
PEEPOP
1542 RVM 25-May-82
Provide the FINAL SOLUTION to the problem of OCTAL, LOGICAL,
HOLLERITH, and CONTROL expressions under gfloating. The bit
patterns for these values need to be preserved, but at the
same time, these values must be able to participate in the
compile-time constant propagation and folding. The past
approach of just not converting these values to internal
REAL (GFLOATING) just didn't work: in obscure situations,
bad code could be generated or bad results could come from
constant folding. The problem was that converting a value
from REAL to GFLOATING and back to REAL did not produce the
original bit pattern, since the hardware instructions to
perform these operations normalized the number. The final
solution was to write new conversions in CNSTCM that do not
normalize their results, and go back to allowing the compiler
to freely convert values to be of the proper type.
Modules:
CNSTCM DATAST P2S1 PNROPT VLTPPR
1543 RVM 25-May-82
Under /GFLOATING, the conversion CMPL.G should be used to
convert two DOUBLE PRECISION numbers to COMPLEX.
Module:
GNRCFN
1544 AHM 26-May-82
Output type 22 default psect index blocks for the .DATA. psect
before type 21 or 1004 sparse data blocks so that they have a
chance to work while the new psected sparse data blocks are
not in LINK. This edit is only for V8 development and will be
removed when the LINK support is finally in.
Modules:
OUTMOD RELBUF
1545 CKS 28-May-82 Q10-00103
Fix check for namelist IO in CGREAD and CGWRITE to not detect
constants as namelists. Character constants are now possible
format specifiers.
Modules:
CGSTMN
1546 CKS 31-May-82
Allow expressions in TYPE, ACCEPT, PRINT, PUNCH, and REREAD.
Modules:
ACT0 ERROUT F72BNF FAZ1 STA0 STA1
1547 AHM 1-Jun-82
Round up size of COMMON blocks from characters to words for
the running total and give "?Program too large" message if the
sum of HILOC, LOWLOC and the size of all COMMON blocks exceeds
18 bits of address space.
Modules:
LISTOU OUTMOD
1550 CKS 1-Jun-82
Put in some SAVSPACEs to free space used by IO lists.
Modules:
ACT1
1551 AHM 3-Jun-82
Add a new psect symbol called PSOOPS with the value 0, add 1
to the values of all the other PS???? symbols and make
ZSYMBOL and ZCODE call CGERR if they see a reference to
PSOOPS. Also, remove all statements that set the psect index
of an STE to PSCODE for external references so that the psect
index will not be destroyed if other symbols with the same
name share the same STE.
Modules:
ARRXPN CGEXPR CMPLEX DOXPN EXPRES FIRST
GLOBAL GNRCFN LEXICA RELBUF STA0
1552 AHM 6-Jun-82
Make NEWQTMP set the IDPSECT and IDPSCHARS fields of the .Q
temp being created to PSDATA so that we can generate the
address of the .Q temp in HSDDESC in OUTMOD.
Module:
REGUTL
1553 CKS 7-Jun-82
ALCSUBSTR can pick reg 0 to do subscript calculation for a substring
node. This results in ADJBP in register 0. Fix it to not use reg 0.
Modules:
REGAL2
1554 CKS 8-Jun-82
Add substring bounds checking. Call PROSB. to check substring bounds
if /DEBUG:BOUNDS.
Modules:
EXPRES ARRXPN
1555 CKS 14-Jun-82 Q10-00111
Check for FMT=* and FMT not specified before calling ALCINTMP to walk
format expression. ALCINTMP does not deal with *.
Modules:
STREGA
1556 CKS 14-Jun-82 Q10-00115
Allow ENTRY statements anyplace in a program unit.
Modules:
CODETA
1557 CKS 14-Jun-82 Q10-00113
If substring bounds are constant, check that upper bound is in range
(unless variable is length *). We already check lower bound.
Module:
P2S1
1560 TFV 15-Jun-82
Modify BLDDIM to give an array too large error for character
arrays greater than or equal to CHARSPERWORD * 2 ** 18
characters and numeric arrays greater than or equal to 2 ** 18
words.
Module:
ACT1
1561 CKS 16-Jun-82
Allocation for character arrays is rather strange. Fix it. Only
ALCINREG currently handles char arrayrefs; teach ALCINTMP, ALCTVARR,
and ALCTARY. Make ALCCHARRAY back into a local routine and remove the
call in ALCARRAY; call it explicitly where needed. Remove the (now
unnecessary) check added by edit 1475 to call ALCCHARRAY directly from
ALCUNIT.
Modules:
REGAL2 STREGA
1562 TFV 18-Jun-82
Fix CGSBPRGM to check ARGMARK only if there is an argument list.
Fix ROUSYM to handle TYPECNV nodes in argument lists. These are
inserted over .Qnnnn variables used as the result descriptor for
concatenations. They cause the VALTYPE for the .Qnnnn variable
to be CHARACTER.
Modules:
CGDO LISTOU
1563 PLB 18-Jun-82
Random TOPS-20 nativization tasks.
- Remove cutback CORE UUO from MRP1 (DRIVER.BLI)
- Convert ERR3 (SKERR/CGERR) to do PSOUT/PBOUT
- Convert OUTSTRs to use routine TTYSTR.
- Convert OUTTYx macros in LEXAID to use TTYSTR.
- Create TTYSTR & EXITUUO routines for TOPS-20.
- Remove REQUIRE of FTTENX from INOUT since LEXAID
does it now.
Modules:
DRIVER ERR3 LEXAID INOUT UNEND COMMAN
1564 AHM 21-Jun-82
Remove code that generated .REQUEST FORLIB:FORLIB during
development. Make /EXTENDED output /SYMSEG and /PVBLOCK
switches to LINK and set psect origins to section 1 addresses.
Modules:
LISTOU OUTMOD REQREL
1565 PLB 21-Jun-82
Use OUTTYX macro from LEXAID for TOPS-20 instead of OUTSTR.
Modules:
LEXICA
1566 CDM 24-Jun-82
Do not output named common names to writeable overlay blocks
when SAVE-d unless they are also declared in COMMON statements.
Also enable all 1045 blocks to be output.
Modules:
PHA3 RELBUF STA2
1567 CDM 24-Jun-82
Make CHAR, ICHAR, LEN inline functions, and when possible into
constants.
Modules:
CGEXPR CMPLEX FIRST GLOBAL GNRCFN LISTOU
OPGNTA OUTMOD P2S1 REGAL2 TABLES
1570 AHM 25-Jun-82
Change the entry in LONGTAB so that type 1070 additive symbol
fixups for extended programs don't try to relocate a symbol
name (though since all the calls to ZSYMBOL with function
GLBSYMFIX used PSABS anyhow) and perform 30 bit fixups instead
of 18 bit fixups so that numerics in COMMON don't lose their
section numbers.
Module:
RELBUF
1571 CKS 27-Jun-82
Don't set parent pointers in a subexpression of OPEN node if
it's READONLY since READONLY doesn't have an expression and
AC 0 doesn't appreciate being a parent pointer.
Modules:
STA1
1572 AHM 29-Jun-82
Move check for ?Program too large from ZENDALL to MRP3 so that
the check is performed even if object code isn't generated.
Modules:
LISTOU PHA3
1573 CKS 1-Jul-82
Add DO WHILE and END DO. Allow the statement number in stepped DO
to be omitted.
Modules:
ACT0 CODETA DRIVER ERROUT F72BNF FIRST
LEXICA STA3 TABLES
1574 AHM 3-Jul-82
Make REDORWRIT supply a type code of 7 (label) for the pointer
to the namelist block in argument blocks for calls to NLI. and
NLO. It used to be a type 0 (immediate) argument.
Module:
CGSTMN
1575 TFV 7-Jul-82
Fix type declarations to allow 'variable * length (subs)' and
'variable (subs) * length'.
Modules:
ACT0 ACT1 ERROUT F72BNF STA2
1576 AHM 7-Jul-82
Make the compiler emit a JRST to the start address of programs
under /EXTENDED and have ZENDALL make that the entry vector.
Modules:
LISTOU PHA3
1577 RVM 9-Jul-82
Set aside a bit in FLAGS2 to be used as the /ABORT flag.
Module:
IOFLG
1600 PLB 9-Jul-82
Code for native TOPS-20 memory management. Uses routine CORUUO.
Modules:
MAIN LISTNG DRIVER SRCA COMMAN
1601 CKS 12-Jul-82 Q10-00132
Improve error message for the expression <character> / <character>.
Instead of saying "illegal combination of character and numeric data",
which is confusing since there is no numeric data involved, say
"illegal operator for type character".
Modules:
VLTPPR ERROUT
1602 RVM 14-Jul-82
Implement native command scanner.
Module:
CMND20
1603 RVM 16-Jul-82
Make .DEBUG preserve T2 so that a switch may follow /DEBUG. Remove
square brackets around the CCL "FORTRAN: etc." message. Disable
CONTROL/H recovery under batch, so that an error in a command
will not effect the next command line (otherwise, the next command
tries to hang, waiting for a CONTROL/H).
Module:
CMND20
1604 CKS 21-Jul-82
Handle long IO lists by using COPYXLIST and MOVSTK instead of
just COPYLIST in routine GIOLIST.
Modules:
EXPRES FAZ1
1605 RVM 2-Aug-82
The DIM function would underflow at compile-time for gfloating
numbers, if the first number was less than the second. The
reason was that the DIM would only zero the high order word
for this case, which is normally OK because the number has been
rounded to the precision of a single precision number. But, under
/GFLOAT, the numbers have 3 bits of precision in the low order
word.
Module:
CNSTCM
1606 RVM 3-Aug-82
Reserve the SW.ABO flag in COMMAN.MAC so that COMMAN, IOFLG,
and CMND20 all agree about which bits are taken.
Module:
COMMAN
1607 TFV 4-Aug-82
Fix CGCHMRK to reuse one argument block for many IOLST. calls in
a single statement.
Module:
CGEXPR
1610 CKS 5-Aug-82
Relax statement ordering rules to allow NAMELIST statements
anywhere following the IMPLCIT statements. This is almost
VAX compatible but not quite: VAX allows NAMELIST to precede
IMPLCIT and we do not.
Modules:
CODETA
1611 RVM 6-Aug-82
Many command scanner changes to fix bugs, incorporate suggestions,
and to add features. Major changes: Exit compiler after processing
PRARG block. Rewrite /RUN code. Add /HELP. Rename /OBJECT and
/NOOBJECT to be /BINARY and /NOBINARY. Improve error message maker.
Add /DFLOATING.
Module:
CMND20
1612 PLB 13-Aug-82
Clean up in trap code from edit 1600.
Module:
CMND20
1613 CDM 13-Aug-82
Change /DEBUG:PARAMETERS to /DEBUG:ARGUMENTS.
Modules:
CGDO CMND20 COMMAN DRIVER EXPRES IOFLG
LISTNG RELBUF STA0
1614 CDM 16-Aug-82
Move the output of argchecking 1120 rel blocks to after the
symbol table output so that LINK can produce better error
messages.
Modules:
LISTOU PHA3
1615 AHM 18-Aug-82
Change the default psect index to .DATA. before outputting
common block sizes in ALLCOM. LINK will be changed to
allocate common blocks in the default psect when reading
psected .REL files.
Module:
OUTMOD
1616 CDM 24-Aug-82 Q10-00148
IMPLICIT statements do give subroutine names a type, and for
character, give an extra variable for the return value, which a
subroutine can't have.
Module:
STA3
1617 CKS 24-Aug-82
Make the TOPS-10 command
.FORTRAN FILE=FILE
work when the appropriate pathological command is defined. (Just
add an AOBJN table to the .ISCAN call.) When invoked this way, the
compiler reads SWITCH.INI! (Thanks to DPM for the idea.)
Modules:
COMMAN
1620 CKS 24-Aug-82 Q10-00143
Improve some error messages. For each numeric operand of //, say
?Numeric operand of concatenation operator
and for a mixed-mode assignment between numeric and character data,
?Illegal assignment between character and numeric data.
This makes a little more sense of the flurry of messages you get with
missing declarations.
Modules:
EXPRES VLTPPR ERROUT
1621 CKS 24-Aug-82 Q10-00145
Edit 1556 to allow ENTRY statements anywhere had the unexpected side
effect that labels on ENTRY statements were marked as being on FORMAT
statements. This is because LABDEF trickily checks the statement order
code to recognize FORMAT statements. Fix: use two distinct order codes
(with identical rows in the transition matrix) for ENTRY and FORMAT.
Modules:
CODETA
1621 RVM 25-Aug-82
Add the /DFLOATING switch to the TOPS-10 command scanner. Reorder
switch table so that it is in alphabetical order. Give an error
message if the user specifies /GFLOAT.
Module:
COMMAN
1622 CKS 25-Aug-82
Handle IOSTAT=arrayref and ASSOCIATEVARIABLE=arrayref correctly.
Modules:
STA1 CGSTMN
1623 RVM 26-Aug-82
TOPS-20 command scanner: Do a CLZFF% before each command read
from the primary input stream in order close all files and
release all JFNs. This fixes the problem of unreleased JFNs
when a command or compile is aborted due to a catastrophic
error. A consequence of this edit is that the compiler cannot
keep a JFN on SWITCH.INI across compiles.
Module:
CMND20
1624 AHM 28-Aug-82
Don't call ZSAVEOUT in MRP3 if /EXTEND was specified, since we
don't support overlays for extended addressing and variables
are always preserved when not using overlays.
Module:
PHA3
1625 RVM 30-Aug-82
Don't output a format size keyword was for list-directed I/O.
Module:
CGSTMNT
1626 CKS 31-Aug-82
Fix Phase-2 optimization of expressions in ENCODE/DECODE statements.
Module:
SKSTMN
1627 CKS 31-Aug-82 Q20-03014
Don't allocate .D variable to hold the function return value for
CHAR(constant) in PARAMETER statements.
1630 AHM 1-Sep-82
Fix bug introduced by edit 1615. Don't output a default psect
index if there is no .REL file being generated.
Module:
OUTMOD
1631 RVM 1-Sep-82 Q20-03013
If the PRARG block overflows, the EXEC writes out TMP files to
disk. The TOPS-20 command scanner didn't look on disk for its
arguments if it found a null PRARG block.
Module:
CMND20
1632 RVM 1-Sep-82
The TOPS-20 compiler does not reclaim its data area after a
compile. The locations .JBFF and .JBREL were only being set
once when the compiler started, rather than after each compile.
Module:
CMND20
1633 TFV 1-Sep-82
Improve /STATISTICS to print number of source lines and lines
per minute and also executable statements and statements per
minute.
Module:
GLOBAL LEXICA MAIN PH2S PHA2 UNEND
1634 CKS 3-Sep-82 Q20-03016
Add missing dot.
Modules:
FAZ1
1635 CDM 24-Sept-82 V6 Q20-01670
Fix to olde V6 QAR which had problems with labels being trashed.
Module:
PEEPOP
1636 RVM 28-Sep-82
Make /EXTEND and /NOEXTEND invisible, as they are not supported
aspects of the FORTRAN product.
Module:
CMND20
1637 CKS 29-Sep-82 Q10-00161
Don't give repeated overflow warnings when an overflowed result
(represented as double precision 377777777777 377777777777) is
rounded to single precision.
Modules:
CNSTCM
1640 RVM 7-Oct-82 Q10-00144
Fix bug that caused the ISN of the line being compiled to be off
when the line is the last line of an INCLUDE file or the "main"
input file. The last line in a file is marked with EOF, rather
than EOS. This prevented the lexical action ACMLEXFOS from setting
the line number correctly, since ACMLEXFOS only reset the line
number if the line ended with EOS. This error caused error messages
to contain the wrong line number and to appear late in the listing.
Module:
LEXICA
1641 AHM 10-Oct-82
When P2SKCONCAT sees the expression A//(B//C)//D, it will
change it into A//B//C//D. Make it also change the parent
pointers for B and C to point to the new concat node if they
have parent pointers.
Module:
P2S1
1642 CDM 11-Oct-82
Make character array refs work for encode/decode variables.
ALCCHA wasn't being called, so call ALCINREG to decide which
array allocation routine to call.
Module:
STREGA
1643 RVM 11-Oct-82
If the EXEC's arguments to the compiler do not exist in a PRARG
block or on disk, then do not complain, just accept commands from
the terminal. Also, add the ;T(emporary) attribute to the filespec
for the disk file which holds the EXEC arguments.
Module:
CMND20
1644 CDM 13-Oct-82
Simple patch to allow the below to generate correct code:
OPEN( ... FILESIZE=<logical variable> ...)
A "no-convert" type convert node where the answer is put into a
temporary had its TARGADDR set incorrectly in ALCTPCNV.
Module:
REGAL2
1645 RVM 15-Oct-82
Add the /NOECHO switch to the TOPS-20 command scanner, and change
a nested /TAKE which does not specify /ECHO or /NOECHO to use the
current value of the echo flag.
Module:
CMND20
1646 TFV 18-Oct-82
Fix ASTER to give an error for character lengths less than or
equal to 0. Fix BLDMSG to output negative decimal numbers in
error messages.
Modules:
INOUT STA2
1647 CDM 18-Oct-82 Q20-06005
Add MAP statement to ENDDSTA so that proper structure references
are made.
Module:
STA3
1650 CDM 18-Oct-82
Copyright for memory image. Global variable COPYRIght now
contains the up-to-date copyright for the compiler in ASCII.
Module:
MAIN
1651 CKS 18-Oct-82
Fix omitted upper substring bound C(I:) to handle the case where
C is length *. Compile it as C(I:LEN(C)).
Modules:
EXPRES GLOBAL
1652 CDM 20-Oct-82 V6 SPR 10-33050
Give warning for RETURN statement in main program.
Modules:
CMND20 COMMAN ERROUT STA0
1653 CDM 21-Oct-82
Make INITLZ check for /NOERROR before typing out queued up
error messages to TTY.
Module:
LEXICA
1654 SRM 21-Oct-82
Increased stack size from 2100 to 2200 to enable us to
compile FM045.FOR in the validation tests. This allows us
to support 58 levels of nested parens. (The native -20
command scanner uses 11 more words of stack than the old
one did. These 11 words made the difference in preventing
us from compiling FM045. See edit 1445.)
Modules:
COMMAN CMND20 GLOBAL
1655 CDM 25-Oct-82
Allow character inline functions (CHAR) for concatenation
arguments in P2SKCO.
Module:
P2S1
1656 CKS 25-Oct-82 Q10-03012
Parameters can't be used to define other parameters in the same
statement. Cure: write an action routine PARMASSIGN to read the
parameter expression and define the parameter variable. This
leaves the statement semantic routine with nothing to do. Also
only give a warning message for parameter statements without
parens if the type of the variable and the expression differ.
Modules:
ACT0 COMMAN CMND20 ERROUT F72BNF STA2
1657 RVM 27-Oct-82
Improve the "Error occured while processing ..." message from
the TOPS-20 command scanner.
Module:
COMND20
1660 TFV 1-Nov-82
Change E180 (CFL) to be 'Reference to character function <name>
must have a fixed length'. It was 'References ...'.
Module:
ERROUT
1661 CKS 2-Nov-82
Call NAMSET for assignments to scalar substrings.
Modules:
STA0
1662 TFV 2-Nov-82
Fix INQUSTA to give the error Exxx (NYI) 'INQUIRE statement is
not yet implemented.'
Modules:
ERROUT STA1
1663 SRM 5-Nov-82
Fix bug in allocation for implied DO loops that have been
folded into SLISTs by /OPT. The assignment statement to store
the final value of the loop was erroneously using ACs that
were in use to hold items preceding the loop in the IO list.
Modules:
STREGA
1664 CKS 8-Nov-82 Q20-06026
Common subexpressions of substring nodes which are allocated to
live in registers can be clobbered by ADJBPs. The problem is
caused by ALCSUBSTR using the wrong variable to check for this
case -- change an RLEN to RBP.
Modules:
REGAL2
1665 CKS 8-Nov-82 Q20-06028
Allow computed GOTO as the last statement in a DO.
Modules:
CODETA STA0
1666 TFV 8-Nov-82
Fix RELINIT to always use FORTRAN for the compiler id. The id
for GFLOATING FORTRAN is no longer used. Type coercion is now
used for DP actuals passed to GFLOATING formals and vice versa.
Module:
OUTMOD
1667 TFV 9-Nov-82
Fix ASTER to give a better found when expecting error for type
declarations.
Module:
STA2
1670 CKS 10-Nov-82
Allow arbitrary expressions (not just constant expressions) as bounds
for adjustably dimensioned arrays.
Modules:
ACT0 ACT1 DOXPN
1671 RVM 11-Nov-82
The TOPS-20 command scanner had problems when the compiler was
reSTARTed because the COMND% JSYS state block was not being
reset.
Module:
CMND20
1672 RVM 11-Nov-82
The TOPS-20 command scanner complained overmuch if the user's
SWITCH.INI file was offline. The scanner no longer complains
if the switch file is offline. I/O errors while reading the
switch file now produce warning instead of error messages,
and the warnings are now followed by a message stating that
the problem occurred while reading the switch file.
Module:
CMND20
1673 RVM 11-Nov-82
Make the error message about nesting /TAKE commands too deep
a warning message and recover from the error by just ignoring
the errant command and continuing to process the nested /TAKEs
already in process. This has the nice property that the user
can recover by issuing the ignored /TAKE command when prompted
again by the compiler.
Module:
CMND20
1674 CDM 11-Nov-82 QAR 10-03021
Fix argchecking further so that constant and expression
arguments get flagged as no-update, and character function
return values are implicit (not checked).
Modules:
RELBUF REQREL
1675 RVM 11-Nov-82 Q10-03032
Implement a suggestion to include more information in the
warning message E168.
Modules:
ERROUT ERROVR OUTMOD
1676 CKS 18-Nov-82 Q20-06053
Allow OPEN specifiers to be hollerith strings.
Modules:
STA1
1677 CKS 20-Nov-82 Q20-06039
Modify the parsing of ENCODE, DECODE, FIND, and REWIND and friends
to use the KEYSCAN action routine to read keyword lists.
Modules:
F72BNF CODETA ACT0 STA0 STA1
CDM 20-Nov-82 Q20-06044
Check that an argument list really exists before lighting the
ARGCHBLOCK bit saying arg checking is necessary.
Module:
STA0
1700 CKS 23-Nov-82 Q10-03039
Fix register allocation for UNIT, FMT, and other character-valued
I/O specifiers. These used to be integer only, so ALCINTMP was called
in single mode. Call it in pair mode if DBLFLG is set.
Modules:
STREGA
1701 RVM 13-Dec-82 Q20-06057
Remove the abbreviation for the /NOOBEJCT switch since
that swich will disappear as soon as the EXEC no longer
needs it.
Module:
CMND20
1702 CKS 13-Dec-82
Improve error message when turkey incorrectly uses FMT= keyword
to specify format in ENCODE/DECODE.
1703 CDM 17-Dec-82
Do not output any processor type to rel file. V5A only puts out
KI, and V7 will not work on a KI, so if we tell Link the truth,
users with libraries will get Link-time warnings.
1704 TFV 21-Dec-82
Fix type declarations to allow optional comma after the optional
*size specifier. The comma is only allowed if the *size is
specified.
Module:
STA2
1705 PLB 22-Dec-82
Fix TWOSEG in ERR3, (TOPS-10), Correct BLT in CMND20.
Modules:
ERR3 CMND20
1706 TFV 22-Dec-82
Fix P2SKSUBSTRING for substring assignments to character
function values.
Module:
P2S1
1707 CKS 4-Jan-83 Q10-03056,03058,03059,03060
Fix exponentiation routines that do constant folding. They were not
coded to handle negative exponents or exponents more than 18 bits long,
and did not properly handle exceptions. Import DEXP2 and GEXP2 from
Forlib to do real exponentiations; import some code from EXP1 to do
integer.
Modules:
CNSTCM
1710 CDM 6-Jan-83
Update internal compiler copyright notice to 1983.
Module:
MAIN
1711 RVM 7-Jan-83
Make /O mean /OPTIMIZE, just as advertised. Also, have
the compiler to exit if the primary input designator is
invalid (this lets the compiler run as a background fork).
Module:
CMND20
1712 AHM 7-Jan-83
Set the psect index for labels on declaration statements to
PSCODE in LABDEF so that we don't ICE from a PSOOPS when
dumping the labels (SUBROUTINE and friends can actually
produce code that gets labeled).
Module:
LEXSUP
1713 CKS 11-Jan-83
Remove V6 routines not used in V7 since edits 1465, 1546, and 1677.
Deleted routines are RECORDMARK, BLDFORMAT, BLDUNIT, BLDKEY, BLDKLIST,
KORFBLD, BLDKORU, BLDIO1, and ZIOSTK.
Modules:
ACT0 ACT1 STA1
1714 CKS 11-Jan-83 Q10-03063
Copy ARRAYREF nodes properly in COPYEXPR.
Modules:
ARRXPN
1715 RVM 12-Jan-83 Q20-06105
The compiler did not realize that character variables were
stored into when they were used as internal files by WRITE
statements. To remedy this, set the STORD attribute when
doing the semantic checks on internal file specifiers used
in WRITE statements.
Modules:
STA0 ACT1
1716 TFV 17-Jan-83 Q20-06103
Fix OPENCLOSE. FLGREG is trashed if UNIT is not specified.
Module:
STA1
***** End V7 Development *****
;.BEGINR REVISION HISTORY
;.COMPONENT FORTRA
;.VERSION 7
;.AUTOPATCH 6
;;.EDIT 1717 RESERVED FOR DEC
;;.EDIT 1720 RESERVED FOR DEC
;;.EDIT 1721 RESERVED FOR DEC
;.EDIT 1722 LOGICAL STATEMENT FUNCTIONS GENERATE INCORRECT CODE
;; Change statement function entry code to always copy double
;; precision args. This is necessary if the arg is used in a
;; relational.
; SRM,1-FEB-83,SPR:10-33235
; A:SRC DOALC.BLI,REVHST.MAC
;.EDIT 1723 INCORRECT CALL BEING GENERATED TO A NON-EXISTENT ENTRY
;; Under certain circumstances, the compiler may generate a call
;; to the non-existent FORLIB entry DFL.1.
; SRM,3-FEB-83,SPR:NONE
; A:SRC STREGA.BLI
;.EDIT 1724 FIX FOLDING OF REAL ** INTEGER UNDER /GFL
; CKS,3-FEB-83,SPR:NONE
; A:SRC CNSTCM.MAC
;.EDIT 1725 FIX EXECUTE ONLY PROBLEM ON TOPS-10
; TFV,3-FEB-83,SPR:NONE
; A:SRC MAIN.BLI
;.EDIT 1726 FIX REGISTER ALLOCATION AROUND ENTRY STATEMENT
;; If a register is allocated for a block which includes an ENTRY
;; statement, the register may get reset incorrectly if one falls
;; through the ENTRY statement.
; DCE,9-FEB-83,SPR:NONE
; A:SRC PH3G.BLI
;;.EDIT 1727 RESERVED FOR V6
;.EDIT 1730 USING DO INDEX AS SUBSCRIPT TO A CHARACTER ARRAY
; CKS,21-FEB-83,SPR:NONE
; A:SRC UTIL.BLI
;.EDIT 1731 MEMORY PROTECTION VIOLATION FOR /STATISTICS
;; Routine STATS calls ZZOUTMSG with a UPLIT. ZZOUTMSG tries to
;; modify the PLIT which is in the hiseg causing a memory
;; protection failure.
; TFV,10-MAR-83,QAR:10-03072
; A:SRC UNEND.BLI
;.EDIT 1732 Long PARAMETER constants not blank padded
;; Constants whose word length is shorter than the identifiers
;; must get blanks padded to the constants. Patch to PARMASSIGN.
; CDM,17-MAR-83,SPR:NONE
; A:SRC ACT0.BLI,GLOBAL.BLI,SRCA.BLI
;.EDIT 1733 ELIMINATE SPURIOUS LINE NUMBERS FOR OVER/UNDERFLOW MESSAGES
; RJD,21-MAR-83,SPR:10-33670
; A:SRC OUTMOD.BLI
;.EDIT 1734 ICE FROM EDIT 1730 FOR BINARY AND LIST DIRECTED I/O
;; MISCIO was calling LEAFSUBSTITUTE for non-existent fields in I/O
;; statements.
;; Module:
;; UTIL
; TFV,24-MAR-83,SPR:NONE
; A:SRC UTIL.BLI
;;.EDIT 1735 RESERVED FOR AUTOPATCH
;;.EDIT 1736 RESERVED FOR AUTOPATCH
;.EDIT 1737 ICE ON CALLS WITH NO ARGUMENTS AND /DEBUG: OR MANY ARGUMENTS
; RJD,4-MAR-83,SPR:20-19002
; A:SRC STA0.BLI
;.EDIT 1740 CONSTANT EXPRESSION NOT ALLOWED IN EQUIVALENCE STATEMENTS
;; Allow constant expressions for EQUIVALENCE statements.
;; Modules:
;; ACT0
; CDM,7-APR-83,SPR:NONE
; A:SRC ACT0.BLI,STA3.BLI
;.EDIT 1741 PRODUCE ERROR MESSAGE FOR CHARACTER IMPLIED DO INDEX
;; Implied DO indexes which are character variables are quite
;; illegal and were creating an ICE when they tried to convert
;; the constant from integer to character!
;; Modules:
;; ACT1
; CDM,7-APR-83,SPR:NONE
; A:SRC ACT1.BLI
;.EDIT 1742 BAD CODE PRODUCED FOR I/O STATEMENT KEYWORDS
;; Fix I/O deficiencies. Do skeleton walk for all I/O keyword
;; values. Modify SKIOLST and SKIO so P2SKSTMNT can use them for
;; FIND, REWIND, etc.. Fix checks for DONOAOBJN on inner do loop
;; index as keyword value. Have P2REGCNTS check all I/O statements
;; for transfers out of the loop. Fix LPIXSUB to do substitution
;; of the loop index variable for I/O statement keywords. MISCIO
;; should look at IOUNIT, IORECORD, IOSTAT, IOFILE, and the IOLIST
;; for registers to substitute. MISCOCI does the same for
;; OPEN/CLOSE/INQUIRE arguments. Also cleanup IOSUBSTITUTE. Fix
;; calls to MISCIO in PROPCASE and LEAFLOOKER.
;; Modules:
;; DOALC PH3G PNROPT SKSTMN UTIL
; TFV,14-APR-83,SPR:NONE
; A:SRC DOALC.BLI,PH3G.BLI,PNROPT.BLI,SKSTMN.BLI,UTIL.BLI
;.EDIT 1743 ICE /OPT for adjustably dimensioned array reference
;; Fill in parent pointer field for array size expression
;; node created.
;; Module:
;; ACT1
; CDM,19-APR-83,SPR:10-33755
; A:SRC ACT1.BLI
;;.EDIT 1744 RESERVED FOR AUTOPATCH
;;.EDIT 1745 RESERVED FOR AUTOPATCH
;.ENDA
;.AUTOPATCH 7
;.EDIT 1746 ICE /DEBUG for adjustably dim array w expression subscripts
;; Subscript expression nodes for adjustably dimensioned arrays are
;; not evaluated for some expressions, so later compiler processing
;; finds an expression node where it wants a variable. Create a
;; .Innnn variable to assign the expression into, and store this
;; away in the dimension tables.
;; Module:
;; DOXPN
; CDM,2-MAY-83,SPR:20-19117
; A:SRC DOXPN.BLI
;;
;.EDIT 1747 ICE /OPT for some programs with array references.
;; The optimizer was trying to hash an array ref SKAR1, when it had
;; already hashed it SKAR2. This can NOT be allowed, since when an
;; array ref is hashed, the parent expression node pointing to the
;; array ref is replaced by a pointer to the hash table entry
;; (EHASH+n) for that array ref. Before this edit, the code would
;; try to hash a hash table entry, resulting in a most bizare
;; looking expression node whose parent pointer points to register
;; 0 or another hash table entry, rather than a valid parent.
;; Modules:
;; GCMNSB OPTMAC (no code changed in OPTMAC)
; CDM,4-MAY-83,SPR:10-33750
; A:SRC GCMNSB.BLI
;.EDIT 1750 Add new error message for "undeclared array"
;; Module:
;; CMND20 COMMAN ERROUT STA3
; MRB,5-MAY-83,SPR:10-33842
; A:SRC CMND20.MAC,COMMAN.MAC,ERROUT.BLI,STA3.BLI
;;
;.EDIT 1751 Suppress extra <cr> in listings
;; Don't put out <source line><cr><cr><lf> to listings, surpress
;; the second <cr> by not setting NOCR. Saved listing lines in
;; BACKLINE sometimes point to <source line><cr> rather than just
;; <source line>, as is expected. This happens when LEXICAL is
;; called with LOOK4CHAR set to something, finds the string, then
;; immediately finds a <cr><lf> before anything else.
;; Module: LEXSUP
; CDM,16-MAY-83,SPR:20-19111
; A:SRC LEXSUP.BLI
;;
;.EDIT 1752 ALLOW INTRINSIC FUNCTION NAMES AS STATEMENT FUNCTIONS
;; Don't assume that a function reference may be an intrinsic
;; function it it has been previously declared as a statement
;; function.
;; Module: EXPRES
; CDM,18-MAY-83,SPR:20-19228
; A:SRC EXPRES.BLI
;.EDIT 1753 BAD CODE FOR DO LOOP INDEX REFERENCES AS COMMON SUBS
;; Turn on the STOREFLG bit in common subexpressions of loop index
;; variables which have to be put into .Qnnnn variables because no
;; free registers are left. ((THIS IS A DAY 1 BUG.))
;; Module:
;; STREGA
; TFV,19-MAY-83,SPR:20-19158
; A:SRC STREGA
;;
;.EDIT 1754 CORRECT ERROR MESSAGES FOR ADJUSTABLY DIM ARRAY'S VARIABLES
;; Remove incorrect error message saying that the use of a variable
;; in an adjustably dimensioned array declaration is illegal before
;; defining it as a dummy in an ENTRY statement later in the
;; program. Also start giving error messages (again) for using
;; variables in these declarations that are not later declared to
;; be dummys or in common.
;; Modules:
;; ACT1 CODETA
; CDM,26-MAY-83,SPR:10-33859
; A:SRC ACT1,CODETA
;;.EDIT 1755 RESERVED FOR AUTOPATCH
;;.EDIT 1756 RESERVED FOR AUTOPATCH
;.EDIT 1757 BAD CODE FOR SOME ASSIGNMENTS WHEN OPTIMIZING
;; The assignment a = a * 3 + 4 generates the wrong code /opt if a
;; is targeted to a register. The P2PL1 (power of two plus one)
;; specop must be computed in a different register. the specop
;; EXPCIOP has the same problem. ((THIS IS A DAY 1 BUG.))
;; Module:
;; STREGA
; TFV,2-Jun-83,SPR:10-33567A
; A:SRC STREGA
;;.EDIT 1760 RESERVED FOR V6
;.EDIT 1761 ICE WHEN /OPT OF OPEN/CLOSE WITH NO DATAOPRS
;; Check for DIALOG/READONLY without args when stepping thru
;; specifier list.
;; Module:
;; UTIL
;; BCM,13-Jun-83,SPR:20-19276
;; A:SRC UTIL
;.EDIT 1762 BAD CODE /OPT FOR COMPLICATED ARRAYREF
;; Fix CMPLXARRAY to handle the case where the subscript expression
;; for a complicated arrayref propagates and folds to constant +
;; constant. Add in both constants to the ADDR field of the
;; arrayref and zero ARG2PTR. ((THIS IS A DAY 1 BUG.))
;; Module:
;; CMPLEX
; TFV,13-Jun-83,SPR:10-33767
; A:SRC CMPLEX
;;.EDIT 1763 RESERVED FOR AUTOPATCH
;;.EDIT 1764 RESERVED FOR AUTOPATCH
;.EDIT 1765 ICE FOR ENCODE/DECODE WITHOUT VARIABLE ARGUMENT
;; Fix KEYSCAN to check for ENCODE/DECODE without a third
;; positional argument. Improve error messages for mis-positioned
;; optional keyword arguments.
;; Module:
;; ACT0
; TGS,29-JUN-83,SPR:10-33978
; A:SRC ACT0
;;
;.EDIT 1766 LARGE ARRAY REF'S ADDRESS CALCULATIONS INCORRECT
;; Compiler puts constant array ref offset calculations in TARGADDR
;; whenever possible. TARGADDR is a half word quantity (17 bit
;; plus 1 bit for sign) which can not store large numbers. A large
;; positive number will be truncated and appear to be a negative
;; number when retrieved, since the retrieved offset is sign
;; extended. (Also negative numbers can appear to be positive the
;; same way.) Before storing into TARGADDR, check if the offset
;; will fit.
;; Modules:
;; ARRXPN CMPLEX TABLES
; CDM,15-JUL-83,SPR:NONE
; A:SRC ARRXPN,CMPLEX,TABLES
;;
;.EDIT 1767 CORRECT EDIT 1743
;; Correct edit 1743 which fills in parent pointers
;; indiscriminately without checking to see if they are expressions
;; first.
; CDM,20-JUL-83,SPR:20-19892
; A:SRC ACT1
;;
;.EDIT 1770 ARGUMENT CHECKING FOR NUMERIC ARRAY LENGTHS
;; Perform argument checking for length of numeric arrays when the
;; length is known at compile time. Create SECDESC to return the
;; length needed for a secondary descriptor (or 0 if none is
;; needed).
;; Modules:
;; RELBUF TABLES
; CDM,25-Jul-83,SPR:NONE
; A:SRC RELBUF,TABLES
;;.EDIT 1771 RESERVED FOR AUTOPATCH
;;.EDIT 1772 RESERVED FOR AUTOPATCH
;.EDIT 1773 UNDESERVED FID WHEN DATA NAME SAME AS PROGRAM NAME
;; When checking in DATALIST for an illegal attempt to initialize a
;; character function name in a DATA statement, do not issue a
;; fatal error if a DATA statement initializes a character variable
;; with the same name as a PROGRAM, SUBROUTINE or BLOCK DATA
;; statement.
;; Module:
;; ACT1
; TGS,9-AUG-83,SPR:10-34064
; A:SRC ACT1
;;
;.EDIT 1774 COMPILER ICE FOR LIBRARY FUNCTIONS IN BLOCK DATA PRGS
;; We were alocating a variable to save register 16 in .A0016
;; for block data subprograms, which is not necessary.
;; Module:
;; DOALC
; CDM,29-AUG-83,SPR:20-19510
; A:SRC DOALC
;;.EDIT 1775 RESERVED FOR AUTOPATCH
;;.ENDA 7-Sep-83
;.EDIT 1776 COMPILER ICE FOR ENCODE/DECODE WITH NAMELIST
;; Namelist I/O is illegal for ENCODE and DECODE. Check for it in
;; IOBLD.
;; Modules:
;; ERROUT STA0
; TFV,9-SEP-83,SPR:NONE
; A:SRC ERROUT,STA0
;.EDIT 1777 FIX ICE FROM WRITE(*,) AND REWIND ETC.
;; Make KSPEC and KUSPEC pass errors from KEYSCAN.
;; Also add explicit zero return for no error.
;; Module:
;; ACT0
; TJK,14-SEP-83,SPR:20-19546
; A:SRC ACT0
;;
;.EDIT 2000 ICE OR BAD CODE FOR CONSTANT APPEARING 2 X'S IN BASIC BLOCK
;; Statement IF (I1.EQ.1) MSK=MSK.AND..NOT.1 generates bad code
;; because it is noticed that the constant 1 already lives in a
;; register. This results in setting both A1SAMEFLG and
;; A1IMMEDFLG, something which should never be done. When the
;; "same" is set, we now clear the "immed". Otherwise we access
;; off a table in OPGNTA (accessed by the A1* flags) and ICE
;; (TOPS10) or create bad code (TOPS20).
;; Module:
;; Strega
; CDM,15-SEP-83,SPR:10-34135
; A:SRC STREGA
;;
;.EDIT 2001 INCORRECT ZERO-TRIP DO LOOPS WITH CONSTANT PROPAGATION
;; If STMTPROP is called because a DO-loop iteration count has
;; become constant due to constant propagation, it tries to
;; convert the loop to AOBJN form. However, in doing so it
;; ignores the sign of the count, so that a DO-loop with an
;; (ANSI) count of -5 is executed 5 times instead of 0 (or
;; 1 for F66).
;; Module:
;; PNROPT
; TJK,22-SEP-83,SPR:20-19572
; A:SRC PNROPT
;;
;.EDIT 2002 INCORRECT ZERO-TRIP DO LOOPS IN DOXPN
;; Fix evaluation of INT((M2-M1+M3)/M3) in DOXPN for cases in
;; which M3 is a constant +1 or -1. Previously it used
;; INT(M2-M1)+1 and 1-INT(M2-M1), which is incorrect when
;; -1 < (M2-M1) < 0 (first case) and 0 < (M2-M1) < 1 (second case).
;; Changed to INT((M2-M1)+M3) and INT(-((M2-M1)+M3)).
;; Module:
;; DOXPN
; TJK,23-SEP-83,SPR:20-19573
; A:SRC DOXPN
;;
;.EDIT 2003 ALLOW REAL AND LOGICAL VARIABLES AS FORMAT SPECIFIERS
;; Add check to IOBLD to allow a format specifier to be
;; a REAL or LOGICAL variable (instead of just INTEGER).
;; Also add check to IOFORMAT.
;; Modules:
;; STA0 CGSTMN
; TJK,27-SEP-83,SPR:20-19583
; A:SRC STA0,CGSTMN
;;.EDIT 2004 RESERVED FOR AUTOPATCH
;;.EDIT 2005 RESERVED FOR AUTOPATCH
;;.ENDA 3-Oct-83
;;
;.EDIT 2006 CORRECT BASIC BLOCK DEFINITION FOR END OF DO-LOOPS
;; Correct BASIC BLOCK definitions in routine CMPBLOCK of module
;; CMPBLO and routine ALCBLOCK of module ALCBLO, and have them
;; agree with each other. Have both routines call ENDSMZTRIP (a
;; routine added to REGUTL in this edit) to determine if a
;; statement ends a MAYBEZTRIP DO-loop. If so end the BASIC
;; BLOCK after that statement.
;; Modules:
;; ALCBLO CMPBLO REGUTL
; TJK,6-OCT-83,SPR:10-34231
; A:SRC ALCBLO,CMPBLO,REGUTL
;;
;.EDIT 2007 ICE FOR LEN, ICHAR WITH DYNAMIC CONCAT AS THE ARGUMENT
;; Do not make LEN or ICHAR inline functions when the argument is a
;; dynamic concatenation. Dynamic concatenation requires "marks"
;; and "unwinds". The existing code to do this requires an
;; argument list structure, but this is thrown away when the
;; functions are made inline.
;; Modules:
;; P2S1 TABLES
; CDM,6-OCT-83,SPR:NONE
; A:SRC P2S1,TABLES
;;
;.EDIT 2010 CORRECT OUTPUT OF SPECIAL CHARACTERS IN BLDMSG
;; Have BLDMSG substitute printable characters for control
;; characters and DEL.
;; Module:
;; INOUT
; TJK,10-OCT-83,SPR:10-34235
; A:SRC INOUT
;;
;.EDIT 2011 SAVE VARIABLE DO-LOOP STEP SIZE IN A TEMPORARY
;; Have all non-constant step size expressions be stored in
;; temporaries. Previously this was not done for any DATAOPR, so
;; if the step size was a variable which changed during execution
;; of the loop, the new value was used for the step (instead of
;; the original value, which is what should be used).
;; Module:
;; DOXPN
; TJK,13-OCT-83,SPR:20-19636
; A:SRC DOXPN
;;
;.EDIT 2012 FIX FOR COMPILER EDIT 1766
;; Fix edit 1766. Arguments to routine AROFCONST were incorrect.
;; Fix made after Inspection of code.
;; Module:
;; CMPLEX
; CDM,13-OCT-83,SPR:NONE
; A:SRC CMPLEX
;;
;.EDIT 2013 REMOVE ROUTINE CLERIDUSECNTS FROM DRIVER
;; Remove CLERIDUSECNTS and the call to it from MRP1. It
;; formerly cleared the IDUSECNT field of shared .I dimension
;; offsets, because it overlapped the IDTARGET field. IDUSECNT
;; is now a separate field. The routine failed to properly check
;; for .I variables, and sometimes cleared things it shouldn't.
;; Module:
;; DRIVER
; TJK,19-OCT-83,SPR:10-34268
; A:SRC DRIVER
;.EDIT 2014 TOPS20-STYLE COMMANDS MAY NOT WORK IN BATCH
;; When the command scanner is parsing commands in batch for
;; TOPS10 compatibility, it may not properly parse a legal
;; TOPS20-style command string.
;; Module:
;; CMND20
; TGS,25-OCT-83,SPR:20-19657
; A:SRC CMND20.MAC
;.EDIT 2015 FTNCMD ERROR WITH SWITCHES IN TOPS10 COMPATIBILITY
;; If a switch is given after the comma separating the list file
;; from the object file in a TOPS-10 compatibility command, the
;; error message "?FTNCMD Comma not given" is returned. (Accomplished
;; by V10 edit 2220).
;; Module:
;; CMND20
; TGS,25-OCT-83,SPR:NONE
; A:SRC CMND20.MAC
;;
;.EDIT 2016 ILLEGAL OPTIMIZED CODE MOTION OUT OF MAYBEZTRIP DO-LOOPS
;; Prevent GLOBELIM from calling HAULASS (which moves assignment
;; statements out of DO-loops) on potentially zero-trip DO-loops.
;; Module:
;; GCMNSB
; TJK,26-OCT-83,SPR:20-19684
; A:SRC GCMNSB
;.EDIT 2017 CORRECT ERROR MESSAGE SAYING VAR MUST BE INTEGER
;; Error message uppercase INTEGER to look like the declaration
;; statement INTEGER.
;; Module:
;; STA1
; CDM,9-NOV-83,SPR:NONE
; A:SRC STA1.BLI
;;.EDIT 2020 RESERVED FOR AUTOPATCH
;;.EDIT 2021 RESERVED FOR AUTOPATCH
;;.ENDA 9-NOV-83
;.ENDA
;.AUTOPATCH 8
;.EDIT 2022 DO NOT PUT OUT EXTRANEOUS 1045 REL BLOCKS
;; Writable overlay blocks (type 1045) were put out for the
;; following program:
;;
;; PROGRAM FOO
;; SAVE /FOO/
;; END
;;
;; ZSAVEOUT deletes undeclared common blocks (FOO above) from the
;; list of those to put in the rel block, but does not check to see
;; if there is a reason to put ANY 1045 block out after deleting
;; these undeclared commons. If there are no delcared commons, and
;; no local variable to SAVE, then do not put out a 1045 block.
;; Module:
;; RELBUF
; CDM,1-DEC-83,SPR:NONE
; A:SRC RELBUF.BLI
;;
;.EDIT 2023 INCORRECT REGISTER ALLOCATION FOR CHARACTER ARRAYS IN IO
;; Have ALCIOCALL call ALCTARY for character array references in
;; an IO list when there aren't enough free regs. Previously the
;; TARGADDR field wasn't being set, resulting in incorrect code,
;; and sometimes causing an ICE or illegal instruction trap.
;; Module:
;; STREGA
; TJK,12-DEC-83,SPR:NONE
; A:SRC STREGA.BLI
;;
;.EDIT 2024 INCORRECT TYPE OF LOGICAL INTRINSIC FUNCTIONS
;; Incorrect definition of macro LG, used to fill in values in
;; PLIT ZATTRIBUTES (globally named by LIBATTRIBUTES). Convert
;; macro to a bind, and use symbolic names instead of numbers.
;; Module:
;; GLOBAL
; TJK,16-DEC-83,SPR:NONE
; A:SRC GLOBAL.BLI
;;
;.EDIT 2025 CORRECT ARGUMENT COUNT FOR INLINE FUNCTIONS
;; P2SKCONCAT doesn't handle inline functions correctly.
;; Specifically, it makes a redundant call to P2SILF, and more
;; importantly it doesn't correctly update the argument count,
;; which can result in incorrect code. This corrects edit 1655.
;; Module:
;; P2S1
; TJK,21-DEC-83,SPR:NONE
; A:SRC P2S1.BLI
;;.EDIT 2026 RESERVED FOR AUTOPATCH
;;.EDIT 2027 RESERVED FOR AUTOPATCH
;;.ENDA 27-DEC-83
;;
;.EDIT 2030 INCORRECT FOLDING OF NEGATED EXPONENTIATION
;; P2SKARITH doesn't check to see if ARSKOPT returns a constant
;; with NEGFLG set. This case should be reduced to a new negated
;; constant with NEGFLG cleared, since some routines which call
;; P2SKARITH ignore NEGFLG when the returned expression is a
;; constant.
;; Module:
;; P2S1
; TJK,4-JAN-84,SPR:20-19858
; A:SRC P2S1.BLI
;;
;.EDIT 2031 BAD CONSTANT PROP OF NEG ARRAY REF INDEX /OPT
;; LOKDEFPT had a bad case for array references. Specifically,
;; it never called CONS2DEF after a recursive call to itself.
;; Among other things, this allowed constants with neg flags to
;; go uncorrected, resulting in bad code.
;; Module:
;; PNROPT
; TJK,6-JAN-84,SPR:NONE
; A:SRC PNROPT.BLI
;.EDIT 2032 NO DEFAULT TEXT IN .CMTOK AFTER FILENAME PARSE
;; Remove the default "+" which was available after parsing a
;; source filespec. If the .CMTOK function of the COMND% JSYS
;; is changed, the default for a .CMTOK field will be parsed
;; before the confirm. This will mean that the command scanner
;; sees all command lines ending with a "+", which is illegal.
;; (Accomplished in V10 by edit 2263).
;; Module:
;; CMND20
; TGS,10-JAN-84,SPR:NONE
; A:SRC CMND20.MAC
;;.EDIT 2033 RESERVED OR AUTOPATCH
;;.EDIT 2034 RESERVED OR AUTOPATCH
;;.ENDA 20-JAN-84
;.EDIT 2035 ICE FOR FILE MISSING THE CRLF ON LAST LINE
;; Fix edit 1640. A file missing the CRLF on the last line causes
;; an ICE. LEXICA was not setting LASTLINE properly when EOF was
;; detected.
;; Module:
;; LEXICA
; TFV,16-Feb-84,SPR:20-19863
; A:SRC LEXICA.BLI
;;.EDIT 2036 RESERVED FOR AUTOPATCH
;;.EDIT 2037 RESERVED FOR AUTOPATCH
;;.ENDA 16-FEB-84
;;
;.EDIT 2040 INCONSISTENT REG ALLOC AND CODE GEN ORDER OF IO KEYWDS
;; Reorder calls for complexity, register allocation, and code
;; generation of I/O keywords. Most of this was already done in
;; V10 in edit 2201, although register allocation for FIND was
;; still incorrect.
;; Modules:
;; CGSTMN STREGA
; TJK,23-FEB-84,SPR:10-34497
; A:SRC CGSTMN.BLI,STREGA.BLI
;;
;.EDIT 2041 INCORRECT REGISTER ALLOCATION IN LHINREGALC
;; Make check for ARG2NODE consistent with check for ARG1NODE in
;; LHINREGALC. Before this edit, CMPRHINLH was being called when
;; it shouldn't. This routine was in turn calling CMPNODINLH,
;; which set TREEPTR to the ARG2PTR of the expression passed to
;; it for a call to ALCINREG. When the expression had no
;; ARG2PTR, TREEPTR was being set to zero and ALCINREG looped
;; recursively until the stack overflowed.
;; Module:
;; STREGA
; TJK,23-FEB-84,SPR:20-19950
; A:SRC STREGA.BLI
;;
;.EDIT 2042 REFLECT OPTMAC'S UPDATED VERSION NUMBER
;; Teach Autopatch about the change in OPTMAV. (No code change)
; TGS,24-FEB-84,SPR:NONE
; A:SRC OPTMAC.BLI
;;
;.EDIT 2043 PUT LIMIT= KEYWORD BACK FOR OPEN AND CLOSE
;; Have OPEN and CLOSE recognize the LIMIT= keyword once again.
;; This keyword takes an integer expression. Entries were added
;; to the tables OPNKWD and IOCKVEC in OPENCLOSE, and KEYWFLAG in
;; CFCHECK. LIMIT= is illegal for INQUIRE and is flagged as both
;; an ANSI and a VAX incompatibility. Note that this edit was
;; somewhat different for V7A and V10. Among other things, V7A
;; didn't have to change TABLES but V10 did.
;; Module:
;; STA1 TABLES
; TJK,24-FEB-84,SPR:10-34503
; A:SRC STA1.BLI,TABLES.BLI
;;
;.EDIT 2044 UNDESERVED ?COMMAND TOO LONG ERROR UNDER BATCH
;; "Command too long for internal buffer" error when giving
;; many command strings in batch. Correct .CMCNT in the COMND%
;; state block so it correctly stores free character count.
;; (Accomplished in V10 by edit 2262).
;; Module:
;; CMND20
; TGS,6-MAR-84,SPR:20-20007
; A:SRC CMND20.MAC
;;.EDIT 2045 RESERVED FOR AUTOPATCH
;;.ENDA 23-MAR-84
;;
;.EDIT 2046 ICE /OPT IN SETPVAL DUE TO ZERO PARENT POINTER
;; DOVARASGN was creating assignment statements with a zero
;; parent pointer in the RHS. Fix it to fill in the parent
;; pointer.
;; Module:
;; IOPT
; TJK,28-MAR-84,SPR:20-20059
; A:SRC IOPT.BLI
;;
;.EDIT 2047 ICE ON WRITE STATEMENT WITH COMPLICATED I/O LIST
;; ALCIOCALL was allocating single-word I/O list elements to
;; registers when double precision arithmetic was involved. The
;; result was that alternating registers were being used. This
;; threw off the complexity calculation, since there were many
;; free registers but not enough consecutive register pairs.
;; This edit prevents ALCINREG from being called for an I/O list
;; element if the I/O statement has the PAIRMODEFLG flag set
;; (i.e., the global flag PAIRMODE is set) and there are fewer
;; then 2 free register pairs.
;;
;; Note that this still doesn't correct all cases of this
;; problem. To properly handle all cases, a routine must be
;; added which is similar to ALCINTMP but which forces the value
;; to memory. In addition, register allocation for double
;; precision array references should be improved to require no
;; more than one free register pair.
;; Module:
;; STREGA
; TJK,20-APR-84,SPR:20-20107
; A:SRC STREGA.BLI
;;
;;.EDIT 2050 RESERVED FOR AUTOPATCH
;.ENDA
;.AUTOPATCH 9
;.EDIT 2051 BAD CODE FOR CHARACTER*(*) ENTRY POINTS
;; Fix FUNCGEN to set the character length for entry points in
;; character functions properly. They were inheriting the length
;; from the last CHARACTER declaration.
;; Module:
;; ACT1
; TFV,27-APR-84,SPR:20-20125
; A:SRC ACT1.BLI
;;
;.EDIT 2052 BAD CODE FOR DO-VARIABLE IN SUBSTRING EXPRESSION
;; CMPLXSUBSTR was incorrectly clearing some flags (specifically,
;; INREGFLG) when the lower bound (minus 1) was a REGCONTENTS
;; node. This edit adds a test so that these flags are only
;; cleared when they really should be.
;; Module:
;; CMPLEX
; TJK,16-MAY-84,SPR:10-34699
; A:SRC CMPLEX.BLI
;;
;.EDIT 2053 UPDATE COMPILER COPYRIGHT
;; Module:
;; MAIN
; CDM,2-MAY-84,SPR:NONE
; A:SRC MAIN.BLI
;;
;;.EDIT 2054 RESERVED FOR AUTOPATCH
;;.ENDA 18-MAY-84
;;
;.EDIT 2055 CORRECT EDIT 1732
;; Edit 1732 did not check for a PARAMETER constant not being of
;; type character so that a illegal constant could make the
;; compiler get a non informative compiler error (illegal
;; instrucion) before the problem can be properly reported to the
;; user.
;; Module:
;; ACT0
; CDM,30-MAY-84,SPR:NONE
; A:SRC ACT0.BLI
;;
;.EDIT 2056 BAD CODE FOR COMPUTED GOTO AT END OF DO-LOOP
;; Fix CGCGO to generate correct code for computed GOTOs when
;; they are the terminal statements of DO-loops. Previously, if
;; the index value was out of range, control would be transferred
;; to the next statement and out of the loop.
;; Module:
;; CGSTMN
; MEM,4-JUN-84,SPR:10-34700
; A:SRC CGSTMN.BLI
;;
;.EDIT 2057 DO-REGISTER NOT SUBSTITUTED INTO CONCAT ARGS
;; Add missing case to LEAFSUBSTITUTE so that argument lists for
;; concatenation nodes are walked. LOKCALST is used to walk the
;; argument list. A parameter was added to LOKCALST to indicate
;; that the argument list is from a concatenation node and that
;; the first argument should be skipped.
;; Modules:
;; COMSUB GOPTIM UTIL
; MEM,11-JUN-84,SPR:20-20187
; A:SRC COMSUB.BLI,GOPTIM.BLI,UTIL.BLI
;;
;.EDIT 2060 RESERVED FOR AUTOPATCH
;.EDIT 2061 RESERVED FOR AUTOPATCH
;;.ENDA 22-JUN-84
;;
;.EDIT 2062 INCORRECT (INNERMOST) DO LOOP BOUNDS /OPTIMIZE
;; Bounds are incorrect since statement's right hand expression is
;; not updated after call to CHKPROP where the value is changed.
;; TJK/CDM. (Edit already done by V10 edit 2374.)
;; Module:
;; PNROPT
; CDM,26-JUN-84,SPR:10-34763
; A:SRC PRNOPT.BLI
;;
;.EDIT 2063 NO ERROR IS GIVEN FOR NAMELIST I/O IN A REREAD STATEMENT
;; Give an error for NAMELIST I/O with REREAD, ENCODE, and DECODE.
;; Modules:
;; ERROUT STA0
; TFV,29-JUN-84,SPR:20-20237
; A:SRC ERROUT.BLI,STA0.BLI
;;
;.EDIT 2064 MEMORY PROTECTION VIOLATION IN FORTB
;; Keep count of spaces placed in buffer to get to start of bad
;; statement in routine BACKTYPE.
;; Modules:
;; LISTNG
; PLB,3-JUL-84,SPR:20-34728
; A:SRC LISTNG.BLI
;;
;.EDIT 2065 CHARACTER INTRINSIC FUNCTION DOES NOT WORK IN IOLST
;; Although a .Dnnnn compile time constant descriptor exists
;; for the result, a two word .Qnnnn variable is also allocated
;; for the result, a DMOVEM 0,.Qnnnn is generated, and the
;; .Qnnnn appears in the IOLST argblock instead of the .Dnnnn
;; descriptor. The fix is easy. ALCIOLST has to not allocate a two
;; word .Qnnnn variable for character function results. Also it must
;; not set STOREFLG.
;; Module:
;; STREGA
; MEM,3-JUL-84,SPR:10-34774
; A:SRC STREGA.BLI
;;
;;.EDIT 2066 RESERVED FOR AUTOPATCH
;;.EDIT 2067 RESERVED FOR AUTOPATCH
;;.ENDA 19-JUL-84
;;
;.EDIT 2070 EXTRANEOUS COPY OF UNREFERENCED CMPLX AND DBL PREC VARIABLES
;; Set ENTNOCOPYFLG of complex and double precision variables that are
;; never referenced in a statement function and hence should not be
;; allocated.
;; Module:
;; DOALC
; MEM,28-AUG-84,SPR:10-34843
; A:SRC DOALC.BLI
;;
;;.EDIT 2071 RESERVED FOR AUTOPATCH
;;.ENDA 20-SEP-84
;;
;.EDIT 2072 BAD CODE GENERATED, REGISTER USED TWICE
;; Prevent a register from being used twice in ALCMEM. A separate
;; register is needed, the allocated register was being loaded
;; twice, clobbering the old value.
;; Module:
;; STREGA
; DCE,10-OCT-84,SPR:20-20395
; A:SRC STREGA.BLI
;;
;.EDIT 2073 INCORRECT ERROR MESSAGE; NO VARIABLE NAME GIVEN
;; In routine CNVCONST, error message E160 was being used, which
;; expects a variable name. Since none can be given, message E163
;; is used instead which doesn't expect a name.
;; Module:
;; ACT0
; CDM,12-OCT-84,SPR:NONE
; A:SRC ACT0.BLI
;;
;.EDIT 2077 NO WARNING FOR PASSING BAD ARGUMENTS TO A STATEMENT FUNCT
;; Give a warning when a constant is passed to a dummy
;; argument expecting a routine.
;; Modules:
;; EXPRES, ERROUT
; RJD,11-FEB-85,SPR:10-35087
; A:SRC EXPRES.BLI,ERROUT.BLI
;;
;.EDIT 2100 UNREFERENCED ARRAYS PASSED TO SUBROUTINES GENERATE BAD CODE
;; Set ENTNOCOPYFLG flag for unreferenced formal arrays. Only
;; call ADJGEN for arrays that are allocated.
;; Modules:
;; DOALC, DOXPN
; RJD,19-FEB-85,SPR:20-20575
; A:SRC DOALC.BLI,DOXPN.BLI
;.ENDA
;.ENDV
;.ENDR REVISION HISTORY
Edit numbers 1733-2177 reserved for V7A
***** End Revision History *****
***** Begin Version 10 *****
2200 TFV 23-Mar-83
INQUIRE implementation. Add new statement to FIRST and TABLES.
Merge semantics into OPENCLOSE. Add new error messages for
INQUIRE. Link INQUIRE statements into IOFIRST/IOLAST linked
list. Do skeleton optimizations for all keyword values.
Modules:
ERROUT FIRST SKSTMN SRCA STA1 TABLES
2201 TFV 30-Mar-83
Finish INQUIRE implementation. Do complexity walk and local
register allocation for INQUIRE arguments. Add INQUIRE to
FINDMARK in case FILE= is a dynamic concatenation. Add code
patterns to generate calls to INQF. (INQUIRE by file) and INQU.
(INQUIRE by unit). Write CGINQUIRE to generate the calls.
Modules:
CGSTMN OPGNTA REGAL2 STREGA
2202 CDM 7-Apr-83
Widen IDDATVAL, DATARPT to a full word each. Remove calls to
EXTSIGN macro for these new larger fields. Comment dimension
structures to show the horrible * TWO WAYS * of accessing
subscripts.
Modules:
DATAST FIRST TABLES
2203 TFV 7-Jun-83
Fix allocation for FMT= and FILE= in I/O statements. Only
allocate a .Qnnnn variable for character expressions, not
character constants and variables.
Module:
STREGA
2204 TFV 20-Jun-83
Add definition point handling for INQUIRE and fix deficiencies
with I/O definition points and the global optimizer. All I/O
statements can have IOSTAT= which is the definition point for
its argument. Also must check for function call arguments in
the expressions for UNIT, FMT, REC, and IOSTAT and all
OPEN/CLOSE/INQUIRE specifiers. Most INQUIRE arguments are also
modified by the INQUIRE statement. Fix ASCRIBE to count I/O
statements as CALLs. STOP, PAUSE, OPEN, CLOSE, and INQUIRE are
one call; READ through REREAD are at least two calls (e.g. IN.
and IOLST.). Fix MATLOK to test all I/O statement END and ERR
labels. It has to generate a new label for the
materializations.
Modules:
DEFPT PH3G
2205 CDM 21-Jun-83
Add manipulation of EFIW tables to NEWENTRY, TBLSEARCH,
TESTENTRY, THASH. Add routine MAKEFIW.
Also kill BASEPOINT, BP, and BPR, which are macros defined as
the global BASEPTR.
Modules:
FIRST GLOBAL SRCA TABLES
2206 TFV 27-Jun-83
Add case to LPIXSUB for INQUIRE. Add case to GRAPH for INQUIRE
statements. It checks for ERR= branches and hooks them up.
Also make MISCOCI in UTIL handle FILE= sustitution for
OPEN/CLOSE/INQUIRE.
Modules:
DOALC GRAPH UTIL
2207 CDM 21-Jul-83
Reformat and comment equivalence routines ALLOCAT, EQERRLIST,
LINKGROUPS, ELISTSEARCH, GRPSCAN, PROCEQUIV. Moved macros
MERIT, USRARGUSE, LIBARGUSE, ORFIXFLG, OMOVDCNS from OPTMAC to
FIRST. They overlap IDADDR for code /OPT. Moved IDDOTO which
overlaps IDSYMBOL. It is in poor taste to hide overlaps of
fields in another module!!
Modules:
FIRST OPTMAC OUTMOD
2210 AHM 27-Jul-83
Rename DUMPDIM and DUMPFORMAT to DMPDIM and DMPFORMAT so that
my interactive dump routines for SIX12 can use symbols of the
form DUMP?? without encroaching on the compiler's name space.
Modules:
DEBUG OUTMOD P3R PH3G PHA3
2211 TFV 18-Aug-83
Add INQUIRE to case statement in LEAFLOOKER, PROPCASE,
LOKINDVAR, and ZSTATEMENT. In LOKINDVAR, check more I/O
specifiers for references to the DO loop index. Create routines
ZDEFIO and ZDEFOCI to zero defpts for I/O specifiers.
Modules:
PH3G PNROPT TSTR VER5
2212 CDM 30-Aug-83
Fix for edit 2211. Check if IOFORM is a half word of -1 rather
than a full word.
Module:
VER5
2213 RVM 11-Sep-83
Hide some symbol definitions from DDT by changing "=" to "==".
(These sysmbols were obscuring op codes.)
Module:
CNSTCM
2214 TJK 26-Sep-83
Fix routine ALCBLOCK to correctly undo an AOBJN loop control
word.
Module:
ALCBLO
2215 TJK 26-Sep-83
Have routine STMTPROP check for zero-trip (or one-trip for F66)
loops, and have it clear MAYBEZTRIP if not zero-trip.
Module:
PNROPT
2216 PLB 27-Sep-83
Generate OWG byte pointers iff OWGBPSECTION contains a non-zero
section number.
Modules:
GLOBAL, TABLES, DATAST, RELBUF, OUTMOD
2217 TJK 28-Sep-83
Have STMTPROP check to see if CTLNEG is set (for DO-loops),
and if so ICE the compiler.
Module:
PNROPT
2220 RVM 29-Sep-83
Make the command scanner accept the revised TOPS-20 command
syntax and implement the extend switch. Also, a problem was
fixed that prevented switches from appearing between the comma
and listing filespec in a TOPS-10 command under compatibility
scanning. (This last problem was fixed in V7a as edit 2015.)
Module:
CMND20
2221 RVM 29-Sep-83
Add new feature test FT612 to control debugging with SIX12.
Change how feature tests so that they receive their default
values if their symbols are not defined.
Module:
CMND20
2222 RVM 29-Sep-83
Keep LEXICA from setting the PSECT fields everytime it sees an
identifier.
Module:
LEXICA
2223 TJK 30-Sep-83
Have STMTPROP check to see if CTLNEG is set (for DO-loops),
and if so have it clear CTLNEG and negate the DO-loop control
expression (which is a constant), instead of generating an
ICE. Also have it defer creating any new constants until the
end of the select case for a DO-loop. Also remove external
declaration of CGERR.
Module:
PNROPT
2224 RVM 3-Oct-83
Set the PSECT fields for arrays to the proper values under
/EXTEND.
Modules:
ACT1 DRIVER
2225 TFV 4-Oct-83
Fix lexical processing of octal constants. Count the leading
zeros. Up to 12 digits is OCTAL, 13 to 24 digits is DOUBLOCT,
more than 24 is an error.
Module:
LEXICA
2226 TJK 6-Oct-83
Remove routine STREGA from module STREGA (an ancient routine
which is never called anywhere).
Module:
STREGA
2227 TJK 21-Oct-83
Add ENDSBBLOCK to REGUTL. This routine determines whether or
not the current statement (pointed to by CSTMNT) ends a basic
block. Also rewrite ALCBLOCK and main routine of CMPBLOCK to
call this routine. Also added external declarations for
ENDSBBLOCK, removed external declarations for ENDSMZTRIP (now
called only by ENDSBBLOCK), made ENDSMZTRIP non-global, and
fixed some comments.
Modules:
ALCBLO CMPBLO REGUTL
2230 CDM 1-Nov-83
Move DO node flags from FIRST to TABLES where they belong.
Modules:
FIRST TABLES
2231 AHM 6-Nov-83
Undo part of edit 2230. Put DOFLGAUX field back in to DO
statement nodes. I forgot that it was used in DUMP.
Module:
FIRST
2232 RVM 8-Nov-83
Allocate variables into the proper psect. The IDADDR and
IDPSCHARS now get their values based on the IDPSECT and
IDPSCHARS fields, respectively. IDPSECT and IDPSCHARS contain
"psect indexes," which are indexes into the vector PSECTS.
The PSECTS vector contains the next allocated offsets into the
low and high segments (/NOEXTEND) or the next allocated
offsets into .DATA., .CODE., or .LARG. psects (/EXTEND).
Pretty much, this edit consisted of replacing LOWLOC and
LARGELOC by PSECTS[.SYMBOL[IDPSECT]].
Module:
OUTMOD
2233 AlB 9-Nov-83
Delay computation of total size of common (COMTSIZ) until
after PROCEQUIV has processed all Equivalences. COMTSIZ
will now reflect the fact that common blocks may have been
extended by PROCEQUIV.
Module:
OUTMOD
2234 AlB 9-Nov-83
Add fields to Common Block table and Equivalence Group table
to allow the storing of Psect information.
Module:
FIRST
2235 AlB 11-Nov-83
Change coding for COMMON/EQUIVALENCE processing for Extended
Addressing. The compiler will now assign to the .LARG. psect
all non-common variables that are equivalenced to one or more
.LARG. variables, and will assign to the common psect all
variables which are equivalenced to a common variable.
Also change to FIRST to better present the changes in Edit 2234.
Modules:
OUTMOD, FIRST
2236 AlB 11-Nov-83
Move the initialization of the COMPSECT field in Common Block entries
out of OUTMOD and into SRCA.
Modules:
OUTMOD, SRCA
2237 TJK 14-Nov-83
Rewrite code in SORTNMAKE (defined in GBLALLOC) which puts
elements of CHOSEN with highest merit in GLOBREG. Previously
it stopped looking after GLOBREG was full, which could
severely pessimize the final choices made. It also wrote one
entry too many, a dangerous practice. In addition to this
change, remove some code from ASCRIBE added in edit 2204.
Module:
PH3G
2240 AlB 28-Nov-83
Force EQVPSECT to equal COMPSECT when the EQUIVALENCE statement
sees a Common element.
Module:
STA3
2241 TFV 7-Dec-83
Implement FORTRAN-77 continuation line processing. Blank,
comment, debug, and remark lines may appear between an initial
line and its continuation lines and between continuation lines.
Also rework the lexical debugging trace facility to generate
symbolic output. To use this facility, DRIVER, INOUT, LEXICA
and LEXSUP must be compiled with DBUGIT=1 (this bind is in
DBUGIT.REQ), Specifying the /BUGOUT switch outputs the data to
the listing file. See LEXSUP for a description of the BUGOUT
values.
Modules:
LEXICA LEXSUP
2242 RVM 12-Dec-83
The /NOEXTEND switch was not using the proper offset into ONFLG
and OFFFLG for the SW.EXT flag. Thus, /NOEXTEND did not cancel
/EXTEND. Also, make /BUGOUT imply /LIST, since this allows code
to be removed from LEXICA (which is almost to big to compile!).
Module:
CMND20
2243 CDM 13-Dec-83
Detect AOBJN DO loop register indexes into large arrays (arrays
in .LARG.). This is done in the skeleton optimizer, and will
disable the DO loop from using an AOBJN instruction for the
cases that can be caught this early in compilation. This will
prevent the negative left half of the AOBJN register appearing
to be an invalid section number when indexing into the array
when running in a non-zero section.
Modules:
P2S1 SKSTMN
2244 CDM 13-Dec-83
Eliminate AOBJN DO loop register indexes into large arrays
(arrays in .LARG.) during code generation. Create a new
STORECLS node, STRHAOBJN to copy the right hand half of the
AOBJN register into another register. Otherwise, the negative
left half of the AOBJN register will appear to be an invalid
section number. This is to catch the cases that the skeleton
optimizer (edit 2243) can not.
Modules:
CGEXPR CMPLEX OPGNTA REGAL2 TABLES
2245 CDM 18-Dec-83
Improve argument checking. Subroutine calls with no arguments
would not output argument checking (1120) rel blocks for Link
unless /DEBUG:ARGUMENTS was given. Now always output the the
rel block, and change the call to the subroutine not to have its
own unique argument block of 0, but instead use the shared
ZERBLK which everyone else with no arguments shares. This
simplifies code in several places.
2246 AlB 20-dec-83
Add the /FLAG and /NOFLAG switches for Compatibility Flagging.
Add bits to flag word F2 for FLAG:STANDARD and /FLAG:VAX.
Modules:
CMND20.MAC, COMMAN.MAC, IOFLG.BLI
2247 AlB 22-Dec-83
1) Added all warning messages for Compatibility Flagging
2) Added CFLAGB and CFLEXB routines to INOUT. These routines
put out flagger warnings for certain types of checks.
3) Added Flagger code to catch the old-style I/O statements
Modules:
ERROUT, INOUT, STA0, STA1, STA3
2250 AlB 22-Dec-83
1) Added Flagger warnings for Data Declarations
2) LOGICAL*2 now allowed, with warning
Module:
STA2
2251 CDM 22-Dec-83
Add new global variable BIGCONCAT to declare the size (50,000
for now) of the largest concatenation allowed as fixed (CONCTF)
or known maximum (CONCTM) in length. If the concatenation is
larger than this, then the concatenation will be dynamic
(CONCTV) so that it will use the character stack.
Modules:
CMND20 GLOBAL P2S1
2252 AlB 27-Dec-83
Various compatibility flagger checks, plus
change to edits 2247 and 2250 to use line number from ISN instead
of LEXLINE.
Modules:
STA0, STA1, STA2, STA3
2253 AlB 28-Dec-83
Various Compatibility flagger checks.
Modules:
ACT0, ACT1, ARRXPN, ERROUT, EXPRES
2254 AHM 28-Dec-83
Make type 1070 local and global symbol definitions use 30 bit
relocation instead of 18 bit RH relocation. Unlike type 2
blocks, 1070 blocks do not use LINK's kludge of relocating the
whole symbol value if the left half is zero.
Module:
RELBUF
2255 AlB 29-Dec-83
Added compatibility flagging for mixed logical and numeric.
Modules:
ERROUT, EXPRES, VLTPPR
2256 AlB 29-Dec-83
Added /LIST and /CREF to the INCLUDE statement, so as to be more
compatibile with the VAX.
Added compatibility flagging for the INCLUDE statement.
Modules:
ERROUT, STA2
2257 AlB 3-Jan-84
Added compatibility flagging for FORMAT statement.
Modules:
ERROUT, FORMAT
2260 AlB 4-Jan-84
Added compatibility flagging to stuff touched by LEXICA.
Module:
LEXICA
2261 AlB 5-Jan-84
Added compatibility flagging for
1) PRINT statement with keyword specifiers
2) WRITE statement with default unit
3) Concantenation of variables with length (*)
4) INCLUDE statement
Modules:
ACT0, ERROUT, STA0, STA2
2262 RVM 5-Jan-84
Fix bug that caused the "Command too long for internal buffer"
message to be given when a great many command strings were
given the compiler under batch. The bug had two causes.
First, edit 1603 disabled CONTROL/H error recovery under batch
by reseting some of the words in the COMND% state block. It
turns out the the .CMINI function would not reset the .CMCNT
word if the state block had been so munged. Second, when
command strings where put into the COMND% buffer "by hand,"
the command scanner would subtract the length of the command
from .CMCNT (the count of free characters in the command
buffer). This is incorrect since .CMCNT is the space left
after the text which has been parsed in the buffer. No text
in the buffer had been parsed yet.
Module:
CMND20
2263 RVM 9-Jan-84
Remove the default "+" which was available after parsing a
source filespec. A Change to the .CMTOK function of the
COMND% JSYS now causes the default for a .CMTOK field to be
parsed before a confirm. This ment that the command scanner
saw all command lines ending with a "+", which is illegal.
(This was fixed in V7a by edit 2032.)
Module:
CMND20
2264 PLB 11-Jan-84
Force OWGBPSECTION to 1 when /EXTEND typed. Zero at REPARSE.
This means the compiler will always output OWGs under /EXTEND.
2265 TFV 12-Jan-84
Increase POOLSIZE to 6000 words so we can compile programs with
large blocks of comment lines. The standard allows unlimited
numbers of comment lines between initial and continuation lines.
Modules:
CMND20 FIRST LEXAID
2266 AHM 13-Jan-84
Change the origin of the .CODE. psect (CODEORG) in RELINIT
from 1,,140 to 1,,1000 so that the program's fake JOBDAT page
is not read only.
Module:
OUTMOD
2267 AHM 16-Jan-84
Complete the work of edit 2254 (I hope). Make type 1070 RH
chained and additive fixups also use 30 bit relocation instead
of 18 bit RH relocation.
Module:
RELBUF
2270 AlB 17-Jan-84
Add compatibility flagging to check identifiers with more than
one use. For those identifiers that have a dangerous conflicting use,
fatal errors are put out; for non-dangerous items, 'VAX incompatibility'
warnings are issued.
Items that appear in a NAMELIST list now get the INNAM attribute
set during NAMELIST parsing, instead of in PH3G, so that compatibility
flagging can be done during the syntax phase.
Modules:
ACT0 ACT1 ERROUT PH3G STA2 STA3
2271 AlB 18-Jan-84
Several Compatibility Flagger checks:
1) Non-Constant substring bounds in DATA statements
2) Single subscript in multi-dimensioned array (EQUIVALENCE)
This subscript is now range-checked, with a warning (not fatal)
message if out of bounds.
3) Numeric/Logical mix in EQUIVALENCE
4) EQUIVALENCE and COMMON now warn about Char/Non-Char mix only if
compatibility flagging is being done
5) Extended range of DO statement
Modules:
ARRXPN ERROUT ERROVD ERROVR GRAPH OUTMOD
2272 TJK 20-Jan-84
Remove code from P2SKCONCAT which folds top-level
subconcatenation nodes in a concatenation argument list,
modify it and make it into a new routine called P2SKFOLD.
Have P2SKCONCAT call this new routine (P2SKCONCAT is
functionally unchanged). Also have SKCALL call P2SKFOLD if
the CALL statement is really a character assignment or
character statement function so that subconcatenations are now
folded in these cases. Also fix SKCALL to set AVALFLG when an
expression is reduced to a DATAOPR due to skeleton
optimizations.
Modules:
P2S1 SKSTMN
2273 AlB 20-Jan-84
The rework of LEXICA for the comment lines disturbed the processing
of the ACMENTREMARK macro. In the new form, that macro is called
when a comment line is recognized, not just when the "!" is seen
on a line. This edit adds code to handle the various 'funny character
in column 1' flagger warnings.
2274 AlB 24-Jan-84
Added compatibility flagger checks for I/O keywords in OPEN, CLOSE
and INQUIRE statements.
Modules:
ERROUT STA1
2275 CDM 24-Jan-84
Move zeroing of DOWDP from routine LPIXSUB (substitute
REGCONTENTS nodes for DO induction variable) to routine CMSTMN
(complexity walk for statements). It was being zeroed before
the complexity for the last statement of the DO loop was being
processed. This meant that it was not known in the processing
of the last statement of a DO loop that the statement was in an
innermost DO loop.
Modules:
DOALC STREGA
2276 AlB 26-Jan-84
Fixed bug with functions being passed as arguments to subroutines.
This bug was caused by edit 2270.
Added compatibility flagging to check for items which conflict with
VAX intrinsic function names (functions that we don't use), and for
those functions/subroutines which either do not exist on VAX/ANSI or
for which there is some incompatibility.
Modules:
ACT1 ERROUT STA0 TABLES
2277 AlB 26-Jan-84
Removed some entries from the function compatibility tables
CFTABLEN and CFTABLEV. The entries that were removed were for
the bit manipulation functions and subroutines that are being
added to Fortran-10/20 to make us more compatible with the VAX.
Made the compatibility test less stringent for the case where we
have a name that is an intrinsic function on the VAX, but is not
an intrinsic function for Fortran-10/20.
Added an element to CASE set in the NAMDEF routine. This has been
missing (and thus a bug) since at least edit 1514. It should have
been a null( i.e. BEGIN END) element.
The new element does compatibility flagging for the INTRINSIC
statement, to wit: If the INTRINSIC routine being defined is not
an intrinsic function on the VAX, a warning is issued.
Modules:
ACT1 STA0
2300 AlB 27-Jan-84
Fixed misspelling of entry in CFTABLEN & CFTABLEV.
Changed the order of tests in COMPFLAG, so that only things which
look like function names are tested. This prevents the testing of
all ordinary things, and thus speeds the flagger process considerably.
Modules:
ACT1 STA0
2301 RVM 28-Jan-84
Make the compiler know about the MIL SPEC/VAX FORTRAN bit
manipulation functions. They are new INTRINSIC functions.
Modules:
GLOBAL GNRCFN
2302 TJK 2-Feb-84
Add new flag IDCLOBB to the IDFNATTRIB field of a symbol table
entry. This flag is set for certain library routines (called
as subroutines). It indicates that ACs are not preserved by
the call.
Have CHASGN generate calls to CASNM. instead of CHASN. for
single-source character assignments, and CNCAM. instead of
CONCA. for character concatenation assignments. Also have it
set IDCLOBB for these routines, which don't preserve ACs.
Replace a check for CONCA. with a check for CNCAM. in SKCALL.
Have ALCCALL mark registers 2-15 (octal) as being clobbered if
IDCLOBB is set.
Modules:
FIRST SKSTMN STA0 STREGA
2303 AlB 3-Feb-84
The compatibility flagger was not catching the fact that the
INTRINSIC statement could reference a name that was not a Fortran-77
intrinsic function (it was catching VAX case, however). It now
makes the test.
The routine CFSRCLIB in module STA0 was returning the name of the
function/subroutine in the global scalar CFFSNAME, so that the
name could be used by WARNLEX to stick into the warning messages.
This method was employed in order to print the 'undotted' name
(e.g. DCOTAN) instead of the 'dotted' name (DCOTN.).
Unfortunately, WARNLEX does not necessarily emit the message
immediately (it could wait for end of statement), and the value
of CFFSNAME would get changed, causing the message to reference
an incorrect name.
CFFSNAME no longer lives. Instead, all WARNLEX calls reference a
name in the symbol table. This causes names of some functions
to be printed in their 'dotted' form. While this is not very clean,
it is preferable to being incorrect.
Modules:
ACT1 STA0
2304 TJK 8-Feb-84
Add P2SKOVRLP to do compile-time overlap checking for
character assignments. Have SKCALL call this routine if the
CALL statement is really a character assignment.
Modules:
P2S1 SKSTMN
2305 AlB 8-Feb-84
Added a slough of entries to the /NOWARN tables. All entries are
for the Compatibility Flagger warnings.
Module:
CMND20
2306 AlB 13-Feb-84
Added code to DMPSYMTAB to put out global definitions of FLGVX.
and FLG77. if Compatibility Flaggng is being done.
FLGVX. is defined as all ones if /FLAG:VAX is used.
FLG77. is defined as all ones if /FLAG:STANDARD is used.
Module:
LISTOU
2307 TJK 13-Feb-84
Have P2SKOVRLP manually set NOALLOC for new symbol table
entries CASNN. and CNCAN., since this isn't automatically done
after phase 1.
Module:
P2S1
2310 CDM 13-Feb-84
Output type 1131 rel block for PSECT redirection of segments
into psects. The command scanner sets the names for the psects
and the code generator dumps the rel block.
Modules:
CMND20 GLOBAL OUTMOD REQREL
2311 PLB 19-Feb-84 BIG BROTHER IS WATCHING YOU!
Modify symbol listings under /EXTEND.
This edit contains hacks re: OWGBPSECTION. All such lines
can be located by XSEARCHing for OWGBPSECTION.
Modules:
OUTMOD RELBUF LISTOU
2312 AlB 20-Feb-84
Fix the INCLUDE switches used by Fortran-10. This code was
originally entered with edit 2256, but was never tested in the
Tops-10 version.
Module:
STA2
2313 TJK 21-Feb-84
Rewrite CGRETURN. This routine had a number of problems
including inefficiency within the routine itself, incorrect
code produced for alternate returns using array references,
and pessimal code produced for some cases. Added a routine
header. Removed macro MOV1GEN. Commented out code pattern
MOVRET. Added entry point for code pattern OPGZER.
Modules:
CGDO OPGNTA
2314 AHM 25-Feb-84
Eliminate immediate arguments for OTSKFSIZ (format size)
FOROTS arguments because size of large arrays don't fit in 18
bits. Add field named ARACONSIZ to dimension table entries.
It points to a constant table entry. Make CMPFMT fill it in
from ARASIZ for Hollerith arrays, and make IOFORMAT use it.
Modules:
CGSTMN STREGA TABLES
2315 AHM 26-Feb-84
Temporarily disable peephole optimization under /EXTEND. Do
it by making OBUFF's call to PEEPOP conditional. It should be
enabled again as soon as PEEPOP is taught about instructions
that reference EFIWs.
Module:
CGEXPR
2316 AlB 27-Feb-84
CFCHECK no longer returns a value.
Changes made in STA1 in order to more nearly conform to programming
conventions.
Module:
STA1
2317 AHM 2-Mar-84
Create GENREF in CGEXPR to construct address fields for
operand references, including references to large numeric
variables. Get rid of MRFDATA, MRFARREF, MRFEXPR, MRFCSB and
OUTPTR, which were replaced by GENREF. Make CGOPGEN, IOPTR,
ARGGEN and IOFORMAT use GENREF instead of generating
references themselves. Make CGDIMBLOCK use ARGGEN and IOPTR
instead of generating references by hand. Delete commented
out code in CGIOARGS for (unimplemented) I/O repeat counts on
MTOP. calls. Eliminate immediate arguments for OTSKEDSIZ
(ENCODE/DECODE record size) FOROTS arguments because size of
large arrays don't fit in 18 bits.
Modules:
CGDO CGEXPR CGSTMN DEBUG STREGA
2320 RVM 9-Mar-84
First, change the name of the /FLAG switch to
/FLAG-NON-STANDARD and /NOFLAG to /NOFLAG-NON-STANDARD.
Second, allow the command standard required abbreviations of
/F for /FLAG... and /NOF for /NOFLAG.... Third, add a default
value of "ALL" for /FLAG....
Module:
CMND20
2321 AHM 12-Mar-84
Make ROUSYM recognize references to EFIW table entries. It
calls a new routine named ROUEFIW to process such references.
Module:
LISTOU
2322 CDM 27-Apr-84
Fix array subscript calculations for /EXTEND to use a full word
to calculate arithmetic. In PROCEQUIV and BLDDIM, check an
array reference against the correct maximum size of an array
declaration /EXTEND. In BLDDIM, call CNSTCM for array
calculations to give underflow/overflow messages for illegal
declarations. Otherwise arrays that are too large may not be
detected since their size will overflow.
Modules:
ACT1 CMND20 COMMAN ERROUT ERROVR
GLOBAL OUTMOD TABLES
2323 AHM 14-Mar-84
Create a new routine named Z30CODE which will output R30CODE
(type 1030) 30 bit relocation rel blocks under /EXTEND. It
calls ZCODE under /NOEXTEND. Make ZOUTBLOCK recognize that
type 1030 blocks need a loading address put in the first word
of a buffer, just like 1 and 1010 blocks. Make DMPMAINRLBF
recognize that all blocks greater than or equal to 1000 are
long count blocks. Define R30CODE rel block type for type
1030 30 bit relocation rel blocks. Also define RLNGCNTBLK to
designate the lowest REL block type which uses a long count
Module:
RELBUF REQREL
2324 AlB 15-Mar-84
Added flagger warnings which were causing undefined globals
with a Tops-10 build: E252, E256, E272, E289, E290.
Module:
ERROVR
2325 AHM 16-Mar-84
Create a new routine named DMPEFIW in PHA3 to dump the EFIW
table to the object file. It will output the EFIWs
themselves, additive fixups for their references to externals,
and local fixups to resolve references to the EFIWs from
instructions and arg blocks. Call DMPEFIW near the end of
MRP3, just before the call to ZENDALL.
Module:
PHA3
2326 AHM 18-Mar-84
Fix bug in edit 2317. TARGADDR fields of ARRAYREF nodes are
18 bit signed integers. GENREF needed to sign extend the
value extracted from TARGADDR fields of large ARRAYREF nodes
which MAKEFIW uses for the 30 bit EFY field of EFIWs.
Module:
CGEXPR
2327 RVM 23-Mar-84
Among other things, put CHARACTER variables into the proper
PSECTS. It turned out that setting the proper psects for
variables turned out to be much more complicated than was first
thought. The distributed nature of FORTRAN's declaration syntax
require the compiler to set the psects for a variable four times
in some cases. Thus a general purpose routine named SETPSECTS
was created that will set the psect fields properly for any type
of variable passed to it. (Although all parts of the compiler
could use SETPSECTS, not all do for the sensible reason that
local knowledge about a variable make the extensive case analysis
of SETPSECTS unnecessary in that case.)
Make sure all formals are put in the .DATA. psect.
Modules:
ACT1 LEXICA STA3
2330 AHM 28-Mar-84
Use Z30CODE to emit OWGBPs in user code so that section
numbers are supplied by LINK. Generate 30 bit additive fixups
for OWGBPs that reference COMMON. For now, continue to use
OWLBPs for static data initialization, since type 1004 REL
blocks can't handle OWGBPs. Remove all references to the
global OWGBPSECTION, since it is no longer used. Use EFIWs
for CHARACTER FUNCTION descriptors under /EXTEND to make
multiple sections of code work. Define new field macros for
the P&S and address fields of OWGBPs.
Modules:
CMND20 GLOBAL OUTMOD RELBUF TABLES
2331 RVM 28-Mar-84
Fix a bug in the way that colons at the end of the /EXTEND keywords
were handled. Under the old code, a ? immediately after the colon
in the /EXTEND switch keyword, would produce the wrong help text.
This occured because the CHKCOLON routine would look for something
in the follow set of the switch keyword when it had no colon, and
if that failed, look for a colon. The solution was simple: look
for a colon AND the follow set at the same time.
Module:
CMND20
2332 TJK 30-Mar-84
Fix some bugs in MAKELIST where parent pointers aren't being
set up properly.
Module:
IOPT
2333 TJK 30-Mar-84
Fix some bugs in SETPVAL and SETPIMMED. Specifically, check
for a zero parent pointer, check for IOLSCLS nodes, don't
assume that ARG2 matches if ARG1 doesn't, and in SETPIMMED
change a compare of an OPERSP with FNCALL to a compare of an
OPRCLS with FNCALL.
Module:
UTIL
2334 AHM 4-Apr-84
Move the object program's entry vector to the .DATA. psect.
Define a symbol named ENTVECSIZE in TABLES for the vector's
size. Allocate 2 words for now. This will allow FOROTS to
modify the reenter instruction upon startup. An entry vector
is only generated under /EXTEND.
Modules:
GLOBAL LISTOU P3R PH3G PHA3 TABLES
2335 TJK 6-Apr-84
Change some AND's to THEN-IF's in STCMASMNT to prevent an
illegal memory reference.
Module:
STREGA
2336 CDM 6-Apr-84
Fix case not caught for edit 1766 for putting too large a
constant into an ARRAYREF's TARGADDR.
Modules:
CMPLEX TABLES
2337 CDM 8-Apr-84
Output EFIW references /LISTING/MACRO.
Modules:
FIRST LISTOU
2340 AlB 13-Apr-84
Removed those flagger checks which worried about Fortran-10/20
instrinsic subprograms which are not intrinsic on the VAX. These
flagger tests are done at run-time, but iff the Fortran-supplied
subprograms are actually used (i.e. not supplied by the user).
Modules:
ACT1 STA0
2341 AlB 17-Apr-84
Added the NML keyword for I/O statements. NML is equivalent to
FMT, but must have a namelist as its value. NML is used by VAX
for namelist references, so this was added for compatibility.
Added NMLSCAN and NMLIOREF to ACT0. NMLSCAN parses the NML= keyword,
NMLIOREF parses a namelist for both FMTSCAN and NMLSCAN.
Modules:
ACT0 ERROUT
2342 AHM 17-Apr-84
Make DATA statements work for some variables in .LARG. Make
OUTDATA in OUTMOD and OUTCHDATA in RELBUF use the psect
indices in the variables they are passed instead of always
using .DATA. This should allow variables in the first section
of .LARG. to be statically initialized by DATA statements.
Also, move EXTERNPSECT plit from RELBUF to GLOBAL so that both
OUTMOD and RELBUF can reference it without LNKFTH warnings.
Modules:
GLOBAL OUTMOD RELBUF
2343 RVM 18-Apr-84
Implement the COMMON and NOCOMMON keywords of /EXTEND.
In CMND20, scan the switch, note the psect that each COMMON block
is put into, and set the default psect for all COMMON blocks.
In GLOBAL, define the table to hold ECTAB, the table of COMMON
blocks named in an /EXTEND switch. Also define the related
tables and status words.
In SRCA, create FNDCOMMON, the routine used to manipulate the table
of COMMON blocks seen during /EXTEND. Also, put COMMON blocks into
the proper psects as they are created.
In STA2, have COMMSTA put the variables in the COMMON block into
the proper psect.
In ACT1, have SETPSECTS know about variables in COMMON.
In FIRST, define the field names of entries in the table of COMMON
blocks named in /EXTEND.
Modules:
ACT1 CMND20 FIRST GLOBAL SRCA STA2
2344 PLB 19-Apr-84
Fixed ZOUTBP in OUTMOD to type 0(?) when input BP EQL 0.
Module:
OUTMOD
2345 AHM 20-Apr-84
Make HSCHD in OUTMOD use additive fixups to generate the
indirect words for external CHARACTER function descriptors.
This makes the code agree with the comments and design spec,
and avoids a LINK bug with deferred 30 bit chained fixups.
Module:
OUTMOD
2346 AHM 23-Apr-84
Create new globals SCOMSZ and LCOMSZ in GLOBAL. Make ALLCOM
in OUTMOD keep separate totals of the sizes of small and large
COMMON blocks in these variables. Make MRP3 in PHA3 use them
when computing the sizes of the psects in the test for the
"?FTNPTL Program too large" diagnostic. Get rid of COMTSIZ
from GLOBAL, LISTOU and PHA3, since no one uses it anymore.
Modules:
GLOBAL LISTOU OUTMOD PHA3
2347 RVM 27-Apr-84
Make /EXTEND mean /EXTEND:COMMON rather than /EXTEND:NOCOMMON.
Also, fix two bugs. First, /NOEXTEND was not setting the default
psect for COMMON blocks back to PSDATA. Second, /EXTEND:COMMON
had the side effect of changing the /EXTEND:DATA size to its
default value!
Module:
CMND20
2350 RVM 28-Apr-84
Make the code and psect keywords to /EXTEND invisible for now,
as they are not yet supported.
Module:
CMND20
2351 AHM 30-Apr-84
Fix another bug in edit 2317. GENREF was not adding the
contents of PBOPWD[OBJADDR] to the target fields of DATAOPRs
ARRAYREFs and random targets when computing an EFIW's Y field.
This made references to the second word of DP variables fail.
Also, clear PBOPWD[OBJADDR] when referencing EFIWs, since this
will make PEEPOP recognize more identical references.
Module:
CGEXPR
2352 CDM 1-May-84
Make intrinsic functions IAND, IOR, and IEOR inline functions. They
are converted to Fortran .AND., .OR., AND .XOR. within the skeleton
optimizer.
Modules:
FIRST GLOBAL P2S1 TABLES
2353 AlB 1-May-84
Add the /FLAG and /NOFLAG switches to the Tops-10 command scanner.
/FLAG has the keywords ALL, ANSI, VAX, NONE, NOANSI, NOVAX.
/NOFLAG has no keywords.
Re-arranged the location of NOWCLR in order to improve the
readability of the source.
Module:
COMMAN
2354 RVM 2-May-84
Make the peephole optimizer work with EFIW table entries.
Delete the AEQLC0 routine because it was not used. Delete OWN
T2, because T2 was not used.
Modules:
CGEXPR PEEPOP
2355 AHM 2-May-84
Put JRST @[REENT.##] in the second word of the entry vector
generated under /EXTEND so that FOROTS, FORDDT or users can
set the reenter address at link time. Also, make the entry
vector 3 words long to allow room for a version number.
Modules:
P3R PH3G PHA3 TABLES
2356 AHM 8-May-84
Use COMPSECT to place COMMON blocks in the correct psect when
outputting type 21 (RCOMMON) REL blocks. Also, change the
default psect origin for .DATA. to 1000140 and .CODE. to
1300000. This way, the impure data areas have the lowest
addresses in both section 0 and non-zero sections.
Modules:
GLOBAL OUTMOD SRCA
2357 AHM 14-May-84
Keep LINK from getting ?LNKIPX Invalid psect index when
loading programs with COMMON blocks compiled /NOEXTEND.
During COMMON block allocation (ALLCOM) only output type 22
(RPSECTORG) REL blocks under /EXTEND.
Module:
OUTMOD
2360 CDM 17-May-84
Fix for edit 2336. CMPLXA was making an add node to add the array's
IDADDR field and the array's address calculation together even if the
pointer to the address calculation is 0 (meaning there isn't any).
This edit simply substitutes the constant IADDR if no calculation
previously exists.
Module:
CMPLEX
2361 AHM 17-May-84
Fix for edit 2360. Prevents generation of immediate mode
instructions for large constants. A local alias for the
ARRAYREF's ARG2PTR field (ADDRNODE) was not kept up to date
even though later code uses it. Update ADDRNODE with
ARG2PTR's new value.
Module:
CMPLEX
2362 CDM 23-May-84
Hopefully the final fix for edits 1766/2012/2336/2360/2361.
Flags from deleted nodes (expressions and constants) were not
being propagated properly. These include A*VALFLG, A*IMMEDFLG,
A*NEGFLG, A*NOTFLG.
Module:
CMPLEX
2363 TJK 6-Jun-84
Add code to do register allocation for arbitrary expressions
in E1 lists and E2 lists (ALCE1LIST and ALCE2LIST). Also move
some calls to VARCLOBB in ALCIOCALL so that the variables are
marked as clobbered after register allocation instead of
before.
Module:
STREGA
2364 TJK 6-Jun-84
Add a call to ENDSMZTRIP in ALCIOLST. If it returns TRUE,
mark all registers as being clobbered since we're at the end
of a MAYBEZTRIP DO-loop. Make ENDSMZTRIP global for use by
ALCIOLST.
Modules:
REGUTL STREGA
2365 TJK 6-Jun-84
Move checks for inner DO-variable in SKIO and SKOPNCLS until
after SKWALK, in case folding occurs.
Module:
SKSTMN
2366 TJK 10-Jun-84
Fix DOMINATE and PDOMINATE to correctly calculate immediate
pre- and post-dominators. P1 wasn't being reset to HEAD for
each successor of HEAD, with the result that the "immediate"
dominator of each successor of HEAD dominated (or was equal
to) each of the "immediate" dominators of the preceding
successors of HEAD. The pre- and post-dominator trees still
worked, but were more pessimal than the correct ones.
Module:
GRAPH
2367 RVM 14-Jun-84
Add the label "GFLPAT" in case we want to find the instruction to
No-op in order to turn on TOPS-10 gfloating support.
Module:
COMMAN
2370 MEM 14-Jun-84
Modify LEXICA and STA1 so that long specifiers can be used for
open/close/inquire statements. The five tables OPNKWD, IOCKVAL,
INQUVAL, IOCKCODE and KEYWFLAG were combined so that it would
be use easier to add more specifiers in the future.
Modules:
ACT0 ERROUT GLOBAL LEXICA STA1
2371 TJK 14-Jun-84
Move defintions of DEFPT1 and DEFPT2 from OPTMAC to TABLES.
Also add definition of DEFPTSS, used to hold definition points
for substrings. These are all in TABLES to avoid hiding
overlapping fields.
Modules:
OPTMAC TABLES
2372 TJK 14-Jun-84
Restructure DEFPT to allow the SETSEL routines to handle
SUBSTRING and ARRAYREF nodes (as well as DATAOPRs). Use
DEFPTSS for the definition point of ARG4PTR in a SUBSTRING.
Handle character data. Fix many, many bugs, mostly involving
missing checks for function references with side effects. Fix
problems with edit 1034. Add support of character data to
first part of IOPT (i.e., the routines called before IOCLEAR).
Modules:
DEFPT IOPT VER5
2373 TJK 14-Jun-84
Make FNARRAY and NEXTUP more paranoid about character expressions.
Modules:
COMSUB GCMNSB
2374 TJK 15-Jun-84
Allow PNROPT to handle character data. Also fix several bugs.
Module:
PNROPT
2375 TJK 15-Jun-84
Allow the global register allocator to handle character data.
Never globally allocate a character variable to a register.
Module:
PH3G
2376 TJK 18-Jun-84
Rewrite MARKIOLSCLS to handle E1 and E2 lists. Also
restructure, add companion routine MARKSUP, and have it set
IOLDYNFLG on all IOLSCLS nodes with a dynamic CONCATENATION
directly beneath them or directly beneath some lower-level
IOLSCLS node. Formerly only the top-level IOLSCLS node was
being marked.
Module:
REGAL2
2377 TJK 16-Jun-84
Correct the case for a DO statement in LOKINDVAR added in edit
1057. It shouldn't look at DOM2, since this isn't used after
DOLPCTL is created. Also add some explicit zero returns in
TESTREPLACE.
Module:
TSTR
2400 TJK 18-Jun-84
Add FOROTS argument types OTSNSLIST, OTSNELIST, OTSNSLIST77,
and OTSNELIST77. Have CAE1LIST and CAE2LIST use the new
argument types. Add support of character data to second part
of IOPT (i.e., the IOCLEAR routines which create E1LISTCALL,
E2LISTCALL, and IOLSTCALL nodes). Fix some bugs. Change
interpretation of the increment fields of E1 and E2 lists.
They now indicate the word or byte displacement to use,
instead of the array element displacement. Also, EDBLELEM
nodes are no longer used, since there is no longer any need to
differentiate between single and double elements (not to
mention character). Also, remove a lot of the distasteful
code associated with EDBLELEM nodes.
Modules:
CGSTMN IOPT TABLES
2401 TJK 19-Jun-84
Prevent P2SKSUBSTR from creating .Dnnnn constant substring
descriptors. This causes problems elsewhere, and would be
even worse with the optimizer turned on. Remove a .Dnnnn
check from P2SKOVRLP. Add DOTDCHECK, which is called during
the complexity walt to check for substrings which can be
converted into .Dnnnn compile time constant descriptors. It
also performs the bounds checking which was formerly done in
P2SKSUBSTR. Make several improvements to the bounds checking.
Add calls to DOTDCHECK in CMPFNARGS, CMPILF, CMPLIOLST,
CMPIOCALL, CMPE1LIST, CMPE2LIST, CMPUNIT, CMPFMT, CMPFILE, and
STCMOPEN.
Modules:
CMPLEX P2S1 STREGA
2402 TJK 19-Jun-84
Add FIXAOBJN, a routine which prevents values from being taken
directly from AOBJN registers. Call this routine from
CMPE1LIST and CMPE2LIST. Note that this only catches a few of
the many known cases. Furthermore, it would really be better
if we could eliminate the AOBJN control word completely in
these cases, instead of inserting STRHAOBJN nodes. Add
STORECLS case to ALCINTMP for STRHAOBJN nodes.
Module:
CMPLEX REGAL2
2403 TJK 20-Jun-84
Turn the optimizer on when character data is present.
Module:
MAIN
2404 TJK 21-Jun-84
Add missing cases to CONTVAR and CONTFN for CONCATENATION.
Improve a few things. Change meaning of CONTVAR slightly,
making it more powerful and correcting bugs in its callers.
Add UNSAFE, a routine which tests for potential storage
overlap. Add call to UNSAFE from CONTVAR. Add call to UNSAFE
from P2SKOVRLP, replacing an equivalent in-line test. Also
change CONTFN to only return TRUE for user functions.
Modules:
P2S1 UTIL
2405 TJK 21-Jun-84
Correct a problem with edit 1441. It missed the place in
FOLDIOLST where CONTFN must be called. Delete DEFONCIOL,
whose references may be replaced by direct calls to IODEPNDS.
Improve FILTER (in LOOKELEM2).
Module:
SKSTMN
2406 TJK 21-Jun-84
Fix problems in GLEXDFPT. Specifically, have it worry about
common/equivalence and functions with potential side effects.
Module:
IOPT
2407 TJK 21-Jun-84
Have VARCLOBB check for SUBSTRING nodes.
Module:
ALCBLO
2410 TJK 22-Jun-84
Fix a few more bugs. Make ISOLATE handle substrings better,
so we can make E1 and E2 lists of substrings from an array.
Module:
IOPT
2411 CDM 30-Jun-84
Fix CMPLXA so that array address calculations with neg/not flags
involved won't take out constants below the flags to add into
the array's TARGADDR. Also rename local symbol NAME to ARRNAME
to avoid any confusion with global NAME.
Module:
CMPLEX
2412 TFV 1-Jul-84
Split LEXICA into two modules. The classifier is in the new
module LEXCLA. The lexeme scanner is in LEXICA. LEXCLA is
called to initialize each program unit, to classify each
statement, to classify the consequent statement of a logical IF,
and to do the standard end of program and missing end of program
actions.
Modules:
DRIVER GLOBAL LEXCLA LEXICA LEXSUP STA2 STA3
2413 MEM 5-Jul-84
Add the keyword TAPEFORMAT to OPENCLOSE.
Module:
STA1
2414 AlB 5-Jul-84
When an array is referenced in an EQUIVALENCE statement, the
subscripts are now checked for 'out of bounds'. The check used
to be done (badly) for the case of single subscripts with
multi-dimensioned arrays; it was never done for multiple subscripts.
The 'out of bounds' message is a warning only; old sources will
still work, albeit with a warning.
Module:
OUTMOD
2415 RVM 7-Jul-84
First, provide some additional help when the user types "?" at
the COMND% JSYS. Second, create an new entry into the error
message maker that allows us to provide some error text rather
than use the ERSTR% JSYS. This improves the reporting of various
semantic errors. Third, echo the command line in error if it is
coming from a indirect command file, regardless of the state of the
echo flag. Fourth, correct a long standing bug that caused the
command scanner not to complain if a TOPS-10 style command didn't
contain any source files.
Module:
CMND20
2416 RVM 8-Jul-84
Make the /EXTEND:COMMON:name(s) switch imply that the default
psect for unnamed COMMON blocks is PSDATA. Likewise, make the
/EXTEND:NOCOMMON:name(s) switch imply that the default psect
for unnamed COMMON blocks is PSLARGE.
Module:
CMND20
2417 RVM 9-Jul-84
Improve upon the rotten error message given when the first thing
in the command line was either a bad keyword or a non-existing
file. The solution was to scan for the old-style action switches
at the same time as all the new stuff, to examine the error that
occured, and to substitute a better error message for the monitor's
bad one using the new SEMERR routine.
Module:
CMND20
2420 TFV 9-Jul-84
Compact the split LEXICA, LEXCLA modules. Remove the dead
states and macros from each. Redo the PLITS of smalstates and
bigstates. Change the lexical tracing routines for debugging so
they typeout the correct names. Also fix flagger warnings so
that each gets printed once instead of twice. Finally, fix the
line numbers for the warnings, they were wrong and could ICE the
compiler.
Modules:
INOUT LEXCLA LEXICA LEXSUP
2421 RVM 10-Jul-84
Impove the error messages for a command that looks like it starts
out at a keyword command by then goes awry.
Module:
CMND20
2422 RVM 12-Jul-84
Set BIGCONCAT in the -10 command scanner. See edit 2251.
Module:
COMMAN
2423 AHM 13-Jul-84
Add support for 1160 Ultimate Sparse Data REL blocks under
/EXTEND. Move OUTDATA and OUTCHDATA into DATAST and make them
maintain a buffer of the most recent constant to take
advantage of the 1160's repeat count feature. Add FLUSHDATA
to DATAST to output the buffer's contents. Define new symbols
in REQREL for 1160 blocks, and in TABLES for byte pointers.
Modules:
DATAST OUTMOD RELBUF REQREL TABLES
2424 MEM 13-Jul-84
Check for IOSTAT in read/write statements instead of just looking
at the first five characters and ignoring the rest. Correct three
error messages broken in OPENCLOSE. Add DIALOGUE to the table of
open/close/inquire keywords.
Modules:
ACT0 ERROUT STA1
2425 AHM 15-Jul-84
Correct a typo in edit 2404 that TJK told us about during EAS
and RBP's wedding reception. The CONCATENATION arm of
CONTVAR's case referred to VAR[ARG2PTR] instead of
CNODE[ARG2PTR] when fetching the arglist.
Module:
UTIL
2426 MEM 16-Jul-84
Don't let an open/close/inquire statement contain the same
specifier multiple times with different spellings. Fix
broken DIALOG=.
Modules:
STA1 TABLES
2427 AlB 17-Jul-84
Redefine the STE fields MERIT, ORFIXFLG, OMOVDCNS, LIBARGUSE and
USRARGUSE such that they are in word 8 instead of word 2.
Remove STE fields IDCHOS and IDUSED, which were being set up but
never used.
The intent of the move is to get those fields out of the left
half of IDADDR; FORTD clears those fields and thus was
destroying the global address.
REGSTUFF was defined in two different ways (by CLEANUP and by
DFCLEANUP). The definitions were taken out of those routines
and placed in FIRST as IDCLEANA and IDCLEANB.
Modules:
DEFPT FIRST GOPT2 VER5
2430 CDM 18-Jul-84
Have the compiler complain /FLAG for a variable mentioned more
than once in SAVE statements (SAVE A,B,A - A is mentioned
twice).
Modules:
CMND20 COMMAN ERROUT STA2
2431 TFV 18-Jul-84 Q-712000
Fix processing of line sequence numbers for second and later
program units. When a statement consisting of END is scanned,
it is the end statement for the program unit. The beginning of
the next line must be scanned for a LSN before returning from
LEXCLA.
Modules:
LEXCLA LEXSUP
2432 AHM 23-Jul-84
Create an alias named RULTFLAGS for the concatenation of the
1160 flag bits RULTRPTFLAG, RULTFILLFLAG and RULTBYTEFLAG, and
clear it near the top of FLUSHDATA. Cures bad REL files
caused by assuming that the garbage left on the top of the
stack was zero.
Modules:
DATAST REQREL
2433 CDM 23-Jul-84
Use VMSIZE for the size of virtual memory in the decision
whether to declare the "Program too large". Should have been
done in edit 2322.
Also delete use of ARGCHK, used for disabling argument checking
in V7 field test. No reason to continue this!
Module:
PHA3
2434 CDM 23-Jul-84
Enhance argument checking to differentiate between character
expressions /EXTEND and /NOEXTEND. We do not want to pass a one
word LOCAL byte pointer where a GLOBAL is wanted. This
condition could reference data in the wrong section.
Modules:
RELBUF REQREL
2435 AHM 24-Jul-84
Invalidate DATNEXT at the start of each program unit's DATA
statement processing by setting it to -1. This insures that
OUTDATA and OUTCHDATA will not append DATA statements in
different program units to the same 1160 block.
Module:
DATAST
2436 MEM 31-JUL-84
Fix error message for read/write statements which was printing
garbage.
Module:
ACT0
2437 PLB 31-July-84
Fix spelling of external FFBUFSAV in DRIVER.
(It was spelled FFBUFSV, and caused bad XSEARCHes)
Module:
DRIVER
2440 RVM 1-Aug-84
Change the origin of the PSDATA psect from 1000140 to 1001000.
FORDDT and FOROTS have reserved the first page of every section
which contains code.
Module:
OUTMOD
2441 RVM 4-Aug-84
Change the way the TOPS-20 command scanner resolves command
line switches and SWITCH.INI switches. This will require less
work in the future to add new flag words.
Module:
CMND20
2442 RVM 4-Aug-84
Make /EXTEND:CODE turn on its bit.
Modules:
COMMAN CMND20 IOFLG
2443 RVM 5-Aug-84
Define the symbolic name MAXSYM for the number of characters
that LINK will allow in a PSECT name. Define SYMLEN as the
number of words needed to hold MAXSYM SIXBIT characters. Make
HINAME and LONAME SYMLEN+1 words long. Word 0 is number of
words used; the other SYMLEN words are the SIXBIT psect name.
This prepares the way for /EXTEND:PSECT.
Module:
FIRST GLOBAL
2444 AlB 6-Aug-84
Generate code which recognizes /EXTEND:CODE.
If the EXTENDCODE bit is set in F2:
o In GENREF, set LARGE to be true if a DATAOPR is an external
subprogram. This will cause EFIW entries to be created for
function and subroutine references.
o In CGOPGEN, add code 'implicit function name' and 'implicit
function name list' cases that will create Symbol Table and
EFIW Table entries for the functions.
o Make INIFDDT generate an EFIW entry for FDDT.
Modules:
CGEXPR DEBUG
2445 RVM 8-Aug-84
Make /EXTEND:PSECT fill in LONAME and HINAME.
Module:
CMND20
2446 MEM 9-Aug-84
Make RELINIT produce type 1050 rel blocks instead of type 24 rel blocks
Module:
GLOBAL OUTMOD RELBUF REQREL
2447 PLB 10-Aug-84
Support nested INCLUDE files. Include files may now be nested
up to 12 levels deep. Added support for SFDs too!
Modules:
CMND20 ERROUT GLOBAL IOFLG LISTNG STA2 UNEND
2450 AlB 14-Aug-84
Fix GENREF to recognize the fact that an external function is of
type CHARACTER, and thus does not want an EFIW, since it should
reference the local character header.
Module:
CGEXPR
2451 AHM 16-Aug-84 Q20-06078
Remove check from STCMSFN and STCMSUB which prevented them
from setting ENTNOCOPYFLG on NOALLOC FORMLARRAY's. This
caused DMOVE/DMOVEM's to be generated for CHARACTER formals
which would smash variables allocated to 1' (since unallocated
two word descriptors have an address of 0'). Also, modify
ADJCALL to only call ADJGEN for arrays that are allocated.
This prevents ADJxy.'s arg lists from referencing 0' and 1'.
ADJx. would Ill Mem Ref when it interpreted byte pointers left
in 0' by the routine prologue as an address.
Modules:
DOALC DOXPN
2452 AHM 20-Aug-84
Make OUTCHDATA return immediately when handed a NIL pointer
for a CHARACTER constant, as GETCHCNST intends it to. This
prevents it from generating bad REL blocks based on the
contents of the compiler's ACs.
Module:
DATAST
2453 AHM 22-Aug-84
Narrow RULTSYMLEN from 9 to 8 bits, to reflect LINK's design.
The spare bit is reserved to DEC, must be zero. Rename
RULTFLAGS to be the whole 1160 flag word and zero it near the
start of FLUSHDATA. Also, change lengthy disjunctions in
OUTDATA and OUTCHDATA into IF/THEN/ELSE's for speed. Finally,
insert a missing dot and reverse the sense of a test in
OUTDATA at the same time.
Modules:
DATAST REQREL
2454 RVM 28-Aug-84
Move the definition of DEFLON (the default value for LONAME)
and DEFHIN (the default value for HINAME) from CMND20 into
GLOBAL. Then make OUTMOD use DEFLON and DEFHIN where needed
in the twoseg redirection rel block. For kicks, make the -10
command scanner set up LONAME and HINAME.
Modules:
CMND20 COMMAN GLOBAL OUTMOD
2455 MEM 30-Aug-84
Replace all references in the compiler to VAX with VMS.
Modules:
ACT0 ACT1 CMND20 COMMAN ERROUT ERROVR FORMAT
INOUT IOFLG LEXCLA LEXICA LISTOU OUTMOD STA0
STA1 STA2 TABLES
2456 AHM 30-Aug-84
Clear all saved INCLUDE file buffer pointers between program
units. Otherwise, the remembered buffer addresses tend to
point into the active heap after it is recycled. This will
hopefully keep nested INCLUDE statements working on Tops-20
until PB comes back from vacation.
Module:
DRIVER
2457 AHM 20-Sep-84
Changes to Ultimate Sparse Data Support for code review.
Comment changes, except for changing access to DCON1 and DCON2
in OUTDATA from formals to globals.
Modules:
DATAST TABLES
2460 AlB 26-Sep-84
Treat REAL*16 as if it were REAL*8 instead of REAL*4.
Module:
STA2
2461 CDM 28-Sept-84
Add octal and hexadecimal constants for the Military Standard
MIL-STD-1753 to DATA statements.
Modules:
ACT0 BUILD ERROUT F72BNF STA1
2462 AHM 2-Oct-84
Use execrable TRUE/FALSE/TRUTH/FALSITY miasma for booleans in
GENREF and its callers to satisfy programming conventions.
Modules:
CGDO CGEXPR CGSTMN
2463 AHM 8-Oct-84
Make ARRAYREFs take advantage of 30 bit addressing in EFIWs.
Define two OPERSPs for ARRAYREF. Create all ARRAYREFs as
ARREFSMALLs in ARRXPND and PROARRXPN. Don't assume ARRAYREFs
for large arrays with small TARGADDRs won't use EFIWs in
ARNOAOBJN. Consult OPERSPs when trying to find identical
ARRAYREFs in ARREQLLH. Mutate ARREFSMALLs into ARREFBIGs in
AROFCONST and CMPLXARRAY when references to large numeric
arrays have too big a TARGADDR. Notice the difference between
ARREFSMALLs and ARREFBIGs when generating operand reference
fields in GENREF.
Modules:
ARRXPN CGEXPR CMPLEX SKSTMN STREGA TABLES
2464 AHM 9-Oct-84
Go the full distance on edit 2463 by optmizing small and
formal numeric ARRAYREFs. Instead of having EFEXTERN 0 when
not doing a SIXBIT fixup, set it to the internal psect index
that EFY is to be relocated by. The left half of EFEXTERN
will be zero in those cases, so define EFFIXEDUP to test for
it. Create ARREFBIG nodes in AROFCONST regardless of the
psect of the array. Use the stored psect index instead of
assuming PSLARGE when relocating an EFIW in DMPEFIW. When
listing an EFIW in LSTEFIW don't output the variable name or
use IDADDR in the offset computation for an EFIW with PSABS in
EFEXTERN - it is an unrelocated formal array reference.
Modules:
CGEXPR CMPLEX FIRST LISTOU PHA3 SRCA
2465 RVM 11-Oct-84
BLISS and CMND20 disagree about which registers are saved across
routine calls. Thus, CMND20 should save and restore all the
preserved registers when calling a BLISS routine.
Module:
CMND20
2466 AHM 12-Oct-84
Yet another patch to subscript optimization in CMPLXARRAY. If
both operands of a topmost plus node are optimized into
TARGADDR, return after SAVSPACEing the plus node. Also,
explicitly set A2VALFLG for the ARRAYREF in CMPLXARRAY in this
situation. These keep SETCOMPLEXITY and CGETVAL
(respectively) from infinitely recursing on a NIL ARG2PTR.
Module:
CMPLEX
2467 RVM 17-Oct-84
Add the OPEN/CLOSE keyword DISP= (a VAX synonym for DISPOSE=).
Module:
STA1
2470 RVM 19-Oct-84
BIGARY was getting the wrong value if /EXTEND was never seen. This
also had the effect that BIGARY was wrong if /EXTEND:anything-but-data
was given.
Module:
CMND20
2471 RVM 25-Oct-84
Remove the instruction at GFLPAT. FORTRAN-10 will now support
gfloating!
Module:
COMMAN
2472 PLB 26-Oct-84
Add code to support **, * and / in PARAMETER. Until now they
caused a CGERR!!
Modules:
CNSTCM SRCA
2473 CDM 29-Oct-84
Add IMPLICIT NONE for the Military Standard MIL-STD-1753.
Modules:
ACT0 ACT1 CMND20 COMMAN ERROUT F72BNF
GLOBAL INOUT STA0
2474 TFV 21-Sep-84, AlB 30-Oct-84
Fix continuation processing to handle unlimited numbers of blank
and comment lines between continuation lines. The lines are
recorded in a linked list of four word entries, defined in
LEXAID.BLI. If there are too many blank and comment lines, the
buffer will get an overflow. When this happens, the buffer is
compacted using the information in the linked list. The info is
also used to speed up continuation processing in the lexeme
scan.
Modules:
DRIVER GLOBAL INOUT LEXAID LEXCLA LEXICA
LEXSUP LISTNG PH2S PHA2
2475 MEM 5-Nov-84
Fix bugs with combinations of neg and not with double octal constants.
Modules:
LEXICA TABLES
2476 MEM 7-Nov-84
Fix index number into THEKEYS for DIALOGUE and READONLY so
compatability message has full specifier in it instead of the
abbreviated 6 character specifier.
Module:
STA1
2477 AlB 16-Nov-84
Change the source POOLSIZE to be 2000 words (10000 characters). This
was done to decrease compilation times.
Change references to flagger message prefixes to use the globals
ANSIPLIT, VMSPLIT and BOTHPLIT.
Modules:
FIRST GLOBAL LEXAID LEXCLA LEXICA STA1
2500 AlB 16-Nov-84
Change the list of entries for source lines from a linked list
in dynamic memory to a fixed-length list in static memory.
Modules:
DRIVER GLOBAL LEXAID LEXCLA LEXICA LISTNG
PH2S PHA2
2501 AlB 20-Nov-84
Special handling of errors found in comment lines. Since these
errors can be detected while scanning unprinted comment lines, they
cannot go through the normal error queueing process.
Instead, a notation is made in the source list entry for the line,
and PRINT will check to see if an error was noted and if so, will
put out the message.
Modules:
INOUT LEXAID LEXCLA LEXICA LISTNG
2502 CDM 20-Nov-84
Correct argument checking in the coercion block to have LINK
complain about calling a function as if it were a subroutine.
Module:
RELBUF
2503 MEM 27-Nov-84
Corrected entry in FMTWIDTH for D, E, F, and G formats.
Corrected indexes for associatevariable, carriagecontrol,
and dispose in THEKEYS.
Modules:
FORMAT STA1
2504 CDM 27-Nov-84
Make 127 dimensions of arrays work, as advertised in the fortran
Manual. Rework parts of BLDDIM to bring it up to date.
Module:
ACT1
2505 AlB 28-Nov-84
Fix some printing problems: Blank lines that were surrounded by
comment lines were not being printed, and BACKLINE was printing
extra stuff.
The rewritten SAVLINE routine in LEXSUP became so trivial that it
was removed, and calls to it were replaced by in-line code.
The BACKPRINT routine was rewritten and moved to LISTNG from
LEXSUP.
Modules:
LEXCLA LEXICA LEXSUP LISTNG
2506 AlB 30-Nov-84
Multiple statement lines were causing any following comments not
to be listed, and would under certain conditions complain if the
following line was a continuation.
Under certain conditions, comment lines were not printed because
LASTCODELINE had moved too far down the linked list. Now when
a continuation line is detected, we back up to the first unprinted
line before printing out comments.
When the classifier found the 'no continue' condition, it was not
backing up LINLCURR when it backed up the pointers.
Modules:
LEXCLA LEXICA LEXSUP
2507 CDM 20-Dec-84
Add enhancement for IMPLICIT NONE (edit 2473) after code inpsection.
Check more cases, and add a symbol table walk at the back end to
catch unreferenced variables.
Modules:
ACT0 ACT1 FIRST GLOBAL OUTMOD
STA0 STA2 STA3
Move macros IDDOTx to FIRST.
Modules:
GCMNSB COMSUB GOPT2 PH3G VER5
2510 CDM 4-Jan-85
Enhancements to edit 2461 for octal and hexadecimal constants in
DATA statements. Better error messages and significant leading
zeroes to match the already existing octal constants.
Module:
ACT0
2511 MEM 7-Jan-85
Fix error message which is expecting a sixbit argument but is getting
an ascii argument.
Module:
ERROUT STA1
2512 CDM 7-Jan-85
Update copyright notice.
Module:
MAIN
2513 AlB 7-Jan-84
The FORMAT statement requires that the format be allocated
by CORMAN to contiguous chunks of core. Unfortunately, the
portability flagger was putting out warnings, which caused
FATLERR to use CORMAN to save the error, which caused a later ICE.
The solution implemented here is to create the table FLAGERR
into which notations of warnings are placed during the syntactic
scan, and from which warnings are issued after the FORMAT is
entirely scanned.
Module:
FORMAT
2514 AlB 24-Jan-85
Patches for QARs 853012 and 853013
Source lines with spaces (not tab) in the label field were being
treated as code lines, even if they had no code. This tended to
confuse the comment/continuation code.
Continuation lines in source statements which do not start with tab
were causing preceding comments not to be printed. Created new
routine CONTPRINT in LEXICA in order to print those comments.
This routine is now called from ACMGOBAKNXT and ACMCONTDIG in both
LEXICA and LEXCLA.
An exclamation mark may now appear anywhere in the source line,
including the label and continuation fields. It will causes the
remainder of the line to be treated as a comment.
Modules:
LEXCLA LEXICA
2515 AlB 29-Jan-85
Answer to QAR 853023: Prevent the FORMAT statement from flagging
the absence of commas after a slash. ANSI says that you don't need
commas 'before or after a slash edit descriptor'.
Modules:
FORMAT
2516 AlB 31-Jan-85
Complete solution to the inclusion/exclusion of commas in FORMAT
statements. Well, almost complete: it doesn't complain if it
sees (2PI3) instead of (2P,I3); the solution to that seemed like
forcing the issue (and was a kludge). Note that ANSI is perfectly
happy with (kPFm.n) but doesn't like (kPIm). Tough.
Modules:
FORMAT
2517 CDM 1-Feb-85
Enhancements to argument checking, upgrading for statement
functions to be up with external routines, and a few bug fixes in
statement functions. Added checks for structure in arguments;
singleton (scalar), array, routine. Added character length
checking in statement functions.
Modules:
ERROUT EXPRES RELBUF REQREL
2520 CDM 12-Feb-85 QAR 853033
Add to edit 2504. Use correct pointer into array dimension
table, not into the dimesions themselves.
Module:
ACT1
2521 CDM 8-Mar-85
Correct call to SAVSPAC for returning hash table entries. Size was
"magic number", rather than the symbol, the size of which has
grown. One word too few was being returned for every hash table.
Module:
PHA2
2522 DCE 8-Mar-85 QAR 853010
Correct definition point algorithm for character assignment
statements. Since they are converted to CALL statements, it looked
as if all of COMMON had to be marked as being possibly redefined
for every assignment statement, by calling THROINCOMMON. This is a
very slow routine, especially when it is called mulitple number of
times. This edit does NOT call it for library functions, which the
character assignment statements are.
Module:
DEFPT
2524 JB 13-Mar-85
Change E292 prefix from INS to INC.
Modules:
CMND20 COMMAN ERROUT
2525 DCE 19-Mar-85 QAR 853010
Speed up optimization of programs with very large symbol tables.
When the optimizer wants to mark variables in COMMON as potentially
changed (for a CALL statement, for example), the entire symbol
table gets searched for variables which are both in COMMON and in
the CHOSEN list (with DISPIX=1). This is too time-consuming. When
the CHOSEN list is set up, keep a CMNMASK word which indicates which
elements of the CHOSEN list represent COMMON blocks, and use this
mask to update the ACC field in THROINCOMMON instead of doing symbol
table walk(s).
Module:
DEFPT
2526 AlB 27-Mar-85
Macro ACMLT modified to correctly handle a look-ahead problem
which was causing some continued lines to either be printed twice,
or to be printed as a blank line. This would also cause garbage
in the listing if that line contained an error.
Module:
LEXICA
2527 AlB 28-Mar-85
The DISCARD routine in LISTNG was causing all trailing comments
to be displayed whenever a preceding source line had an error.
However, the BACKTYPE routine gets confused if one attempts
to type a line which does not (yet) have a line terminator.
Solution is not to use BACKTYPE when compacting the buffer.
Module:
LISTNG
2530 AlB 3-Apr-85
Change the wording of E78 in ERROVD so that it matches the wording of
E78 in ERROUT. This was causing a problem with Tops-10 testing
because ORGs didn't match.
Module:
ERROVD
***** End V10 Development *****
;.BEGINR REVISION HISTORY
;.COMPONENT FORTRA
;.VERSION 10
;.AUTOPATCH 11
;.EDIT 2531 ADD ERROR MESSAGE FOR SUBROUTINE NAME IN I/O LISTS
;; Produce an error message if trying to put a subroutine
;; name in an I/O statement list.
; CDM,10-Apr-85,SPR:NONE
; A:SRC REVHST.MAC, ACT1.BLI
;;
;.EDIT 2532 CORRECT /DEB:ARG TO NOT GIVE MESSAGE FOR SUBROUTINE
;; Only put out type checking information for known (called)
;; function names. Subroutine and ambiguous external names
;; should not have type checking information output.
; CDM,10-Apr-85,SPR:NONE
; A:SRC REVHST.MAC, EXPRES.BLI, FIRST.BLI, RELBUF.BLI
;;
;.EDIT 2533 CORRECT FORMAT FLAGGING OF QUOTES WITHIN ALPHA LITERALS
;; Do not put out the 'commas needed' compatibility flagger
;; message when quotes are included within an alpha literal.
; AlB,10-May-85,SPR:NONE
; A:SRC FORMAT.BLI
;;
;.EDIT 2534 DUPLICATE ERROR MESSAGES IN SUBSTRING ASSIGNMENT
;; In SUBASSIGN set the STORD bit in the left hand expression
;; of the assignment and delete the call to NAMSET.
; MEM,30-May-85
; A:SRC STA0.BLI
;;
;.EDIT 2535 CAN'T INCLUDE PROTECTED FILE FROM [1,2]
;; Set the PO.PRV bit in the FILOP arg block.
; MEM,7-Jun-85
; A:SRC STA2.BLI
;;.EDIT 2536 RESERVED FOR AUTOPATCH
;;
;.EDIT 2537 /FLAG:VMS GIVES EXTRA INVALID MESSAGE FOR NAMELIST
;; When no FMT= or NML= is given in a format expression,
;; FMT= is the default. FMTSCAN is called, but doesn't
;; know if it is FMT= has really been given or not. Add
;; argument to indicate this.
; CDM,16-JUL-85,SPR:NONE
; A:SRC ACT0.BLI
;;
;.EDIT 2540 DOT AT END OF STATEMENT CAUSES NEXT STATEMENT TO BE SKIPPED
;; When a program contains an extra period at the end of
;; a statement line, the lexical scanner looks for a dotted
;; operator. Since it fails when it runs out of statement,
;; it erroneously skips past the next statement.
; AlB,26-JUL-85,QAR:853096
; A:SRC LEXICA.BLI
;;
;;.ENDA 24-JUN-85
;;
;.EDIT 2541 INDUCTION VARIABLE INCORRECT UPON EXIT FROM DO LOOP
;; When the loop count can stay in a register, but the induction
;; variable must be materialized (MATRLZIXONLY bit is set), the
;; induction variable may not be updated after the last time
;; through the loop.
; MEM,1-AUG-85,SPR:10-35285
; A:SRC CGDO.BLI
;;.EDIT 2542 Reserved for autopatch
;;.ENDA 1-Aug-85
;;
;.EDIT 2543 REGISTER CONTAINING DO VARIABLE INCORRECT AFTER DO LOOP
;; If the contents of a DO variable is moved into a register
;; other than the AOBJN register, after exiting from the DO loop
;; this register should not be used for the DO variable (it is
;; not updated the last time).
; MEM,9-AUG-85,SPR:20-20863
; A:SRC DOALC.BLI
;;
;.EDIT 2544 LOSE NEG FLAG DURING SKELETON OPT
;; When converting subtract node into add node, don't just set neg
;; flag to one, because it might already be set and need to be
;; cleared.
; MEM,13-AUG-85,SPR:NONE
; A:SRC P2S1.BLI
;;
;.EDIT 2545 BAD LISTINGS WITH STOP/PAUSE STATEMENT AND TOO MANY DIGITS
;; Detect too many digits on the end of STOP/PAUSE statements and
;; stop saving them away. Too many digits will write over memory
;; that isn't allocated for the literal constant.
; CDM,26-AUG-85,SPR:NONE
; A:SRC LEXICA.BLI
;;
;.EDIT 2546 ITEM ON STK SHOULD BE BYTEPOINTER NOT JUST ADDRESS
;; In WHILSTA when we push the conditional expression onto STK, we should
;; push a bytepointer to the expression instead of the expression itself
;; because this is what IFNOTGEN is expecting.
; MEM,5-SEP-85,SPR:NONE
; A:SRC STA3.BLI
;;.EDIT 2547 Reserved for autopatch
;;.ENDA 5-Sep-85
;;
;.EDIT 2550 DEFINITION PTS INCORRECTLY HANDLES STMT FUNCTIONS
;; Only parameters of a statement function were used to calculate the
;; definition points of variables, however, the body of the statement
;; function must be used in definition point calculations also. A
;; variable, other than a parameter to the statement function, may be
;; changed by itself being a parameter in a function call within the
;; statement function.
; MEM,11-SEP-85,SPR:NONE
; A:SRC DEFPT.BLI
;;
;.EDIT 2551 NEG FLAG LOST DURING COMMON SUB ELIMINATION
;; The expression -(-X+Y)+Z was transformed into X+(Y+Z) because when
;; Y and Z were put together only the flags immediately in front of them
;; were carried along. Any flags on the plus node above the Y must be
;; XORed together with Y's flags to get the new flags for Y in the
;; new expression.
; MEM,12-SEP-85,SPR:NONE
; A:SRC COMSUB.BLI
;;
;.EDIT 2552 RECTYPE ACCEPTED AS OPEN SPECIFIER
;; Removed RECTYPE as an accepted abbreviation for RECORDTYPE.
; MEM,16-SEP-85,SPR:NONE
; A:SRC STA1.BLI
;;
;;.EDIT 2553 RESERVED FOR AUTOPATCH
;;.ENDA 10-Oct-85
;;
;.EDIT 2554 SFN WITH A USER FNCALL CAUSES BAD CODE
;; When a SFN calls a user function and passes it a non-formal variable
;; which the user function changes, then any registers containing the
;; the old value of the non-formal can not be used in place of the
;; variable in the following statements - call VARCLOBB on all such
;; variables.
; MEM,31-OCT-85,SPR:NONE
; A:SRC REGAL2.BLI
;;
;;.EDIT 2555 RESERVED FOR AUTOPATCH
;;.EDIT 2556 RESERVED FOR AUTOPATCH
;;.ENDA 1-Nov-85
;;
;.EDIT 2557 ALLOW GENERIC FUNCTION NAMES IN INTRINSIC STATEMENTS
;; Check for the use of specific function names in argument lists
;; instead of in INTRINSIC statements.
; JB,6-NOV-85,SPR:20-20970
; A:SRC EXPRES.BLI,STA0.BLI,STA3.BLI
;;
;.EDIT 2560 CONTINUATION LINES IGNORED
;; When a source line is continued onto several lines, CHARPOS must be
;; set back to the beginning of the line. If CHARPOS is left pointing
;; to the end of the line, then everything on that line will be ignored.
; MEM,11-NOV-85,SPR:20-20964
; A:SRC LEXICA.BLI
;;
;;.ENDA 14-NOV-85
;.EDIT 2561 PROAR. AND PROSB. FLAGGED BY IMPLICIT NONE
;; When using IMPLICIT NONE with /DEBUG:BOUNDS or /DEBUG:ALL, PROAR.
;; and PROSB. get warnings for not being explicitly defined. We are
;; now making sure that the compiler knows they are library functions
;; and not user symbols.
; CDM,19-NOV-85,SPR:20-20985
; A:SRC ARRXPN.BLI
;;
;.EDIT 2562 INCORRECT WARNINGS WITH IMPLICIT NONE
;; When using IMPLICIT NONE, a symbol in an EXTERNAL statement gets a
;; warning that it must be explicitly declared. If the symbol isn't
;; used as a function in the same program it shouldn't get the warning
;; because function types must be explicitly declared, whereas
;; subroutines needn't be. We added a check for this.
; JB,9-DEC-85,SPR:10-35412
; A:SRC ACT1.BLI,OUTMOD.BLI
;;
;.EDIT 2563 SPURIOUS IBIT IN MOVEM STORING FORMAL SBPGM INTO DUMMY ARG
;; When a subprogram has a subprogram name as a formal parameter, the
;; the indirect bit is set in the STE for the subprogram name after the
;; address of the subprogram has been moved into the dummy argument.
;; However, if this subprogram has an entry statement (also passing the
;; subprogram name as a parameter) the indirect bit in the STE must be
;; ignored when moving the address of the subprogram into the dummy
;; argument.
; MEM,17-Dec-85,SPR:20-CS00071
; A:SRC CGDO.BLI
;;
;;.EDIT 2564 RESERVED FOR AUTOPATCH
;.ENDA 19-DEC-85
;;
;.AUTOPATCH 14
;.EDIT 2565 LONG CONTINUATION LINES CAUSE COMPILER TO LOOP INFINITELY
;; After lexica's buffer is full, it keeps on writing over the next
;; contiguous words in memory. This obviously can cause problems,
;; so don't let LINLCURR (pointer into buffer) ever advance past the
;; end of the buffer.
; MEM,8-Jan-85,SPR:10-35425
; A:SRC REVHST.MAC,LEXCLA.BLI
;;
;;.EDIT 2566 RESERVED FOR AUTOPATCH
;;.ENDA 23-JAN-86
;;
;.EDIT 2567 INCORRECT ARRAYREFS FOR ADJUSTABLY DIMENSIONED ARRAYS
;; Dimsension table was shared between two arrays if the upper
;; bounds are the same and the lower bound of the first array is 1.
;; This is bad news for subsequent arrays with the same upper bound
;; but with different lower bounds.
; MEM,6-Feb-85,SPR:10-35439
; A:SRC REVHST.MAC,ACT1.BLI
;;
;.EDIT 2570 ICES WITH ARRAYS WITH BOTH CONSTANT AND VARIABLE DIMENSIONS
;; When we have adjustably dimensioned arrays, .Innnn variables are
;; created. A use count (IDUSECNT) is associated with each variable that
;; tells the number of uses of that variable - if this use count drops to
;; zero then we don't need to allocate the variable. When some of the
;; dimensions of an array are constant and some are variable, the IDUSECNT
;; field was being set in the constant table entries. This should not be.
; MEM,19-Feb-85,SPR:10-35308
; A:SRC REVHST.MAC,ACT1.BLI
;;
;;.EDIT 2571 RESERVED FOR AUTOPATCH
;;.ENDA 28-Feb-86
;;
;.EDIT 2572 REG ALLOC FOR OPEN DONE IN DIFFERENT ORDER FROM CODE GENERATION
;; Complexity walk, register allocation and code generation must be done
;; in the same order. For the open statement the register allocation was
;; done in the reverse order from complexity and code generation.
; MEM,12-Mar-86,SPR:10-35449
; A:SRC REVHST.MAC,STREGA.BLI
;;
;.EDIT 2573 EXTRA ERROR MESSAGE IF 99-100 CONTINUATION LINES
;; When there are exactly 99-100 continuation lines, routine SKIPDL
;; gives an extra error message. This error message should never be
;; put out.
; MEM,17-Mar-86,SPR:10-35425
; A:SRC REVHST.MAC,LEXICA.BLI
;;.EDIT 2574 RESERVED FOR AUTOPATCH
;;.ENDA 08-APR-86
;;
;.EDIT 2575 /DEBUG:ARGUMENTS THOUGHT SCALAR WAS EXTERNAL
;; A scalar, which has the same name as the routine its in, and is
;; passed to another routine, gives a structure type of "routine"
;; instead of "singleton" to LINK for /DEBUG:ARGUMENTS typechecking.
; CDM,28-APR-86,SPR:20-21228
; A:SRC REVHST.MAC,RELBUF.BLI
;;
;.ENDA
;.ENDV
;.ENDR REVISION HISTORY
***** End Revision History *****
***** Begin Version 11 *****
4500 MEM 21-Jan-85
Support of the new OPEN and INQUIRE statement keywords.
Modules:
CGSTMN CMND20 ERROUT FIRST REGAL2 SKSTMN STA1 STREGA
TABLES TSTR UTIL VER5
4501 MEM 22-Jan-85
Support of the indexed READ statement and new keywords.
Modules:
ACT0 CMND20 CGSTMN DEFPT ERROUT FIRST SKSTMN STA0
STREGA TABLES TSTR UTIL
4502 MEM 22-Jan-85
Support of the DELETE statement.
Modules:
CGSTMN CODETA DEFPT DOALC FIRST GRAPH CODETA PH3G
PNROPT SKSTMN STA1 STREGA TABLES TSTR VER5
4503 MEM 22-Jan-85
Support of the REWRITE statement.
Modules:
CGSTMN CODETA DEFPT DOALC ERROUT FIRST GRAPH CODETA
PH3G PNROPT REGAL2 SKSTMN STA0 STREGA TABLES TSTR
VER5
4504 MEM 22-Jan-85
Support of the UNLOCK statement.
Modules:
CGSTMN CODETA DOALC FIRST GRAPH CODETA PH3G PNROPT
SKSTMN STA3 STREGA TABLES TSTR VER5
4505 MEM 2-Apr-85
Rip out doing register substitution for keys in an open statement,
because forots can't get the contents of registers in a secondary
arg block.
Module:
UTIL
4506 MEM 25-Jul-85
Added a case for call stms to ELIM so that we will common sub the
indices of character arrays and substrings in assignments stmts.
Module:
COMSUB
4507 MEM 25-Jul-85
Create lower/length substring node.
Modules:
CMPLEX CGEXPR P2S1 REGAL2 TABLES
4510 MEM 14-Aug-85
Move code for substring bounds checking from DOTDCHECK back to
P2SKSUBSTR.
Modules:
CMPLEX P2S1
4511 CDM 23-Aug-85
Detect too many digits on the end of STOP/PAUSE statements and
stop saving them away. Too many digits will write over memory
that isn't allocated for the literal constant.
Module:
LEXICA
4512 CDM 26-Aug-85
Delete old never called routines. TMPGEN, STRNGSCAN, ZSIXBIT.
Modules:
ACT1 STA1 LISTOU
4513 CDM 12-Sep-85
Improvements to /STATISTICS for reporting symbol table size
and COMMON block size.
Modules:
GLOBAL IOFLG INOUT LISTOU OUTMOD UNEND
4514 MEM 13-Sep-85
Fillin in blank fields SRCID, OPRCLS, and SRCLBL in the node (character
assignment) under a character statement function node.
Module:
STA0
4515 CDM 20-Sep-85
Phase I for VMS long symbols. Create routine ONEWPTR for Sixbit
symbols. For now, return what is passed it. For phase II, return
[1,,pointer to symbol].
Modules:
ARRXPN CGDO CGEXPR CMPLEX DEBUG DOALC DOXPN
EXPRES GCMNSB LEXICA P2S1 SRCA TSTR
4516 CDM 2-Oct-85
Phase I.I for VMS long symbols. Pass Sixbit to all error message
routines, do not pass addresses of Sixbit anymore. In later edits
we will pass [length,,pointer to symbol] instead of a pointer to
the symbol to the error message routines. Amazingly, this generates
LESS code, since no byte pointer is constructed.
Modules:
ACT0 ACT1 ARRXPN DRIVER ERROUT EXPRES FIRST
GCMNSB GNRCFN INOUT OUTMOD STA0 STA3
4517 MEM 4-Oct-85
Add inline 1-char relationals and assignments.
Modules:
CGEXPR CGSTMN CMPLEX COMSUB DEFPT FIRST OPGNTA
OUTMOD P2S1 P2S2 PEEPOP PH3G PNROPT REGAL2
SKSTMN SRCA STREGA TABLES
4520 MEM 4-Oct-85
Pool similar .Dnnnns.
Modules:
CMPLEX FIRST GLOBAL LISTOU OUTMOD
4521 JB 16-OCT-85
Improved the undefined label error message. FATLERR is called
instead of the routine generating the error message locally.
Modules:
DRIVER ERROUT
4522 MEM 5-Nov-85
Add inline 1-char relationals and assignments for function calls
and dummy variables.
Modules:
CGEXPR OPGNTA P2S1 SKSTMN STREGA TABLES
4523 MEM 6-Nov-85
Add propagation of 1-char constants.
Module:
PNROPT
4524 CDM 21-NOV-85
Additions to edit 2561. Fill in IDLIBFNFLG for FDDT. It's
beyond the scope of a maintenance edit.
Module:
ARRXPN DEBUG
4525 CDM 22-Nov-85
Simple change to IOFORM in CGSTMN. A DO index in a format
specifier can be a regcontents node by code generation. A
definite error, but not worth an internal compiler error.
For this particular case, tone it down, and give something
a little less severe.
Module:
CGSTMN
4526 MEM 3-Dec-85
Give an error when RMS stuff is used on TOPS10.
Modules:
ERROUT STA0 STA1 STA3
4527 CDM 1-Jan-86
VMS Long symbols phase II. Convert all internal symbols from
one word of sixbit to [length,,pointer]. The lengths will be one
word until a later edit, which will store and use long symbols.
Modules:
ACT0 ACT1 ARRXPN CGDO CGSTMN CMND20 COMSUB
DATAST DEBUG DRIVER ERROUT ERROVR FIRST GCMNSB
GNRCFN INOUT IOFLG IOPT LEXAID LEXICA LISTNG
LISTOU OUTMOD P2S1 PH3G PHA3 PNROPT REGUTL
RELBUF SKSTMN SRCA STA0 STA2 STA3 TABLES
TSTR UNEND UTIL
4530 19-Feb-86
Add long symbol support to compiler needing no work in forots.
Modules:
ACT0 CGDO CGSTMN CMND20 CODETA DATAST DEBUG
ERROUT GLOBAL IOFLG LEXAID LEXCLA LEXICA LEXSUP
LISTOU OUTMOD PH3G RELBUF REQREL TABLES UNEND
4531 MEM 19-Feb-86
Output secondary symbol table for FORDDT.
Module:
LISTOU
4532 MEM 19-Feb-86
Add long symbol support to compiler requiring forots work.
Modules:
CGDO CGSTMN DEBUG
4533 CDM 1-Apr-86
Fix for long symbols with NAMELIST. TBLSEARCH is being called
later in the compiler than has been before. SNADDR and SNREF
are shared in memory for labels. They are used for different
purposes in code generation and previous to code generation.
Fix TESTENTRY to not change SNREF if SNADDR has been set for
code generation.
Modules:
CGSTMN LEXICA SRCA
4534 CDM 12-May-86
Correct error message. KEYBUFFER was being overwritten before
error message was displayed.
Module:
ACT0
4535 CDM 13-May-86
Make Link do a 30 bit fixup for a one word pointer to a label
/EXTEND. This shows up in NAMELIST processing, since we have
labels pointing to Sixbit for the names.
Also clean up peephole buffer output in LISTOU to stop using
magic numbers.
Modules:
CGSTMN LISTOU TABLES
4536 CDM 15-May-86
Update copyright notice.
4537 MEM 21-May-86
Add lexeme for underline so we get better error messages when
underline is misused.
Modules:
EXPRES LEFT72 LEXICA LEXNAM LEXSUP
4540 MEM 30-May-86
Only perform check for IOKEY if we have a READ statement.
Module:
UTIL
4541 MEM 3-Jun-86
Make MAXREC legal instead of issuing a VMS incompatible warning.
Modules:
TABLES
4542 CDM 26-Jun-86
Remove KA10 and CKA10. No one uses these.
Module:
IOFLG
4543 JB 9-Jul-86
Allow list-directed I/O for internal files, but flag it as
non-standard.
Modules:
ERROUT STA0
ENDV11
\
PAGE
SUBTTL VERSION NUMBER
LASTED==0 ;LAST EDITOR
MAJVER==11 ;MAJOR VERSION NUMBER
MINVER==0 ;MINOR VERSION NUMBER
EDNUM==4543 ;EDIT NUMBER
JOBVER=137
LOC JOBVER
EXP <LASTED>B2+<MAJVER>B11+<MINVER>B17+<EDNUM>
END