public inbox for gcc@gcc.gnu.org
 help / color / mirror / Atom feed
* f77 on sco5 fails on GOTOFF references
@ 1997-12-29 22:49 Robert Lipe
  1997-12-30  1:29 ` Richard Henderson
  0 siblings, 1 reply; 20+ messages in thread
From: Robert Lipe @ 1997-12-29 22:49 UTC (permalink / raw)
  To: egcs; +Cc: jcardoso

The attached program was sent to me by Joao Cardoso. When compiled 
with "-O -fpic", emits assembly code that the native SCO assemblers
for neither SCO OpenServer 5 nor Unixware 7/System V Release 5 can
grok.   Given the common parentage, I suspect this code would fail
on systems derived from the other AT&T parentage SVR4 ELF assemblers.

The specific line in the assembly that fails is:

        pushl $.LC0@GOTOFF(%ebx)

Can anyone offer hints as to which stick I can use to beat these 
targets into not emitting this construct?  The references to "magic"
in the i386.c and i386.md files made me think that asking for help
would be wise. :-)

Thanx,
RJL




      subroutine scaleg (n,ma,a,mb,b,low,igh,cscale,cperm,wk)
c
c     *****parameters:
      integer igh,low,ma,mb,n
      double precision a(ma,n),b(mb,n),cperm(n),cscale(n),wk(n,6)
c
c     *****local variables:
      integer i,ir,it,j,jc,kount,nr,nrp2
      double precision alpha,basl,beta,cmax,coef,coef2,coef5,cor,
     *                 ew,ewc,fi,fj,gamma,pgamma,sum,t,ta,tb,tc
c
c     *****fortran functions:
      double precision dabs, dlog10, dsign
c     float
c
c     *****subroutines called:
c     none
c
c     ---------------------------------------------------------------
c
c     *****purpose:
c     scales the matrices a and b in the generalized eigenvalue
c     problem a*x = (lambda)*b*x such that the magnitudes of the
c     elements of the submatrices of a and b (as specified by low
c     and igh) are close to unity in the least squares sense.
c     ref.:  ward, r. c., balancing the generalized eigenvalue
c     problem, siam j. sci. stat. comput., vol. 2, no. 2, june 1981,
c     141-152.
c
c     *****parameter description:
c
c     on input:
c
c       ma,mb   integer
c               row dimensions of the arrays containing matrices
c               a and b respectively, as declared in the main calling
c               program dimension statement;
c
c       n       integer
c               order of the matrices a and b;
c
c       a       real(ma,n)
c               contains the a matrix of the generalized eigenproblem
c               defined above;
c
c       b       real(mb,n)
c               contains the b matrix of the generalized eigenproblem
c               defined above;
c
c       low     integer
c               specifies the beginning -1 for the rows and
c               columns of a and b to be scaled;
c
c       igh     integer
c               specifies the ending -1 for the rows and columns
c               of a and b to be scaled;
c
c       cperm   real(n)
c               work array.  only locations low through igh are
c               referenced and altered by this subroutine;
c
c       wk      real(n,6)
c               work array that must contain at least 6*n locations.
c               only locations low through igh, n+low through n+igh,
c               ..., 5*n+low through 5*n+igh are referenced and
c               altered by this subroutine.
c
c     on output:
c
c       a,b     contain the scaled a and b matrices;
c
c       cscale  real(n)
c               contains in its low through igh locations the integer
c               exponents of 2 used for the column scaling factors.
c               the other locations are not referenced;
c
c       wk      contains in its low through igh locations the integer
c               exponents of 2 used for the row scaling factors.
c
c     *****algorithm notes:
c     none.
c
c     *****history:
c     written by r. c. ward.......
c     modified 8/86 by bobby bodenheimer so that if
c       sum = 0 (corresponding to the case where the matrix
c       doesn't need to be scaled) the routine returns.
c
c     ---------------------------------------------------------------
c
      if (low .eq. igh) go to 410
      do 210 i = low,igh
         wk(i,1) = 0.0d0
         wk(i,2) = 0.0d0
         wk(i,3) = 0.0d0
         wk(i,4) = 0.0d0
         wk(i,5) = 0.0d0
         wk(i,6) = 0.0d0
         cscale(i) = 0.0d0
         cperm(i) = 0.0d0
  210 continue
c
c     compute right side vector in resulting linear equations
c
      basl = dlog10(2.0d0)
      do 240 i = low,igh
         do 240 j = low,igh
            tb = b(i,j)
            ta = a(i,j)
            if (ta .eq. 0.0d0) go to 220
            ta = dlog10(dabs(ta)) / basl
  220       continue
            if (tb .eq. 0.0d0) go to 230
            tb = dlog10(dabs(tb)) / basl
  230       continue
            wk(i,5) = wk(i,5) - ta - tb
            wk(j,6) = wk(j,6) - ta - tb
  240 continue
      nr = igh-low+1
      coef = 1.0d0/float(2*nr)
      coef2 = coef*coef
      coef5 = 0.5d0*coef2
      nrp2 = nr+2
      beta = 0.0d0
      it = 1
c
c     start generalized conjugate gradient iteration
c
  250 continue
      ew = 0.0d0
      ewc = 0.0d0
      gamma = 0.0d0
      do 260 i = low,igh
         gamma = gamma + wk(i,5)*wk(i,5) + wk(i,6)*wk(i,6)
         ew = ew + wk(i,5)
         ewc = ewc + wk(i,6)
  260 continue
      gamma = coef*gamma - coef2*(ew**2 + ewc**2)
     +        - coef5*(ew - ewc)**2
      if (it .ne. 1) beta = gamma / pgamma
      t = coef5*(ewc - 3.0d0*ew)
      tc = coef5*(ew - 3.0d0*ewc)
      do 270 i = low,igh
         wk(i,2) = beta*wk(i,2) + coef*wk(i,5) + t
         cperm(i) = beta*cperm(i) + coef*wk(i,6) + tc
  270 continue
c
c     apply matrix to vector
c
      do 300 i = low,igh
         kount = 0
         sum = 0.0d0
         do 290 j = low,igh
            if (a(i,j) .eq. 0.0d0) go to 280
            kount = kount+1
            sum = sum + cperm(j)
  280       continue
            if (b(i,j) .eq. 0.0d0) go to 290
            kount = kount+1
            sum = sum + cperm(j)
  290    continue
         wk(i,3) = float(kount)*wk(i,2) + sum
  300 continue
      do 330 j = low,igh
         kount = 0
         sum = 0.0d0
         do 320 i = low,igh
            if (a(i,j) .eq. 0.0d0) go to 310
            kount = kount+1
            sum = sum + wk(i,2)
  310       continue
            if (b(i,j) .eq. 0.0d0) go to 320
            kount = kount+1
            sum = sum + wk(i,2)
  320    continue
         wk(j,4) = float(kount)*cperm(j) + sum
  330 continue
      sum = 0.0d0
      do 340 i = low,igh
         sum = sum + wk(i,2)*wk(i,3) + cperm(i)*wk(i,4)
  340 continue
      if(sum.eq.0.0d0) return
      alpha = gamma / sum
c
c     determine correction to current iterate
c
      cmax = 0.0d0
      do 350 i = low,igh
         cor = alpha * wk(i,2)
         if (dabs(cor) .gt. cmax) cmax = dabs(cor)
         wk(i,1) = wk(i,1) + cor
         cor = alpha * cperm(i)
         if (dabs(cor) .gt. cmax) cmax = dabs(cor)
         cscale(i) = cscale(i) + cor
  350 continue
      if (cmax .lt. 0.5d0) go to 370
      do 360 i = low,igh
         wk(i,5) = wk(i,5) - alpha*wk(i,3)
         wk(i,6) = wk(i,6) - alpha*wk(i,4)
  360 continue
      pgamma = gamma
      it = it+1
      if (it .le. nrp2) go to 250
c
c     end generalized conjugate gradient iteration
c
  370 continue
      do 380 i = low,igh
         ir = wk(i,1) + dsign(0.5d0,wk(i,1))
         wk(i,1) = ir
         jc = cscale(i) + dsign(0.5d0,cscale(i))
         cscale(i) = jc
  380 continue
c
c     scale a and b
c
      do 400 i = 1,igh
         ir = wk(i,1)
         fi = 2.0d0**ir
         if (i .lt. low) fi = 1.0d0
         do 400 j =low,n
            jc = cscale(j)
            fj = 2.0d0**jc
            if (j .le. igh) go to 390
            if (i .lt. low) go to 400
            fj = 1.0d0
  390       continue
            a(i,j) = a(i,j)*fi*fj
            b(i,j) = b(i,j)*fi*fj
  400 continue
  410 continue
      return
c
c     last line of scaleg
c
      end

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-29 22:49 f77 on sco5 fails on GOTOFF references Robert Lipe
@ 1997-12-30  1:29 ` Richard Henderson
  1997-12-30  8:53   ` Robert Lipe
  0 siblings, 1 reply; 20+ messages in thread
From: Richard Henderson @ 1997-12-30  1:29 UTC (permalink / raw)
  To: Robert Lipe; +Cc: egcs, jcardoso

On Mon, Dec 29, 1997 at 11:49:06PM -0600, Robert Lipe wrote:
> The attached program was sent to me by Joao Cardoso. When compiled 
> with "-O -fpic", emits assembly code that the native SCO assemblers
> for neither SCO OpenServer 5 nor Unixware 7/System V Release 5 can
> grok.   Given the common parentage, I suspect this code would fail
> on systems derived from the other AT&T parentage SVR4 ELF assemblers.
> 
> The specific line in the assembly that fails is:
> 
>         pushl $.LC0@GOTOFF(%ebx)

You are looking for a contruct that can generate an R_386_GOTOFF
relocation.  I'd thought SVR4 was canonical here -- it surprises 
me that it doesn't work.

It should be the same thing that 

  void hello(void)
  {
    printf("Hello, World\n");
  }
  
generates with -fpic.  Failing that, I'll have to defer on how 
to turn off @GOTOFF, though considering the performance hit you'd
take from always using @GOT, it would be worth convincing whoever
to fix those assemblers.


r~

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-30  1:29 ` Richard Henderson
@ 1997-12-30  8:53   ` Robert Lipe
  1997-12-30 17:43     ` John Carr
  0 siblings, 1 reply; 20+ messages in thread
