[Search for users] [Overall Top Noters] [List of all Conferences] [Download this site]

Conference turris::fortran

Title:Digital Fortran
Notice:Read notes 1.* for important information
Moderator:QUARK::LIONEL
Created:Thu Jun 01 1995
Last Modified:Fri Jun 06 1997
Last Successful Update:Fri Jun 06 1997
Number of topics:1333
Total number of notes:6734

1264.0. "run-time ACCVIO with /OPTIMIZE=(LEVEL=3) or higher" by CUJO::SAMPSON () Thu Apr 17 1997 00:46

	Hello again,

	One of our customers tripped over an optimization problem
in the latest Digital Fortran 77 for OpenVMS Alpha compiler.  He
spent some time cutting it down for me, and I did some more cutting.
My two next replies are the source files, P.FOR and P.INC, that can
be used to reproduce the run-time ACCVIO.

	Workarounds are available (compiling with optimization
level 2 or lower, or rearranging source code until the ACCVIO
disappears).  However, this has already cost the customer time,
and a reasonably timely fix would be appreciated.

	Thanks,
	Bob Sampson
T.RTitleUserPersonal
Name
DateLines
1264.1P.FORCUJO::SAMPSONThu Apr 17 1997 00:4767
!
! 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.2P.INCCUJO::SAMPSONThu Apr 17 1997 00:4725
	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.3looks like a bugTLE::WHITLOCKStan WhitlockThu Apr 17 1997 09:294
I get the ACCVIO with our latest DV77AV... we'll have a look.  Thanks for the
same example.

/Stan
1264.4... or perhaps 5656WIBBIN::NOYCEPulling weeds, pickin' stonesThu Apr 17 1997 09:381
Fortran devos: this looks like GEM_BUGS 5750.
1264.5how soon?CUJO::SAMPSONFri Apr 18 1997 10:071
    Thanks.  Any idea when an updated kit with this fix may be available?
1264.6QUARK::LIONELFree advice is worth every centFri Apr 18 1997 12:533
We have an ECO kit planned for sometime in the next few weeks.

			Steve
1264.7interaction with /CHECK=BOUNDSCUJO::SAMPSONFri Apr 18 1997 22:0120
	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.8smee againCUJO::SAMPSONFri May 16 1997 01:128
	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.9QUARK::LIONELFree advice is worth every centFri May 16 1997 10:423
Next week is our plan.

		Steve
1264.10Er, ah, hate to ask, but...CUJO::SAMPSONTue Jun 03 1997 01:201
	...any updated estimate on that DFAV ECO?
1264.11QUARK::LIONELFree advice is worth every centTue Jun 03 1997 09:304
We ran into a bit of snag with the accompanying RTL update.  The ECO kit is
being packaged this week.

					Steve