egcs-19981019 testing on i686-pc-cygwin32: g77 ICE at -Os

tprince@cat.e-mail.com tprince@cat.e-mail.com
Tue Oct 20 15:44:00 GMT 1998


Installation exhibits the redundant rebuild of libf2c, using 'make
-k install' because of the attempt to install incorrectly configured
texinfo and chill.

build flags, as usual:
BOOT_CFLAGS='Os -march=pentiumpro -malign-double'

attempts to compile using g77 -Os  produce:

 internal error--unrecognizable insn:
(insn:QI 2908 2905 962 (set (reg:DF 8 %st(0))
             (mem/s:DF (plus:SI (plus:SI (mult:SI (mem:SI (plus:SI
(reg:SI 6 %epb)
                                                      (const_int -5332)) 0)
                                            (const_int 8))
                                     (reg:SI 4 %esi))
                             (const_int -16)) 0)) -1 (insn_list 948 (nil))
        (nil))

Error does not occur at optimization -O.  The same code ran as
usual on irix6.4 at -O2.  Source code:



Dr. Timothy C. Prince
Consulting Engineer
Solar Turbines, a Caterpillar Company
alternate e-mail: tprince@computer.org
C
C***********************************************
      subroutine verify(iou)
C***********************************************************************
C                                                                      *
C      VERIFY     auxiliary test routine to check-out function SECND  *
C                 and to verify that sufficiently long Loop sizes are  *
C                 defined in Subr. SIZES for accurate CPU timing.      *
C                                                                      *
C       iou    -  Logical Output Device Number                         *
C                                                                      *
C***********************************************************************
      implicitdoubleprecision (a-h,o-z)
CIBM  IMPLICIT  REAL*8           (A-H,O-Z)
C
CLOX  REAL*8 SECND
C
C/C/      PARAMETER( l1=   1001, l2=   101, l1d= 2*1001 )
C/C/      PARAMETER( l13= 64, l13h= 64/2, l213= 64+32, l813= 8*64 )
C/C/      PARAMETER( l14= 2048, l16= 75, l416= 4*75 , l21= 25)
C/C/      PARAMETER( kn= 47, kn2= 95, np= 3, ls= 3*47, krs= 24)
C
      parameter(ntmp= 100)
C
      common/space1/u(1001),v(1001),w(1001),x(1001),y(1001),z(1001),g(10
     &01),du1(101),du2(101),du3(101),grd(1001),dex(1001),xi(1001),ex(100
     &1),ex1(1001),dex1(1001),vx(1001),xx(1001),rx(1001),rh(2048),vsp(10
     &1),vstp(101),vxne(101),vxnd(101),ve3(101),vlr(101),vlin(101),b5(10
     &1),plan(300),d(300),sa(101),sb(101)
C
      common/space2/p(4,512),px(25,101),cx(25,101),vy(101,25),vh(101,7),
     &vf(101,7),vg(101,7),vs(101,7),za(101,7),zp(101,7),zq(101,7),zr(101
     &,7),zm(101,7),zb(101,7),zu(101,7),zv(101,7),zz(101,7),b(64,64),c(6
     &4,64),h(64,64),u1(5,101,2),u2(5,101,2),u3(5,101,2)
C
      common/alpha/mk,ik,im,ml,il,mruns,nruns,jr,iovec,npfs(8,3,47)
      common/tau/tclock,tsecov,testov,cumtim(4)
C
      common/beta/tic,times(8,3,47),see(5,3,8,3),terrs(8,3,47),csums(8,3
     &,47),fopn(8,3,47),dos(8,3,47)
C
      common/spaces/ion,j5,k2,k3,loop1,laps,loop,m,kr,lp,n13h,ibuf,nx,l,
     &npass,nfail,n,n1,n2,n13,n213,n813,n14,n16,n416,n21,nt1,nt2,last,id
     &ebug,mpy,loop2,mucho,mpylim,intbuf(16)
C
      common/spacei/wtp(3),mul(3),ispan(47,3),ipass(47,3)