From: Robert Lipe @ 1997-12-30  8:53 UTC (permalink / raw)
  To: Richard Henderson; +Cc: egcs, jcardoso

> > with "-O -fpic", emits assembly code that the native SCO assemblers
> > for neither SCO OpenServer 5 nor Unixware 7/System V Release 5 can
> > grok.   Given the common parentage, I suspect this code would fail
> > on systems derived from the other AT&T parentage SVR4 ELF assemblers.
> > 
> > The specific line in the assembly that fails is:
> > 
> >         pushl $.LC0@GOTOFF(%ebx)
> 
> You are looking for a contruct that can generate an R_386_GOTOFF
> relocation.  I'd thought SVR4 was canonical here -- it surprises 
> me that it doesn't work.

It's a bummer, for sure.

> It should be the same thing that 
> 
>   void hello(void)
>   {
>     printf("Hello, World\n");
>   }
>   
> generates with -fpic.  Failing that, I'll have to defer on how 
> to turn off @GOTOFF, though considering the performance hit you'd
> take from always using @GOT, it would be worth convincing whoever
> to fix those assemblers.

OK, that code doesn't quite emit the same thing, but it gave me a much
smaller example to work from.

The SVR5/x86 and OpenServer (and presumably SVR4/x86) assemblers will 
accept 
	pushl .LC0@GOTOFF(%ebx)
but not
	pushl $.LC0@GOTOFF(%ebx)

So apparently, these assemblers can't do a push immediate of an assembler-
computed offset.

Isn't this thne functional equivalent of
        leal .LC0@GOTOFF(%ebx),%eax
        pushl %eax
Oh, I guess this approach clobbers %eax.

It strikes me as odd that in years of GCC support on AT&T-derived
ELF assemblers we've never seen this failure before this Fortran case.
Is this just some sort of thing that the Fortan front-end does that 
gcc/g++ front-ends wouldn't do?

I'll report this to SCO in hopes they can fix the SVR5 assembler, but
I think we'll have this problem on many non-GAS x86 ELF targets.

-- 
Robert Lipe       http://www.dgii.com/people/robertl       robertl@dgii.com

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-30  8:53   ` Robert Lipe
@ 1997-12-30 17:43     ` John Carr
  1997-12-31  0:08       ` Robert Lipe
  0 siblings, 1 reply; 20+ messages in thread
From: John Carr @ 1997-12-30 17:43 UTC (permalink / raw)
  To: Robert Lipe; +Cc: egcs, jcardoso

> It strikes me as odd that in years of GCC support on AT&T-derived
> ELF assemblers we've never seen this failure before this Fortran case.
> Is this just some sort of thing that the Fortan front-end does that 
> gcc/g++ front-ends wouldn't do?

The RS/6000 had a similar bug a couple years back.  Fortran was trying
to compute the address of a constant, something which C never did.  I
think passing a constant argument by reference triggered the problem.
The machine description had to be changed in that case.


^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-30 17:43     ` John Carr
@ 1997-12-31  0:08       ` Robert Lipe
  1997-12-31 16:50         ` Richard Henderson
  0 siblings, 1 reply; 20+ messages in thread
