LAPACK - dgesvx.f


[ Follow Ups ] [ Post Followup ] [ Netlib Discussion Forum ] [ FAQ ]

Posted by Kendall Atkinson on November 21, 1997 at 00:07:44:

Below is a test program for dgesvx.f, and it works
fine on my HP workstation (compiled under their f90 compiler).
However, my colleague in Korea is having a great deal of difficulty
running it on his SUN workstation. It returns the following
message.

=========== Error message ========================

** On entry to DGESVX parameter number 16 had an illegal value
Note: the following IEEE floating-point arithmetic exceptions
occurred and were never cleared; see ieee_flags(3M):
Inexact; Underflow;
Sun's implementation of IEEE arithmetic is discussed in
the Numerical Computation Guide.

Also, whatever 'N' I give, the routine returns 'N=3'.

====== End of error message =========================

We have the routine dgesvx.f as a standalone package that
includes all of the various routines it needs. This works
fine on my HP system, but evidently not on my Korean
colleagues machine. There is no compilation error. As an
alternative, is there something stupid in the test program
that is excused by the HP compiler, but not by the SUN compiler?

In advance, thanks for any help you can give. Also, this
is hopefully not a completely stupid question with a trivial
answer.

Ken Atkinson

====== A simple-minded test program =================
C TITLE: THIS IS A DEMO PROGRAM FOR SUBROUTINE DGESVX FROM LAPACK
C
C IT WILL SOLVE A LINEAR SYSTEM A*X=B, GIVEN BY THE USER.
C
IMPLICIT DOUBLE PRECISION (A-H,O-Z)
INTEGER ORDER, FORDER
CHARACTER*1 EQUED, FACT, TRANS
INTEGER INFO, LDA, LDAF, LBD, LDX, N
PARAMETER (ORDER=64, FORDER=4*ORDER, NRHS=1)
DIMENSION A(ORDER,ORDER), AF(ORDER,ORDER), B(ORDER), X(ORDER),
* BERR(NRHS), C(ORDER), FERR(NRHS), R(ORDER), WORK(FORDER),
* IWORK(ORDER), T(ORDER)
C
C INPUT ORDER OF LINEAR SYSTEM.
LDA = ORDER
LDAF = ORDER
LBD = ORDER
LDX = ORDER
FACT = 'N'
TRANS = 'N'
10 WRITE(*,*) ' GIVE THE ORDER OF THE LINEAR SYSTEM.'
WRITE(*,*) 'IT SHOULD BE <= ',ORDER
READ(*,*) N
IF(N .EQ. 0) STOP
C
C CREATE THE LINEAR SYSTEM.
H=1.0D0/N
DO 15 I=1,N
15 T(I) = (I-0.5D0)*H
DO 30 I=1,N
DO 20 J=1,N
20 A(I,J) = -H*COS(T(I)*T(J))
30 A(I,I) = A(I,I) + 4.0D0
DO 50 I=1,N
SUM = 0.0D0
DO 40 J=1,N
40 SUM = SUM + A(I,J)
50 B(I) = SUM
C
C SOLVE THE LINEAR SYSTEM.
CALL DGESVX(FACT,TRANS,N,NRHS,A,LDA,AF,LDAF,IPIV,EQUED,R,C,
* B,LBD,X,LDX,RCOND,FERR,BERR,WORK,IWORK,INFO)
IF(RCOND .EQ. 0.0D0) THEN
PRINT *, 'THE MATRIX IS SINGULAR'
STOP
ELSE
PRINT 1002, RCOND
END IF
1002 FORMAT(' CONDITION NUMBER = ',1PE8.2,/)
C
C PRINT THE RESULTS.
WRITE(*,1000) N
1000 FORMAT(///,' N=',I3,//,' I SOLUTION',/)
WRITE(*,1001) (I,X(I), I=1,N)
1001 FORMAT(I4,1PE20.10)
GO TO 10
END

====== End of test program =========================





Follow Ups: