Internal Compiler Error with -fastsse on Pentium 3

The following code compiles fine with -fast but not with -fastsse on a Pentium 3 machine.

$ cat spill2.f90
MODULE SPILL
  IMPLICIT NONE

  INTEGER, PARAMETER :: N = 14

  REAL, SAVE :: A(5*13,N), S(10,N), FRF(N)
  REAL, SAVE :: C(0:200)

CONTAINS

  SUBROUTINE T(K1, K2, CLH, FAC, F, S1, S2, TG, LT)
    INTEGER, INTENT(IN) :: K1, K2
    INTEGER, INTENT(IN) :: LT
    REAL, DIMENSION(:,:), INTENT(INOUT) :: TG
    REAL, DIMENSION(:), INTENT(IN) :: CLH, FAC, F, S1, S2

    INTEGER, PARAMETER :: N1 = 8

    REAL, DIMENSION(K1:K2) :: F0, F1, F2, F3
    INTEGER :: J, IFP, I, IND0, IND1, INDS

    DO J = 1, LT
       F3(J) = FAC(J) * C(IFP)
       DO I = 1, N
          TG(N1+I,J) = CLH(J) * (F0(J) * A(IND0,I) +  &
               F2(J) * A(IND0+1,I) + F1(J) * A(IND1,I) +  &
               F3(J) * A(IND1+1,I) + S1(J) * (S(INDS,I) + S2(J) *  &
               (S(INDS+1,I) - S(INDS,I))) + F(J) * FRF(I))
       END DO
    END DO
  END SUBROUTINE T
END MODULE SPILL



$ pgf95 -c -fastsse spill2.f90
PGF90-W-0000-Internal compiler error. xr_getreg: no reg to spill       9 (spill2.f90: 22)
PGF90-W-0000-Internal compiler error. xmm_to_mem       0 (spill2.f90: 22)
  0 inform,   2 warnings,   0 severes, 0 fatal for t
/tmp/pgf95o2xfQbMFPeZ4.s: Assembler messages:
/tmp/pgf95o2xfQbMFPeZ4.s:266: Error: bad register name `%xmm8'
/tmp/pgf95o2xfQbMFPeZ4.s:267: Error: bad register name `%xmm8'
/tmp/pgf95o2xfQbMFPeZ4.s:271: Error: bad register name `%xmm8'
/tmp/pgf95o2xfQbMFPeZ4.s:278: Error: bad register name `%xmm8'



$ pgf95 -V

pgf95 7.1-6 32-bit target on x86 Linux -tp piii
Copyright 1989-2000, The Portland Group, Inc.  All Rights Reserved.
Copyright 2000-2007, STMicroelectronics, Inc.  All Rights Reserved.

Is this fixed in the current release, or is there a workaround, or is the fastsse flag just not a good idea on a Pentium 3?

Hi rusteve,

Only “-fast” is valid for a Pentium III since “-fastsse” is for a processor that supports SSE and SSE2.

  • Mat