From: Robert Lipe @ 1997-12-31  0:08 UTC (permalink / raw)
  To: egcs, jcardoso

> > It strikes me as odd that in years of GCC support on AT&T-derived
> > ELF assemblers we've never seen this failure before this Fortran case.
> > Is this just some sort of thing that the Fortan front-end does that 
> > gcc/g++ front-ends wouldn't do?
> 
> The RS/6000 had a similar bug a couple years back.  Fortran was trying
> to compute the address of a constant, something which C never did.  I

Coming from the C-shore of the language ocean, that does indeed strike
me as something that just doesn't happen very often, if ever, under C.

I probably should have used "interesting" instead of "odd".  After I 
looked at the problem more, I decided it was just lameness in the native
assembler.   I've filed a problem report with SCO on it.

It's sort of a curse on OpenServer becuase we don't support GAS very
well at all on this target.    When I start thinking about the subset
of OpenServer Fortran users that are building with -fpic, I just can't
get too worked up about making it work right for the COFF case o
additionally.

If there isn't an easy way to make the machine-dependent code not
emit this construct, I suggest we just punt on it.

-- 
Robert Lipe       http://www.dgii.com/people/robertl       robertl@dgii.com

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-31  0:08       ` Robert Lipe
@ 1997-12-31 16:50         ` Richard Henderson
  1997-12-31 20:11           ` Robert Lipe
                             ` (2 more replies)
  0 siblings, 3 replies; 20+ messages in thread
From: Richard Henderson @ 1997-12-31 16:50 UTC (permalink / raw)
  To: Robert Lipe; +Cc: egcs, jcardoso

On Wed, Dec 31, 1997 at 01:05:34AM -0600, Robert Lipe wrote:
> > The RS/6000 had a similar bug a couple years back.  Fortran was trying
> > to compute the address of a constant, something which C never did.

This is exactly what is trying to happen.

> I probably should have used "interesting" instead of "odd".  After I 
> looked at the problem more, I decided it was just lameness in the native
> assembler.   I've filed a problem report with SCO on it.

It is not an SCO assembler bug.  If anything, it is a GAS bug, since
it should have reported an error.  To push the address of a constant
with -fpic, we must use a lea/pushl combination -- just the pushl is
not valid.

I believe the problem to be between LEGITIMATE_PIC_OPERAND_P and the
pushl "i" constraint, and the fact that the i386 backend lies to gcc
about how pic really works.  If the later were fixed (big overhaul),
I'm sure many things would work much better.


r~

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-31 16:50         ` Richard Henderson
@ 1997-12-31 20:11           ` Robert Lipe
  1998-01-01 11:31           ` Dave Love
  1998-01-09  0:57           ` Richard Henderson
  2 siblings, 0 replies; 20+ messages in thread
From: Robert Lipe @ 1997-12-31 20:11 UTC (permalink / raw)
  To: egcs; +Cc: jcardoso

re: pushl immediate with computed offset from GOTOFF(%reg)

> > assembler.   I've filed a problem report with SCO on it.
> 
> It is not an SCO assembler bug.  If anything, it is a GAS bug, since
> it should have reported an error.  To push the address of a constant
> with -fpic, we must use a lea/pushl combination -- just the pushl is
> not valid.

I had wondered about that, but since I'm far from a studly x86 assembler
programmer, I didn't.   I'd just assumed it was a synthetic assembler
operation that didn't trounce %eax as the other approach would have.

> I believe the problem to be between LEGITIMATE_PIC_OPERAND_P and the
> pushl "i" constraint, and the fact that the i386 backend lies to gcc
> about how pic really works.  If the later were fixed (big overhaul),
> I'm sure many things would work much better.

So there are actually two problems here that sort of cancle each other
out, right?   The first is that GCC is emitting something icky and the 
second is that GAS is actually assembling it into something that works.
Cute.

Since both of these are beyond me to fix, I'll back out of this 
conversation now.

Thanx for the help.

-- 
Robert Lipe       http://www.dgii.com/people/robertl       robertl@dgii.com

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-31 16:50         ` Richard Henderson
  1997-12-31 20:11           ` Robert Lipe
@ 1998-01-01 11:31           ` Dave Love
  1998-01-09  0:57           ` Richard Henderson
  2 siblings, 0 replies; 20+ messages in thread
From: Dave Love @ 1998-01-01 11:31 UTC (permalink / raw)
  To: egcs

>>>>> "Richard" == Richard Henderson <rth@cygnus.com> writes:

 Richard> It is not an SCO assembler bug.  If anything, it is a GAS
 Richard> bug, since it should have reported an error.

