Commit fc370eff by Craig Burley Committed by Craig Burley

New tests

From-SVN: r25636
parent 460fb615
1999-03-08 Craig Burley <craig@jcb-sc.com> 1999-03-08 Craig Burley <craig@jcb-sc.com>
* g77.f-torture/compile/19990305-0.f: New test.
* g77.f-torture/execute/19981119-0.f: New test.
1999-03-08 Craig Burley <craig@jcb-sc.com>
* g77.f-torture/execute/970625-2.f: call ABORT if final * g77.f-torture/execute/970625-2.f: call ABORT if final
result is not correct, instead of just printing it. result is not correct, instead of just printing it.
Add this checking via newly introduced obfuscation, to Add this checking via newly introduced obfuscation, to
......
* Date: Fri, 5 Mar 1999 00:35:44 -0500 (EST)
* From: Denes Molnar <molnard@phys.columbia.edu>
* To: fortran@gnu.org
* Subject: f771 gets fatal signal 6
* Content-Type: TEXT/PLAIN; charset=US-ASCII
* X-UIDL: 8d81e9cbdcc96209c6e9b298d966ba7f
*
* Hi,
*
*
* Comiling object from the source code below WORKS FINE with
* 'g77 -o hwuci2 -c hwuci2.F'
* but FAILS with fatal signal 6
* 'g77 -o hwuci2 -O -c hwuci2.F'
*
* Any explanations?
*
* I am running GNU Fortran 0.5.23 with GCC 2.8.1 (glibc1).
*
*
* Denes Molnar
*
* %%%%%%%%%%%%%%%%%%%%%%%%%
* %the source:
* %%%%%%%%%%%%%%%%%%%%%%%%%
*
CDECK ID>, HWUCI2.
*CMZ :- -23/08/94 13.22.29 by Mike Seymour
*-- Author : Ulrich Baur & Nigel Glover, adapted by Ian Knowles
C-----------------------------------------------------------------------
FUNCTION HWUCI2(A,B,Y0)
C-----------------------------------------------------------------------
C Integral LOG(A-EPSI-BY(1-Y))/(Y-Y0)
C-----------------------------------------------------------------------
IMPLICIT NONE
DOUBLE COMPLEX HWUCI2,HWULI2,EPSI,Y1,Y2,Z1,Z2,Z3,Z4
DOUBLE PRECISION A,B,Y0,ZERO,ONE,FOUR,HALF
EXTERNAL HWULI2
COMMON/SMALL/EPSI
PARAMETER (ZERO=0.D0, ONE =1.D0, FOUR= 4.D0, HALF=0.5D0)
IF(B.EQ.ZERO)THEN
HWUCI2=CMPLX(ZERO,ZERO)
ELSE
Y1=HALF*(ONE+SQRT(ONE-FOUR*(A+EPSI)/B))
Y2=ONE-Y1
Z1=Y0/(Y0-Y1)
Z2=(Y0-ONE)/(Y0-Y1)
Z3=Y0/(Y0-Y2)
Z4=(Y0-ONE)/(Y0-Y2)
HWUCI2=HWULI2(Z1)-HWULI2(Z2)+HWULI2(Z3)-HWULI2(Z4)
ENDIF
RETURN
END
*
* %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
* X-Delivered: at request of burley on mescaline.gnu.org
* Date: Sat, 31 Oct 1998 18:26:29 +0200 (EET)
* From: "B. Yanchitsky" <yan@im.imag.kiev.ua>
* To: fortran@gnu.org
* Subject: Bug report
* MIME-Version: 1.0
* Content-Type: TEXT/PLAIN; charset=US-ASCII
*
* There is a trouble with g77 on Alpha.
* My configuration:
* Digital Personal Workstation 433au,
* Digital Unix 4.0D,
* GNU Fortran 0.5.23 and GNU C 2.8.1.
*
* The following program treated successfully but crashed when running.
*
* C --- PROGRAM BEGIN -------
*
subroutine sub(N,u)
integer N
double precision u(-N:N,-N:N)
C vvvv CRASH HERE vvvvv
u(-N,N)=0d0
return
end
program bug
integer N
double precision a(-10:10,-10:10)
N=10
call sub(N,a)
stop
end
*
* C --- PROGRAM END -------
*
* Good luck!
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment