| T.R | Title | User | Personal Name
 | Date | Lines | 
|---|
| 1264.1 | P.FOR | CUJO::SAMPSON |  | Wed Apr 16 1997 23:47 | 67 | 
|  | !
! This program demonstrates an optimization problem for
! Digital Fortran 77 for OpenVMS Alpha EV7.1-107-3313,
! linked 13-JAN-1997 15:23:01.02.  When compiled with
! /OPTIMIZE=(LEVEL=3) or higher, a run-time ACCVIO will
! occur.  The source code has been cut down to nearly
! the minimum; changes make the problem go into hiding.
! Two files are required; P.FOR and P.INC.
!
! $ FORTRAN P
! $ LINK P
! $ RUN P
!
	PROGRAM P
	IMPLICIT NONE
	INCLUDE 'P.INC'
	INTEGER*4 I
	ITP = 1
	TP(ITP).TP_I1 = 5
	TP(ITP).TP_I2 = 1
	TP(ITP).TP_R4 = 4.321
	CALL S()
	DO I = 1,16
	  WRITE (*,*) RA1(I), RA1(1632+I)
	END DO
	END
	SUBROUTINE S()
	IMPLICIT NONE
	INCLUDE 'P.INC'
	INTEGER*4 I,J,K
	IF (TP(ITP).TP_I2 .EQ. 0) THEN
	  TP(ITP).TP_R3 = FLOAT(IV1) + 1E0
	ELSE
	  TP(ITP).TP_R3 = FLOAT(IV1) - 1E0
	END IF
	K = NRA1 / 2
	K = K + 1
	DO I = 1,51
	  DO J = 1,8
	    RA1(K) = -1E0
	    K = K + 1
	    RA1(K) = +1E0
	    K = K + 1
	  END DO
	END DO
!
! When compiled with /OPTIMIZE=(LEVEL=3) or higher, index variable K
! (which is optimized into a register) appears to get trashed,
! resulting in a run-time ACCVIO.  Inserting a TYPE statement
! here makes the optimization problem go into hiding.
!
	DO J = 1,4
	  RA1(K) = -1E0
	  K = K + 1
	  RA1(K) = +1E0
	  K = K + 1
	END DO
	RETURN
	END
 | 
| 1264.2 | P.INC | CUJO::SAMPSON |  | Wed Apr 16 1997 23:47 | 25 | 
|  | 	INTEGER*4	NRA1
	PARAMETER	(NRA1 = 1648)
	INTEGER*4	MAXTP
	PARAMETER	(MAXTP = 10)
	STRUCTURE /TP/
	  INTEGER*4	TP_I1
	  INTEGER*4	TP_I2
	  REAL*4	TP_R1
	  REAL*4	TP_R2
	  REAL*4	TP_R3
	  REAL*4	TP_R4
	END STRUCTURE
	REAL*4		RA1 (NRA1)
	INTEGER*4	IV1
	INTEGER*4	IV2
	RECORD /TP/ TP (MAXTP)
	INTEGER*4	ITP
	COMMON /CMN1/ RA1, IV1, IV2
	COMMON /CMN2/ TP
	COMMON /CMN3/ ITP
 | 
| 1264.3 | looks like a bug | TLE::WHITLOCK | Stan Whitlock | Thu Apr 17 1997 08:29 | 4 | 
|  | I get the ACCVIO with our latest DV77AV... we'll have a look.  Thanks for the
same example.
/Stan
 | 
| 1264.4 | ... or perhaps 5656 | WIBBIN::NOYCE | Pulling weeds, pickin' stones | Thu Apr 17 1997 08:38 | 1 | 
|  | Fortran devos: this looks like GEM_BUGS 5750.
 | 
| 1264.5 | how soon? | CUJO::SAMPSON |  | Fri Apr 18 1997 09:07 | 1 | 
|  |     Thanks.  Any idea when an updated kit with this fix may be available?
 | 
| 1264.6 |  | QUARK::LIONEL | Free advice is worth every cent | Fri Apr 18 1997 11:53 | 3 | 
|  | We have an ECO kit planned for sometime in the next few weeks.
			Steve
 | 
| 1264.7 | interaction with /CHECK=BOUNDS | CUJO::SAMPSON |  | Fri Apr 18 1997 21:01 | 20 | 
|  | 	Okay, great, we're looking forward to it.
	Regarding possible workarounds, the /CHECK=[NO]BOUNDS option
appears to affect the optimization level at which the run-time ACCVIO
appears:
/OPTIMIZE=LEVEL=	0	1	2	3	4	5
----------------  ------- ------- ------- ------- ------- -------
/CHECK=NOBOUNDS        ok      ok  ACCVIO  ACCVIO  ACCVIO  ACCVIO
/CHECK=BOUNDS          ok      ok      ok  ACCVIO  ACCVIO  ACCVIO
	Unfortunately, this problem shows up in a module that they
really want to run at full speed.  So /CHECK=BOUNDS and/or decreased
optimization are not considered the ideal workarounds.  Perhaps they
can subtly rearrange the source code to make the problem go into hiding.
	So far, other options don't appear to have any effect.
	Thanks,
	Bob Sampson
 | 
| 1264.8 | smee again | CUJO::SAMPSON |  | Fri May 16 1997 00:12 | 8 | 
|  | 	Hello again,
	Al Meier asked me to pester you again for a guesstimate on when
the DFAV ECO will be available.  It's been four weeks, and well worth
waiting for, I'm sure...
	Thanks,
	Bob Sampson
 | 
| 1264.9 |  | QUARK::LIONEL | Free advice is worth every cent | Fri May 16 1997 09:42 | 3 | 
|  | Next week is our plan.
		Steve
 | 
| 1264.10 | Er, ah, hate to ask, but... | CUJO::SAMPSON |  | Tue Jun 03 1997 00:20 | 1 | 
|  | 	...any updated estimate on that DFAV ECO?
 | 
| 1264.11 |  | QUARK::LIONEL | Free advice is worth every cent | Tue Jun 03 1997 08:30 | 4 | 
|  | We ran into a bit of snag with the accompanying RTL update.  The ECO kit is
being packaged this week.
					Steve
 |