FWIW this is a longstanding known problem, documented in the G77
manual, and I forwarded an example to egcs-bugs recently.  (It's been
reported several times, so it's not an utterly obscure problem.)

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1997-12-31 16:50         ` Richard Henderson
  1997-12-31 20:11           ` Robert Lipe
  1998-01-01 11:31           ` Dave Love
@ 1998-01-09  0:57           ` Richard Henderson
  1998-01-09  9:22             ` Robert Lipe
                               ` (3 more replies)
  2 siblings, 4 replies; 20+ messages in thread
From: Richard Henderson @ 1998-01-09  0:57 UTC (permalink / raw)
  To: egcs; +Cc: Robert Lipe, jcardoso, scox

On Wed, Dec 31, 1997 at 03:04:45PM -0800, Richard Henderson wrote:
> I believe the problem to be between LEGITIMATE_PIC_OPERAND_P and the
> pushl "i" constraint, and the fact that the i386 backend lies to gcc
> about how pic really works.  If the later were fixed (big overhaul),
> I'm sure many things would work much better.

I still believe that hiding the use of %ebx from the compiler for
constant pool addresses is wrong, but I did not have the patience
to walk through all of the lossage when turning that on.

However, here's a hacky patch that works for the test case

      subroutine foo(a)
      double precision a
      a = dlog10(2.0d0)
      return
      end

I've no idea if a similar change is required elsewhere as well.


r~



Fri Jan  9 00:48:09 1998  Richard Henderson  <rth@cygnus.com>

	* i386.md (push): Delete identical !TARGET_MOVE pattern.  Add
	patterns to prohibit symbolic constants if flag_pic.


Index: i386.md
===================================================================
RCS file: /cvs/cvsfiles/egcs/gcc/config/i386/i386.md,v
retrieving revision 1.4
diff -u -p -d -r1.4 i386.md
--- i386.md	1997/11/05 19:29:37	1.4
+++ i386.md	1998/01/09 08:45:36
@@ -835,7 +835,13 @@
 (define_insn ""
   [(set (match_operand:SI 0 "push_operand" "=<")
 	(match_operand:SI 1 "general_operand" "g"))]
-  "TARGET_PUSH_MEMORY"
+  "TARGET_PUSH_MEMORY && !flag_pic"
+  "push%L0 %1")
+
+(define_insn ""
+  [(set (match_operand:SI 0 "push_operand" "=<")
+	(match_operand:SI 1 "general_operand" "rmn"))]
+  "TARGET_PUSH_MEMORY && flag_pic"
   "push%L0 %1")
 
 ;; If not a 386, it is faster to move MEM to a REG and then push, rather than
@@ -844,13 +850,13 @@
 (define_insn ""
   [(set (match_operand:SI 0 "push_operand" "=<")
 	(match_operand:SI 1 "nonmemory_operand" "ri"))]
-  "!TARGET_PUSH_MEMORY && TARGET_MOVE"
+  "!TARGET_PUSH_MEMORY && !flag_pic"
   "push%L0 %1")
 
 (define_insn ""
   [(set (match_operand:SI 0 "push_operand" "=<")
-	(match_operand:SI 1 "nonmemory_operand" "ri"))]
-  "!TARGET_PUSH_MEMORY && !TARGET_MOVE"
+	(match_operand:SI 1 "nonmemory_operand" "rn"))]
+  "!TARGET_PUSH_MEMORY && flag_pic"
   "push%L0 %1")
 
 ;; General case of fullword move.

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1998-01-09  0:57           ` Richard Henderson
@ 1998-01-09  9:22             ` Robert Lipe
  1998-01-11 13:22               ` Joao Cardoso
  1998-01-09 12:09             ` Robert Lipe
                               ` (2 subsequent siblings)
  3 siblings, 1 reply; 20+ messages in thread
From: Robert Lipe @ 1998-01-09  9:22 UTC (permalink / raw)
  To: Richard Henderson; +Cc: egcs, jcardoso, scox

> However, here's a hacky patch that works for the test case
> 
>       subroutine foo(a)
>       double precision a
>       a = dlog10(2.0d0)
>       return
>       end
> 
> I've no idea if a similar change is required elsewhere as well.

Richard,  your patch does indeed stop the assembler from hurling
on the fortran code that was sent to me that started this thread.
Since that code was meant to be a library fragment and I don't do 
fortran, I have no way of testing that it actually executes correctly 
for that specific case.   I can, however, knock off a make check.


WARNING: apples and oranges test follows.   I patched the 1225 snap
with your fix.   As a reference, I include the output from the 
same command on 1.0.1.    I don't *believe* this will make any 
difference.   I could be wrong, but I thought that havinga baseline
for comparison was important.

make check-g77 RUNTESTFLAGS='--target_board unix{-melf} --tool_opts -fPIC'

First: the 1.0.1 unpatched results:

                === g77 tests ===

Running target unix/-melf
Using /usr/local/bin/../share/dejagnu/baseboards/unix.exp as board description f
ile for target.
Using /usr/local/bin/../share/dejagnu/config/unix.exp as generic interface file
for target.
Using /home/play/egcs-1.0/gcc/testsuite/config/default.exp as tool-and-target-sp
ecific interface file.
Running /home/play/egcs-1.0/gcc/testsuite/g77.f-torture/compile/compile.exp ...
FAIL: g77.f-torture/compile/alpha1.f,  -O1
FAIL: g77.f-torture/compile/alpha1.f,  -O2
FAIL: g77.f-torture/compile/alpha1.f,  -O2 -fomit-frame-pointer -finline-functio
ns
Running /home/play/egcs-1.0/gcc/testsuite/g77.f-torture/execute/execute.exp ...
FAIL: g77.f-torture/execute/cabs.f compilation,  -O0
FAIL: g77.f-torture/execute/cabs.f compilation,  -O1
FAIL: g77.f-torture/execute/cabs.f compilation,  -O2
FAIL: g77.f-torture/execute/cabs.f compilation,  -O2 -fomit-frame-pointer -finli
ne-functions
FAIL: g77.f-torture/execute/claus.f compilation,  -O0
FAIL: g77.f-torture/execute/claus.f compilation,  -O1
FAIL: g77.f-torture/execute/claus.f compilation,  -O2
FAIL: g77.f-torture/execute/claus.f compilation,  -O2 -fomit-frame-pointer -finline-functions
FAIL: g77.f-torture/execute/complex_1.f compilation,  -O0
FAIL: g77.f-torture/execute/complex_1.f compilation,  -O1
FAIL: g77.f-torture/execute/complex_1.f compilation,  -O2
FAIL: g77.f-torture/execute/complex_1.f compilation,  -O2 -fomit-frame-pointer -
finline-functions
FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O0
FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O1
FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O2
FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O2 -fomit-frame-pointer -f
inline-functions
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O0
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O1
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 -fomit-frame-pointer -finl
ine-functions
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 -fomit-frame-pointer -finl
ine-functions -funroll-loops
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 -fomit-frame-pointer -finl
ine-functions -funroll-all-loops
FAIL: g77.f-torture/execute/erfc.f compilation,  -O0
FAIL: g77.f-torture/execute/erfc.f compilation,  -O1
FAIL: g77.f-torture/execute/erfc.f compilation,  -O2
FAIL: g77.f-torture/execute/erfc.f compilation,  -O2 -fomit-frame-pointer -finli
ne-functions
FAIL: g77.f-torture/execute/exp.f compilation,  -O0
FAIL: g77.f-torture/execute/exp.f compilation,  -O1
FAIL: g77.f-torture/execute/exp.f compilation,  -O2
FAIL: g77.f-torture/execute/exp.f compilation,  -O2 -fomit-frame-pointer -finlin
e-functions
FAIL: g77.f-torture/execute/le.f compilation,  -O0
FAIL: g77.f-torture/execute/le.f compilation,  -O1
FAIL: g77.f-torture/execute/short.f compilation,  -O0
FAIL: g77.f-torture/execute/short.f compilation,  -O1
FAIL: g77.f-torture/execute/short.f compilation,  -O2
FAIL: g77.f-torture/execute/short.f compilation,  -O2 -fomit-frame-pointer -finl
ine-functions
FAIL: g77.f-torture/execute/short.f compilation,  -O2 -fomit-frame-pointer -finl
ine-functions -funroll-loops
FAIL: g77.f-torture/execute/short.f compilation,  -O2 -fomit-frame-pointer -finl
ine-functions -funroll-all-loops

                === g77 Summary ===

# of expected passes            53
# of unexpected failures        41
# of untested testcases         38
/home/play/10/gcc/g77 version egcs-2.90.23 980102 (egcs-1.0.1 release)


Now the patched 1225 results:

FAIL: g77.f-torture/execute/cabs.f compilation,  -O0
FAIL: g77.f-torture/execute/claus.f compilation,  -O0
FAIL: g77.f-torture/execute/complex_1.f compilation,  -O0
FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O0
FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O0
FAIL: g77.f-torture/execute/dnrm2.f execution,  -O2 -fomit-frame-pointer -finlin
e-functions -funroll-loops
FAIL: g77.f-torture/execute/dnrm2.f execution,  -O2 -fomit-frame-pointer -finlin
e-functions -funroll-all-loops
FAIL: g77.f-torture/execute/erfc.f compilation,  -O0
FAIL: g77.f-torture/execute/exp.f compilation,  -O0
FAIL: g77.f-torture/execute/le.f compilation,  -O0
FAIL: g77.f-torture/execute/short.f compilation,  -O0

                === g77 Summary ===

# of expected passes            112
# of unexpected failures        11
# of untested testcases         9
/home/play/negcs/gcc/g77 version egcs-2.91.03 971225 (gcc-2.8.0)


And, just as a sanity check to be sure that only the PIC stuff is
involved here:

$  make check-g77 RUNTESTFLAGS='--target_board unix{-melf} '
FAIL: g77.f-torture/execute/dnrm2.f execution,  -O2 -fomit-frame-pointer -finlin
e-functions -funroll-loops
FAIL: g77.f-torture/execute/dnrm2.f execution,  -O2 -fomit-frame-pointer -finlin
e-functions -funroll-all-loops

                === g77 Summary ===

# of expected passes            130
# of unexpected failures        2
/home/play/negcs/gcc/g77 version egcs-2.91.03 971225 (gcc-2.8.0)




dnrm2.f has always failed on this target, so let's throw that one out.

Of the ones that are still failing, they're  all of the form:
	/usr/tmp/cca002Lv.s:87:invalid operand combination: leal


Sure enough, the compiler is emitting things like:
        leal .LC0@GOTOFF(%ebx),-76(%ebp)


Yes, this patch did indeed help things substantially, Richard.  If
you'd like to take a shot at the leal voodoo as well, I can knock off
a build and a test for you.

Thank you for your help.

RJL



> 
> 
> r~
> 
> 
> 
> Fri Jan  9 00:48:09 1998  Richard Henderson  <rth@cygnus.com>
> 
> 	* i386.md (push): Delete identical !TARGET_MOVE pattern.  Add
> 	patterns to prohibit symbolic constants if flag_pic.
> 
> 
> Index: i386.md
> ===================================================================
> RCS file: /cvs/cvsfiles/egcs/gcc/config/i386/i386.md,v
> retrieving revision 1.4
> diff -u -p -d -r1.4 i386.md
> --- i386.md	1997/11/05 19:29:37	1.4
> +++ i386.md	1998/01/09 08:45:36
> @@ -835,7 +835,13 @@
>  (define_insn ""
>    [(set (match_operand:SI 0 "push_operand" "=<")
>  	(match_operand:SI 1 "general_operand" "g"))]
> -  "TARGET_PUSH_MEMORY"
> +  "TARGET_PUSH_MEMORY && !flag_pic"
> +  "push%L0 %1")
> +
> +(define_insn ""
> +  [(set (match_operand:SI 0 "push_operand" "=<")
> +	(match_operand:SI 1 "general_operand" "rmn"))]
> +  "TARGET_PUSH_MEMORY && flag_pic"
>    "push%L0 %1")
>  
>  ;; If not a 386, it is faster to move MEM to a REG and then push, rather than
> @@ -844,13 +850,13 @@
>  (define_insn ""
>    [(set (match_operand:SI 0 "push_operand" "=<")
>  	(match_operand:SI 1 "nonmemory_operand" "ri"))]
> -  "!TARGET_PUSH_MEMORY && TARGET_MOVE"
> +  "!TARGET_PUSH_MEMORY && !flag_pic"
>    "push%L0 %1")
>  
>  (define_insn ""
>    [(set (match_operand:SI 0 "push_operand" "=<")
> -	(match_operand:SI 1 "nonmemory_operand" "ri"))]
> -  "!TARGET_PUSH_MEMORY && !TARGET_MOVE"
> +	(match_operand:SI 1 "nonmemory_operand" "rn"))]
> +  "!TARGET_PUSH_MEMORY && flag_pic"
>    "push%L0 %1")
>  
>  ;; General case of fullword move.
> 
> 

-- 
Robert Lipe       http://www.dgii.com/people/robertl       robertl@dgii.com

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1998-01-09  0:57           ` Richard Henderson
  1998-01-09  9:22             ` Robert Lipe
@ 1998-01-09 12:09             ` Robert Lipe
  1998-01-12 17:55             ` Dave Love
  1998-01-19  2:25             ` whither fix for bogus x86 pushi? Robert Lipe
  3 siblings, 0 replies; 20+ messages in thread