C
C
      dimensiontim(ntmp),tum(ntmp),tav(ntmp),ter(ntmp)
      dimensiontmx(ntmp),sig(ntmp),len(ntmp)
      savemulti
C
C
C     CALL TRACE ('VERIFY  ')
C
      do k= 1,101
          x(k)= 0.0d0
          y(k)= 0.0d0
          cx(1,k)= 0.0d0
        enddo
      nzd= 0
C
C***********************************************************************
C     Measure tsecov:  Overhead time for calling SECND
C***********************************************************************
C
      tsecov= secovt(iou)
      tic= tsecov
C
C***********************************************************************
C     Measure time resolution of cpu-timer;  tclock= MIN t
C***********************************************************************
C
      fuzz= 1.00d-12
      nticks= min(int(1.00d2/(tsecov+fuzz)),10000)
      dt= 0.00d0
      cumtim(1)= 0.0d0
      t1= secnd(cumtim(1))
      m= 0
C
      do k= 1,nticks
          cumtim(1)= 0.0d0
          t2= secnd(cumtim(1))
          if(t2.ne.t1)then
              m= m+1
              dt= dt+(t2-t1)
              t1= t2
              if(m >= 200)then
                exit
                endif
            endif
        enddo
      if(m >  2.and.dt >  0.00d0)then
        tclock= dt/(real (m)+fuzz)
        else
            tclock= 1.00d0
            write(*,1850)
            write(iou,1850)
        endif
      write(*,1860)m,tclock
      write(iou,1860)m,tclock
C
C***********************************************************************
C                               *****
C         VERIFY ADEQUATE Loop SIZE VERSUS CPU CLOCK ACCURACY
C***********************************************************************
C                               *****
C
C         VERIFY produced the following output on CRAY-XMP4 in a
C         fully loaded, multi-processing, multi-programming system:
C
C
C         VERIFY ADEQUATE Loop SIZE VERSUS CPU CLOCK ACCURACY
C         -----     -------     -------    -------   --------
C         EXTRA     MAXIMUM     DIGITAL    DYNAMIC   RELATIVE
C         Loop      CPUTIME     CLOCK      CLOCK     TIMING
C         SIZE      SECONDS     ERROR      ERROR     ERROR
C         -----     -------     -------    -------   --------
C             1  5.0000e-06      10.00%     17.63%     14.26%
C             2  7.0000e-06       7.14%      6.93%      4.79%
C             4  1.6000e-05       3.12%      6.56%      7.59%
C             8  2.8000e-05       1.79%      2.90%      2.35%
C            16  6.1000e-05       0.82%      6.72%      4.50%
C            32  1.1700e-04       0.43%      4.21%      4.62%
C            64  2.2700e-04       0.22%      3.13%      2.41%
C           128  4.4900e-04       0.11%      3.14%      0.96%
C           256  8.8900e-04       0.06%      2.06%      2.50%
C           512  1.7740e-03       0.03%      1.92%      1.59%
C          1024  3.4780e-03       0.01%      0.70%      1.63%
C          1360              Current Run:    Loop1=   10.000
C          2048  7.0050e-03       0.01%      0.74%      1.28%
C          4096  1.3823e-02       0.00%      1.35%      0.78%
C         -----     -------     -------    -------   --------
C
C          Approximate Serial Job Time=   2.5e+01 Sec.    ( Nruns= 7 RUN
C                               S)
C
C***********************************************************************
C                               *****
C
      write(iou,1870)
      write(iou,1910)
      write(iou,1880)
      write(iou,1890)
      write(iou,1900)
      write(iou,1910)
C
C
C***********************************************************************
C                               *****
C     Measure Cpu Clock Timing Errors As A Function Of Loop Size(lo)
C***********************************************************************
C                               *****
C
      ttest= 100.00d0*tclock
      ilimit= 30
      nj= 5
      lo= 128
      do i= 1,max(8,ntmp)
C
          lo= lo+lo
          do j= 1,nj
              n= 100
              cumtim(1)= 0.0d0
              t0= secnd(cumtim(1))