From: Robert Lipe @ 1998-01-09 12:09 UTC (permalink / raw)
  To: Richard Henderson; +Cc: egcs, jcardoso, scox

Richard Henderson wrote:
> On Wed, Dec 31, 1997 at 03:04:45PM -0800, Richard Henderson wrote:
> > I believe the problem to be between LEGITIMATE_PIC_OPERAND_P and the
> > pushl "i" constraint, and the fact that the i386 backend lies to gcc
> > about how pic really works.  If the later were fixed (big overhaul),
> > I'm sure many things would work much better.
> 
> I still believe that hiding the use of %ebx from the compiler for
> constant pool addresses is wrong, but I did not have the patience
> to walk through all of the lossage when turning that on.

That reminds me of something I'd meant to mention in this group.

Since the construct that GCC is emitting isn't even a legal Intel
addressing mode, but GAS was accepting it, I dropped a note to the
gas2 list.   Ian agreed that this was bad and said he'd make the
assembler reject this syntax.

So, just as a "heads-up" to anyone using GAS x86 snapshots before
this is all worked out in egcs or gcc, this stuff may soon start 
failing in a more obvious way.

RJL



^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1998-01-11 13:22               ` Joao Cardoso
@ 1998-01-11 13:22                 ` Robert Lipe
  1998-01-12 10:18                 ` J. Kean Johnston
  1 sibling, 0 replies; 20+ messages in thread
From: Robert Lipe @ 1998-01-11 13:22 UTC (permalink / raw)
  To: Joao Cardoso; +Cc: Richard Henderson, egcs, scox

> All 377 octave fortran files compiled OK, and octave's "make check" only 
> fail on 2 of a total of 1401 tests, so I can assume that probably 
> (almost) all is OK. The two failed tests have nothing to do with

Good.   So Richard's test does indeed fix the "real world" failure,
though some testsuite issues remain.

> Fortran, although they did not fail if compiled with gcc-2.7.2.3/g77-0.5.21.

If you can reduce them to a small, manageable test case that fails
the odds of getting them fixed are much better.

> Good news is that I can now build working shared libraries for octave,
> which I was never been able to do under gcc (with Robert's patches). The

There's a good reason why I'm now hanging out in the EGCS group instead
of doing my own version of GCC these days. :-)

> only catch is that some c++ files only compile with -O or -O0. With more
> aggressive optimization the SCO "as" core dumps with SIGSEGV! The assembler

There are cases where the SCO assembler drops core with higher 
optimization levels.   For some reason, it seems to happen more
often when GCC is emitting 386  or 486 code than when built for
Pentium.   It can still happen.

I've submitted test cases to the appropriate staff at SCO.

It is possible to use the GNU assembler on OpenServer, but it has
pains of its own.   I've detailed this in the past on the egcs list,
so you can find the documentation in the archives.


> PS: Why can't I build egcs-1.0 with --enable-shared?
> I got a "-mcoff not compatible with -fpic" or something similar.

I've never messed with --enabled-shared on this host.   I don't 
think Kean has.   This means you're probably one of the first and
get to take some arrows in the chest.

It's almost certainly an artifact of the way we're multilibbing 
things between one object file format  that supports PIC (ELF) 
and one that doesn't (COFF).


> Start another thread?

Yes, please.



^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1998-01-09  9:22             ` Robert Lipe
@ 1998-01-11 13:22               ` Joao Cardoso
  1998-01-11 13:22                 ` Robert Lipe
  1998-01-12 10:18                 ` J. Kean Johnston
  0 siblings, 2 replies; 20+ messages in thread
From: Joao Cardoso @ 1998-01-11 13:22 UTC (permalink / raw)
  To: Robert Lipe; +Cc: Richard Henderson, egcs, scox

Robert Lipe wrote:
> 
> > However, here's a hacky patch that works for the test case
> >
> >       subroutine foo(a)
> >       double precision a
> >       a = dlog10(2.0d0)
> >       return
> >       end
> >
> > I've no idea if a similar change is required elsewhere as well.
> 
> Richard,  your patch does indeed stop the assembler from hurling
> on the fortran code that was sent to me that started this thread.
> Since that code was meant to be a library fragment and I don't do
> fortran, I have no way of testing that it actually executes correctly
> for that specific case.

Hi,

I might be of some help here:

I have applied the patch (and also sco5.h patch) to egcs-1.0 and rebuild
octave (a Matlab alike) that is the package from where the original fortran
file (that initiated this thread) comes from.

All 377 octave fortran files compiled OK, and octave's "make check" only 
fail on 2 of a total of 1401 tests, so I can assume that probably 
(almost) all is OK. The two failed tests have nothing to do with
Fortran, although they did not fail if compiled with gcc-2.7.2.3/g77-0.5.21.

Good news is that I can now build working shared libraries for octave,
which I was never been able to do under gcc (with Robert's patches). The
only catch is that some c++ files only compile with -O or -O0. With more
aggressive optimization the SCO "as" core dumps with SIGSEGV! The assembler
files are 10000 to 30000 lines long, so I don't post them unless you
ask for it :).

Thanks to you all,
Joao

PS: Why can't I build egcs-1.0 with --enable-shared?
I got a "-mcoff not compatible with -fpic" or something similar.
Start another thread?

-- 
Joao Cardoso, INESC  |  e-mail: jcardoso@inescn.pt
R. Jose Falcao 110   |  tel:    + 351 2 2094345
4050 Porto, Portugal |  fax:    + 351 2 2008487

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1998-01-11 13:22               ` Joao Cardoso
  1998-01-11 13:22                 ` Robert Lipe
@ 1998-01-12 10:18                 ` J. Kean Johnston
  1 sibling, 0 replies; 20+ messages in thread
From: J. Kean Johnston @ 1998-01-12 10:18 UTC (permalink / raw)
  To: Joao Cardoso; +Cc: Robert Lipe, Richard Henderson, egcs, scox

On Sat, Jan 10, 1998 at 07:57:47PM +0000, Joao Cardoso wrote:
> Good news is that I can now build working shared libraries for octave,
> which I was never been able to do under gcc (with Robert's patches). The
This is indeed good news!

> only catch is that some c++ files only compile with -O or -O0. With more
> aggressive optimization the SCO "as" core dumps with SIGSEGV! The assembler
> files are 10000 to 30000 lines long, so I don't post them unless you
> ask for it :).
There is a known problem in the assember which I have escalted here in
the development system group. It was most noticeable if you configured
your egcs with i486-pc-sco* or if you configured it ON a 486 and it picked
that target type up by default. There is a problem in elf with the section
names / certain instructions that causes the assembler to dump core.

A related problem is the linker when you use gcc -s -o foo lots_of_.o.
The linker will dump core too. If you ever encounter this problem,
simply remove the -s from your command line, try again and manually
strip the binary. Both problems are known and being looked at.

Kean.

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: f77 on sco5 fails on GOTOFF references
  1998-01-09  0:57           ` Richard Henderson
  1998-01-09  9:22             ` Robert Lipe
  1998-01-09 12:09             ` Robert Lipe
@ 1998-01-12 17:55             ` Dave Love
  1998-01-19  2:25             ` whither fix for bogus x86 pushi? Robert Lipe
  3 siblings, 0 replies; 20+ messages in thread
From: Dave Love @ 1998-01-12 17:55 UTC (permalink / raw)
  To: egcs

>>>>> "Richard" == Richard Henderson <rth@cygnus.com> writes:

 Richard> However, here's a hacky patch that works for the test case

 Richard>       subroutine foo(a)
 Richard>       double precision a
 Richard>       a = dlog10(2.0d0)
 Richard>       return
 Richard>       end

 Richard> I've no idea if a similar change is required elsewhere as well.

I guess it is.  That patch doesn't fix the case reported most recently
against the gcc-2.7-based g77 which I sent in (`dgage') with `g77
-fPIC' on linux (RH4.2-ish).

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: whither fix for bogus x86 pushi?
  1998-01-09  0:57           ` Richard Henderson
                               ` (2 preceding siblings ...)
  1998-01-12 17:55             ` Dave Love
@ 1998-01-19  2:25             ` Robert Lipe
  1998-01-20  2:21               ` Richard Henderson
  1998-01-20  4:00               ` Richard Henderson
  3 siblings, 2 replies; 20+ messages in thread