C                                    Time Kernel 12
              do m= 1,lo
                do k= 1,n
                  x(k)= x(k+1)-x(k)
                  enddo
                enddo
              cumtim(1)= 0.0d0
              tim(j)= secnd(cumtim(1))-t0-tsecov
            enddo
          call stats(tum,tim,nj)
          rterr= 100.0*(tum(2)/(tum(1)+fuzz))
          if(tum(1) <= 0.00d0)then
            rterr= 100.00d0
            endif
          call tdigit(sig(i),nzd,tum(4))
C
          tav(i)= tum(1)
          tmx(i)= tum(4)
          ter(i)= rterr
          len(i)= lo
          if(i >  ilimit.and.tum(1) <  fuzz)then
            write(*,1920)lo,tum(1)
            endif
          if(i >  8.and.tum(1) >= ttest)then
            exit
            endif
        enddo
      nn= i
C
C***********************************************************************
C                               *****
C     Compute Multiple-Pass Loop Counters Loop1 and Loop2
C     Such that:  each Kernel is run at least 100 ticks of Cpu-timer.
C***********************************************************************
C                               *****
C
      i2= 2
      loop1= 1
      mucho= 1
      call sizes(12)
      loop12= ipass(12,2)*mul(2)
C
C
      loop1= int((real (lo)/(real (loop12)+fuzz))*(ttest/(tum(1)+fuzz)))
      mucho= loop1
C
C     When Loop1= 100 each kernel is executed over a million times
C     and the time used to re-intialize overstored input variables
C     is negligible.  Thus each kernel may be run arbitrarily many times
C     (Loop1*Loop2 >> 100) without overflow and produce verifiable check
C                               sums.
C
C     Each kernel's results are automatically checksummed for  Loop1 :=
C
C     Loop1*Loop2=   1   clock resolution << 0.01 SEC,  or Cpu << 1 Mflo
C                               ps
C     Loop1*Loop2=  10   clock resolution << 0.01 SEC,  or Cpu <  2 Mflo
C                               ps
C     Loop1*Loop2=  50   clock resolution <= 0.01 SEC,  or Cpu <  2 Mflo
C                               ps
C     Loop1*Loop2= 100   clock resolution <= 0.01 SEC,  or Cpu <  5 Mflo
C                               ps
C     Loop1*Loop2= 200   clock resolution <= 0.01 SEC,  or Cpu < 10 Mflo
C                               ps
C
      mpy= 1
      loop2= 1
      mpylim= loop2
      if(loop1 >  100)then
          loop2= (loop1+50)/100
          mpylim= loop2
        endif
      loop1= 100
C
C     IF TIMING ERRORS ARE TOO LARGE, THEN INCREASE:  MULTI (hence run-t
C                               ime):
C
      multi= 1
C
      if(multi >  1)then
        loop2= multi*loop2
        endif
      mucho= loop1
      mpylim= loop2
      loops0= loop12*loop1*loop2
      repete= real (loop1*loop2)
      if(loop == 1)then
        repete= 1.00d0/(real (loop12)+fuzz)
        endif
      m= 0
      tnn= (tav(nn)+2.00d0*tav(nn-1))*0.500d0
      fuzz= 1.0d-12
      if(tnn <  fuzz)then
        tnn= fuzz
        endif
      do i= 1,nn
          rterr= ter(i)
          lo= len(i)
C                                    Compute Relative Clock Error
C
          rt= 0.0d0
          if(len(i) >= 0)then
            rt= len(nn)/len(i)
            endif
          rperr= 100.00d0
          if(tnn >  fuzz)then
            rperr= 100.00d0*(abs(tnn-rt*tav(i))/tnn)
            endif
          write(iou,1930)lo,tmx(i),sig(i),rterr,rperr