From: Robert Lipe @ 1998-01-19  2:25 UTC (permalink / raw)
  To: Richard Henderson; +Cc: egcs, jcardoso, scox

On Jan 9, Richard Henderson asked me to try the following patch.   It
cured a number of testcase failures on the g77/pic and caused no other
testcase failures.

I don't see this in the current EGCS CVS tree.     Is it awaiting further
feedback from one of us, or does it need additional work, or is it just
in the queue to be committed?

Thanx,
RJL

> Fri Jan  9 00:48:09 1998  Richard Henderson  <rth@cygnus.com>
> 
> 	* i386.md (push): Delete identical !TARGET_MOVE pattern.  Add
> 	patterns to prohibit symbolic constants if flag_pic.
> 
> 
> Index: i386.md
> ===================================================================
> RCS file: /cvs/cvsfiles/egcs/gcc/config/i386/i386.md,v
> retrieving revision 1.4
> diff -u -p -d -r1.4 i386.md
> --- i386.md	1997/11/05 19:29:37	1.4
> +++ i386.md	1998/01/09 08:45:36
> @@ -835,7 +835,13 @@
>  (define_insn ""
>    [(set (match_operand:SI 0 "push_operand" "=<")
>  	(match_operand:SI 1 "general_operand" "g"))]
> -  "TARGET_PUSH_MEMORY"
> +  "TARGET_PUSH_MEMORY && !flag_pic"
> +  "push%L0 %1")
> +
> +(define_insn ""
> +  [(set (match_operand:SI 0 "push_operand" "=<")
> +	(match_operand:SI 1 "general_operand" "rmn"))]
> +  "TARGET_PUSH_MEMORY && flag_pic"
>    "push%L0 %1")
>  
>  ;; If not a 386, it is faster to move MEM to a REG and then push, rather than
> @@ -844,13 +850,13 @@
>  (define_insn ""
>    [(set (match_operand:SI 0 "push_operand" "=<")
>  	(match_operand:SI 1 "nonmemory_operand" "ri"))]
> -  "!TARGET_PUSH_MEMORY && TARGET_MOVE"
> +  "!TARGET_PUSH_MEMORY && !flag_pic"
>    "push%L0 %1")
>  
>  (define_insn ""
>    [(set (match_operand:SI 0 "push_operand" "=<")
> -	(match_operand:SI 1 "nonmemory_operand" "ri"))]
> -  "!TARGET_PUSH_MEMORY && !TARGET_MOVE"
> +	(match_operand:SI 1 "nonmemory_operand" "rn"))]
> +  "!TARGET_PUSH_MEMORY && flag_pic"
>    "push%L0 %1")
>  
>  ;; General case of fullword move.
> 
> 

-- 
Robert Lipe       http://www.dgii.com/people/robertl       robertl@dgii.com

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: whither fix for bogus x86 pushi?
  1998-01-20  2:21                 ` Robert Lipe
@ 1998-01-19 23:51                   ` Richard Henderson
  0 siblings, 0 replies; 20+ messages in thread
From: Richard Henderson @ 1998-01-19 23:51 UTC (permalink / raw)
  To: Robert Lipe; +Cc: Richard Henderson, egcs, jcardoso, scox

On Mon, Jan 19, 1998 at 11:02:00PM -0600, Robert Lipe wrote:
> This patch doesn't cure all the ailments of PIC on x86, but it does
> give the Fortran PIC stuff as clean of a bill of health as the stock
> ELF modes. 

Ok, I've comitted my patch, then. 


r~

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: whither fix for bogus x86 pushi?
  1998-01-19  2:25             ` whither fix for bogus x86 pushi? Robert Lipe
@ 1998-01-20  2:21               ` Richard Henderson
  1998-01-20  2:21                 ` Robert Lipe
  1998-01-20  4:00               ` Richard Henderson
  1 sibling, 1 reply; 20+ messages in thread
From: Richard Henderson @ 1998-01-20  2:21 UTC (permalink / raw)
  To: Robert Lipe; +Cc: Richard Henderson, egcs, jcardoso, scox

On Sun, Jan 18, 1998 at 10:55:16PM -0600, Robert Lipe wrote:
> On Jan 9, Richard Henderson asked me to try the following patch.   It
> cured a number of testcase failures on the g77/pic and caused no other
> testcase failures.

Try this replacement that should take care of the other -O0 failures.


r~

^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: whither fix for bogus x86 pushi?
  1998-01-20  2:21               ` Richard Henderson
@ 1998-01-20  2:21                 ` Robert Lipe
  1998-01-19 23:51                   ` Richard Henderson
  0 siblings, 1 reply; 20+ messages in thread
From: Robert Lipe @ 1998-01-20  2:21 UTC (permalink / raw)
  To: Richard Henderson; +Cc: egcs, jcardoso, scox

> Try this replacement that should take care of the other -O0 failures.

Richard, I applied your patch, rebuilt, and reran my test suite from 
yesterday.   [ Hey, with a little practice, this *can* be done in under
two minutes of human time.  Yeah, it still takes five hours of machine 
time... ] 

This patch doesn't cure all the ailments of PIC on x86, but it does
give the Fortran PIC stuff as clean of a bill of health as the stock
ELF modes. 

Oh.   The 940909 failures are fixed by an unrelated patch I submitted
yesterday.

Good job, Richard.

Thanx!

RJL


--- multi-980118/summary
+++ multi-980119/summary
@@ -4,19 +4,9 @@
 
 Running target unix/-mcoff
 FAIL: gcc.c-torture/execute/scope-1.c compilation,  -O2 -g 
-FAIL: gcc.failure/940409-1.c,  -O0  
-FAIL: gcc.failure/940409-1.c,  -O1  
-FAIL: gcc.failure/940409-1.c,  -O2  
-FAIL: gcc.failure/940409-1.c,  -O2 -fomit-frame-pointer -finline-functions  
-FAIL: gcc.failure/940409-1.c,  -O2 -g  
 
 
 Running target unix/-melf
-FAIL: gcc.failure/940409-1.c,  -O0  
-FAIL: gcc.failure/940409-1.c,  -O1  
-FAIL: gcc.failure/940409-1.c,  -O2  
-FAIL: gcc.failure/940409-1.c,  -O2 -fomit-frame-pointer -finline-functions  
-FAIL: gcc.failure/940409-1.c,  -O2 -g  
 
 
 Running target unix/-fPIC
@@ -35,11 +25,6 @@
 FAIL: gcc.c-torture/execute/nestfunc-1.c execution,  -O2 
 FAIL: gcc.c-torture/execute/nestfunc-1.c execution,  -O2 -fomit-frame-pointer -finline-functions 
 FAIL: gcc.c-torture/execute/nestfunc-1.c execution,  -O2 -g 
-FAIL: gcc.failure/940409-1.c,  -O0  
-FAIL: gcc.failure/940409-1.c,  -O1  
-FAIL: gcc.failure/940409-1.c,  -O2  
-FAIL: gcc.failure/940409-1.c,  -O2 -fomit-frame-pointer -finline-functions  
-FAIL: gcc.failure/940409-1.c,  -O2 -g  
 FAIL: gcc.misc-tests/gcov-1.c execution test
 FAIL: gcov-1.c:1:is 4:should be 11
 FAIL: gcov-1.c:1:is 5:should be 10
@@ -177,49 +162,8 @@
 
 
 Running target unix/-fPIC
-FAIL: g77.f-torture/compile/alpha1.f,  -O1  
-FAIL: g77.f-torture/compile/alpha1.f,  -O2  
-FAIL: g77.f-torture/compile/alpha1.f,  -O2 -fomit-frame-pointer -finline-functions  
-FAIL: g77.f-torture/execute/cabs.f compilation,  -O0 
-FAIL: g77.f-torture/execute/cabs.f compilation,  -O1 
-FAIL: g77.f-torture/execute/cabs.f compilation,  -O2 
-FAIL: g77.f-torture/execute/cabs.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/claus.f compilation,  -O0 
-FAIL: g77.f-torture/execute/claus.f compilation,  -O1 
-FAIL: g77.f-torture/execute/claus.f compilation,  -O2 
-FAIL: g77.f-torture/execute/claus.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/claus.f compilation,  -O2 -fomit-frame-pointer -finline-functions -funroll-loops 
-FAIL: g77.f-torture/execute/claus.f compilation,  -O2 -fomit-frame-pointer -finline-functions -funroll-all-loops 
-FAIL: g77.f-torture/execute/complex_1.f compilation,  -O0 
-FAIL: g77.f-torture/execute/complex_1.f compilation,  -O1 
-FAIL: g77.f-torture/execute/complex_1.f compilation,  -O2 
-FAIL: g77.f-torture/execute/complex_1.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O0 
-FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O1 
-FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O2 
-FAIL: g77.f-torture/execute/dcomplex.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O0 
-FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O1 
-FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 
-FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 -fomit-frame-pointer -finline-functions -funroll-loops 
-FAIL: g77.f-torture/execute/dnrm2.f compilation,  -O2 -fomit-frame-pointer -finline-functions -funroll-all-loops 
-FAIL: g77.f-torture/execute/erfc.f compilation,  -O0 
-FAIL: g77.f-torture/execute/erfc.f compilation,  -O1 
-FAIL: g77.f-torture/execute/erfc.f compilation,  -O2 
-FAIL: g77.f-torture/execute/erfc.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/exp.f compilation,  -O0 
-FAIL: g77.f-torture/execute/exp.f compilation,  -O1 
-FAIL: g77.f-torture/execute/exp.f compilation,  -O2 
-FAIL: g77.f-torture/execute/exp.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/le.f compilation,  -O0 
-FAIL: g77.f-torture/execute/le.f compilation,  -O1 
-FAIL: g77.f-torture/execute/short.f compilation,  -O0 
-FAIL: g77.f-torture/execute/short.f compilation,  -O1 
-FAIL: g77.f-torture/execute/short.f compilation,  -O2 
-FAIL: g77.f-torture/execute/short.f compilation,  -O2 -fomit-frame-pointer -finline-functions 
-FAIL: g77.f-torture/execute/short.f compilation,  -O2 -fomit-frame-pointer -finline-functions -funroll-loops 
-FAIL: g77.f-torture/execute/short.f compilation,  -O2 -fomit-frame-pointer -finline-functions -funroll-all-loops 
+FAIL: g77.f-torture/execute/dnrm2.f execution,  -O2 -fomit-frame-pointer -finline-functions -funroll-loops 
+FAIL: g77.f-torture/execute/dnrm2.f execution,  -O2 -fomit-frame-pointer -finline-functions -funroll-all-loops 
 
 
 



^ permalink raw reply	[flat|nested] 20+ messages in thread

* Re: whither fix for bogus x86 pushi?
  1998-01-19  2:25             ` whither fix for bogus x86 pushi? Robert Lipe
  1998-01-20  2:21               ` Richard Henderson
@ 1998-01-20  4:00               ` Richard Henderson
  1 sibling, 0 replies; 20+ messages in thread
From: Richard Henderson @ 1998-01-20  4:00 UTC (permalink / raw)
  To: Robert Lipe; +Cc: Richard Henderson, egcs, jcardoso, scox

On Sun, Jan 18, 1998 at 10:55:16PM -0600, Robert Lipe wrote:
> I don't see this in the current EGCS CVS tree.     Is it awaiting further
> feedback from one of us, or does it need additional work, or is it just
> in the queue to be committed?

I need to find the similar -O0 failures on movl.


r~

^ permalink raw reply	[flat|nested] 20+ messages in thread

end of thread, other threads:[~1998-01-20  4:00 UTC | newest]

Thread overview: 20+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1997-12-29 22:49 f77 on sco5 fails on GOTOFF references Robert Lipe
1997-12-30  1:29 ` Richard Henderson
1997-12-30  8:53   ` Robert Lipe
1997-12-30 17:43     ` John Carr
1997-12-31  0:08       ` Robert Lipe
1997-12-31 16:50         ` Richard Henderson
1997-12-31 20:11           ` Robert Lipe
1998-01-01 11:31           ` Dave Love
1998-01-09  0:57           ` Richard Henderson
1998-01-09  9:22             ` Robert Lipe
1998-01-11 13:22               ` Joao Cardoso
1998-01-11 13:22                 ` Robert Lipe
1998-01-12 10:18                 ` J. Kean Johnston
1998-01-09 12:09             ` Robert Lipe
1998-01-12 17:55             ` Dave Love
1998-01-19  2:25             ` whither fix for bogus x86 pushi? Robert Lipe
1998-01-20  2:21               ` Richard Henderson
1998-01-20  2:21                 ` Robert Lipe
1998-01-19 23:51                   ` Richard Henderson
1998-01-20  4:00               ` Richard Henderson

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).