C
C                                    Find loops0 Size Used
C
          if(loops0 >= lo.and.loops0 <= 2*lo)then
              m= lo
              write(iou,1940)loops0,loop1
              write(iou,1950)loops0,loop2
              write(iou,1960)loops0,repete
              write(*,1940)loops0,loop1
              write(*,1950)loops0,loop2
              write(*,1960)loops0,repete
              if(rterr >  10.00d0)then
                  write(iou,1970)
                  write(iou,1980)
                  write(*,1970)
                  write(*,1980)
                endif
            endif
        enddo
      if(m <= 0)then
          write(iou,1960)loops0,repete
          write(*,1960)loops0,repete
        endif
      write(iou,1910)
      write(iou,1990)
      write(iou,2000)
      write(iou,2010)
      write(iou,2020)
      write(iou,2030)
      write(iou,2040)
      write(iou,2050)
      write(iou,2040)
      write(*,1990)
      write(*,2000)
      write(*,2010)
      write(*,2020)
      write(*,2030)
      write(*,2040)
      write(*,2050)
      write(*,2040)
C
      task= 10.00d0
      passes= real (lo)*(task/(tnn+fuzz))
      loiter= int(passes)
      flops= 0.00d0
      cumtim(1)= 0.0d0
      t1= secnd(cumtim(1))
      t2= 0.00d0
C
      do j= 1,4
          n= 100
          t0= t1
C                                    Time Kernel 12
          do m= 1,loiter
            do k= 1,n
              x(k)= x(k+1)-x(k)
              enddo
            enddo
          cumtim(1)= 0.0d0
          t1= secnd(cumtim(1))
          td= t1-t0-tsecov
          t2= t2+td
          flops= flops+passes*real (n)
          ratemf= (1.00d-6*flops)/(t2+fuzz)
          write(*,2060)j,t2,td,ratemf,flops
          write(iou,2060)j,t2,td,ratemf,flops
        enddo
      write(iou,2040)
      write(iou,2070)
      write(*,2040)
      write(*,2070)
      return
1850    format(1x,'WARNING(VERIFY): POOR Cpu-timer resolution; REPLACE?'
     &)
1860    format('VERIFY:',i10,e12.4,' =  Time Resolution of Cpu-timer')
1870    format(/,8x,'VERIFY ADEQUATE Loop SIZE VERSUS CPU CLOCK ACCURACY
     &')
1880    format(8x,'EXTRA     MAXIMUM     DIGITAL    DYNAMIC   RELATIVE')
1890    format(8x,'Loop      CPUTIME     CLOCK      CLOCK     TIMING  ')
1900    format(8x,'SIZE      SECONDS     ERROR      ERROR     ERROR   ')
1910    format(8x,'-----     -------     -------    -------   --------')
1920    format('VERIFY:',i12,' Repetitions.  Bad Timer=',e14.5,' sec.')
1930    format(6x,i7,e12.4,f11.2,'%',f10.2,'%',f10.2,'%')
1940    format(7x,i6,7x,'                           Loop1 = ',i8)
1950    format(7x,i6,7x,'                           Loop2 = ',i8)
1960    format(7x,i6,7x,'Repetition Count = Loop1 * Loop2 = ',f12.3)
1970    format(34x,'VERIFY: POOR TIMING OR ERROR. NEED LONGER RUN ')
1980    format(34x,'INCREASE loop limit:  MULTI  in Subroutine VERIFY')
C
C***********************************************************************
C                               *****
C     Clock Calibration Test of Internal Cpu-timer SECND;
C           Verify 10 Internal SECND Intervals using External Stopwatch
C***********************************************************************
C                               *****
C
C
1990    format(//,' CLOCK CALIBRATION TEST OF INTERNAL CPU-TIMER: SECND'
     &)
2000    format(' MONOPROCESS THIS TEST, STANDALONE, NO TIMESHARING.')
2010    format(' VERIFY TIMED INTERVALS SHOWN BELOW USING EXTERNAL CLOCK
     &')
2020    format(' START YOUR STOPWATCH NOW !')
2030    format(/,'           Verify  T or DT  observe external clock:',/
     &)
2040    format('           -------     -------      ------      -----')
2050    format('           Total T ?   Delta T ?    Mflops ?    Flops')
2060    format(4x,i2,3f12.2,2e15.5)
2070    format(' END CALIBRATION TEST.',/)
      end
C

           To:                                              INTERNET - IBMMAIL



More information about the Gcc-bugs mailing list