mirror of
https://github.com/gonum/gonum.git
synced 2025-10-23 23:23:15 +08:00
Adddsterf and tests
This commit is contained in:
20
internal/testdata/dsterftest/Makefile
vendored
Normal file
20
internal/testdata/dsterftest/Makefile
vendored
Normal file
@@ -0,0 +1,20 @@
|
||||
FC = gfortran
|
||||
FFLAGS = -O2
|
||||
|
||||
targets = testdsterf
|
||||
objects = disnan.o dlamch.o dlanst.o dlaisnan.o dlassq.o dlapy2.o lsame.o dlae2.o dlascl.o dlasrt.o dsterf.o xerbla.o
|
||||
|
||||
default : $(targets)
|
||||
.PHONY : default
|
||||
|
||||
testdsterf : testdsterf.o $(objects)
|
||||
|
||||
% : %.o
|
||||
$(FC) $(FFLAGS) $^ -o $@
|
||||
|
||||
%.o : %.f90
|
||||
$(FC) $(FFLAGS) -c -o $@ $<
|
||||
|
||||
clean :
|
||||
rm -f *.o $(targets) *.txt
|
||||
.PHONY : clean
|
80
internal/testdata/dsterftest/disnan.f
vendored
Normal file
80
internal/testdata/dsterftest/disnan.f
vendored
Normal file
@@ -0,0 +1,80 @@
|
||||
*> \brief \b DISNAN tests input for NaN.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DISNAN + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/disnan.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/disnan.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/disnan.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* LOGICAL FUNCTION DISNAN( DIN )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* DOUBLE PRECISION DIN
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DISNAN returns .TRUE. if its argument is NaN, and .FALSE.
|
||||
*> otherwise. To be replaced by the Fortran 2003 intrinsic in the
|
||||
*> future.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] DIN
|
||||
*> \verbatim
|
||||
*> DIN is DOUBLE PRECISION
|
||||
*> Input to test for NaN.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
LOGICAL FUNCTION DISNAN( DIN )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
DOUBLE PRECISION DIN
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. External Functions ..
|
||||
LOGICAL DLAISNAN
|
||||
EXTERNAL DLAISNAN
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
DISNAN = DLAISNAN(DIN,DIN)
|
||||
RETURN
|
||||
END
|
185
internal/testdata/dsterftest/dlae2.f
vendored
Normal file
185
internal/testdata/dsterftest/dlae2.f
vendored
Normal file
@@ -0,0 +1,185 @@
|
||||
*> \brief \b DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLAE2 + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlae2.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlae2.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlae2.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* SUBROUTINE DLAE2( A, B, C, RT1, RT2 )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* DOUBLE PRECISION A, B, C, RT1, RT2
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLAE2 computes the eigenvalues of a 2-by-2 symmetric matrix
|
||||
*> [ A B ]
|
||||
*> [ B C ].
|
||||
*> On return, RT1 is the eigenvalue of larger absolute value, and RT2
|
||||
*> is the eigenvalue of smaller absolute value.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] A
|
||||
*> \verbatim
|
||||
*> A is DOUBLE PRECISION
|
||||
*> The (1,1) element of the 2-by-2 matrix.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] B
|
||||
*> \verbatim
|
||||
*> B is DOUBLE PRECISION
|
||||
*> The (1,2) and (2,1) elements of the 2-by-2 matrix.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] C
|
||||
*> \verbatim
|
||||
*> C is DOUBLE PRECISION
|
||||
*> The (2,2) element of the 2-by-2 matrix.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[out] RT1
|
||||
*> \verbatim
|
||||
*> RT1 is DOUBLE PRECISION
|
||||
*> The eigenvalue of larger absolute value.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[out] RT2
|
||||
*> \verbatim
|
||||
*> RT2 is DOUBLE PRECISION
|
||||
*> The eigenvalue of smaller absolute value.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
*> \par Further Details:
|
||||
* =====================
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> RT1 is accurate to a few ulps barring over/underflow.
|
||||
*>
|
||||
*> RT2 may be inaccurate if there is massive cancellation in the
|
||||
*> determinant A*C-B*B; higher precision or correctly rounded or
|
||||
*> correctly truncated arithmetic would be needed to compute RT2
|
||||
*> accurately in all cases.
|
||||
*>
|
||||
*> Overflow is possible only if RT1 is within a factor of 5 of overflow.
|
||||
*> Underflow is harmless if the input data is 0 or exceeds
|
||||
*> underflow_threshold / macheps.
|
||||
*> \endverbatim
|
||||
*>
|
||||
* =====================================================================
|
||||
SUBROUTINE DLAE2( A, B, C, RT1, RT2 )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
DOUBLE PRECISION A, B, C, RT1, RT2
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ONE
|
||||
PARAMETER ( ONE = 1.0D0 )
|
||||
DOUBLE PRECISION TWO
|
||||
PARAMETER ( TWO = 2.0D0 )
|
||||
DOUBLE PRECISION ZERO
|
||||
PARAMETER ( ZERO = 0.0D0 )
|
||||
DOUBLE PRECISION HALF
|
||||
PARAMETER ( HALF = 0.5D0 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
DOUBLE PRECISION AB, ACMN, ACMX, ADF, DF, RT, SM, TB
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ABS, SQRT
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
* Compute the eigenvalues
|
||||
*
|
||||
SM = A + C
|
||||
DF = A - C
|
||||
ADF = ABS( DF )
|
||||
TB = B + B
|
||||
AB = ABS( TB )
|
||||
IF( ABS( A ).GT.ABS( C ) ) THEN
|
||||
ACMX = A
|
||||
ACMN = C
|
||||
ELSE
|
||||
ACMX = C
|
||||
ACMN = A
|
||||
END IF
|
||||
IF( ADF.GT.AB ) THEN
|
||||
RT = ADF*SQRT( ONE+( AB / ADF )**2 )
|
||||
ELSE IF( ADF.LT.AB ) THEN
|
||||
RT = AB*SQRT( ONE+( ADF / AB )**2 )
|
||||
ELSE
|
||||
*
|
||||
* Includes case AB=ADF=0
|
||||
*
|
||||
RT = AB*SQRT( TWO )
|
||||
END IF
|
||||
IF( SM.LT.ZERO ) THEN
|
||||
RT1 = HALF*( SM-RT )
|
||||
*
|
||||
* Order of execution important.
|
||||
* To get fully accurate smaller eigenvalue,
|
||||
* next line needs to be executed in higher precision.
|
||||
*
|
||||
RT2 = ( ACMX / RT1 )*ACMN - ( B / RT1 )*B
|
||||
ELSE IF( SM.GT.ZERO ) THEN
|
||||
RT1 = HALF*( SM+RT )
|
||||
*
|
||||
* Order of execution important.
|
||||
* To get fully accurate smaller eigenvalue,
|
||||
* next line needs to be executed in higher precision.
|
||||
*
|
||||
RT2 = ( ACMX / RT1 )*ACMN - ( B / RT1 )*B
|
||||
ELSE
|
||||
*
|
||||
* Includes case RT1 = RT2 = 0
|
||||
*
|
||||
RT1 = HALF*RT
|
||||
RT2 = -HALF*RT
|
||||
END IF
|
||||
RETURN
|
||||
*
|
||||
* End of DLAE2
|
||||
*
|
||||
END
|
91
internal/testdata/dsterftest/dlaisnan.f
vendored
Normal file
91
internal/testdata/dsterftest/dlaisnan.f
vendored
Normal file
@@ -0,0 +1,91 @@
|
||||
*> \brief \b DLAISNAN tests input for NaN by comparing two arguments for inequality.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLAISNAN + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaisnan.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaisnan.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaisnan.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* LOGICAL FUNCTION DLAISNAN( DIN1, DIN2 )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* DOUBLE PRECISION DIN1, DIN2
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> This routine is not for general use. It exists solely to avoid
|
||||
*> over-optimization in DISNAN.
|
||||
*>
|
||||
*> DLAISNAN checks for NaNs by comparing its two arguments for
|
||||
*> inequality. NaN is the only floating-point value where NaN != NaN
|
||||
*> returns .TRUE. To check for NaNs, pass the same variable as both
|
||||
*> arguments.
|
||||
*>
|
||||
*> A compiler must assume that the two arguments are
|
||||
*> not the same variable, and the test will not be optimized away.
|
||||
*> Interprocedural or whole-program optimization may delete this
|
||||
*> test. The ISNAN functions will be replaced by the correct
|
||||
*> Fortran 03 intrinsic once the intrinsic is widely available.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] DIN1
|
||||
*> \verbatim
|
||||
*> DIN1 is DOUBLE PRECISION
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] DIN2
|
||||
*> \verbatim
|
||||
*> DIN2 is DOUBLE PRECISION
|
||||
*> Two numbers to compare for inequality.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
LOGICAL FUNCTION DLAISNAN( DIN1, DIN2 )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
DOUBLE PRECISION DIN1, DIN2
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Executable Statements ..
|
||||
DLAISNAN = (DIN1.NE.DIN2)
|
||||
RETURN
|
||||
END
|
193
internal/testdata/dsterftest/dlamch.f
vendored
Normal file
193
internal/testdata/dsterftest/dlamch.f
vendored
Normal file
@@ -0,0 +1,193 @@
|
||||
*> \brief \b DLAMCH
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* DOUBLE PRECISION FUNCTION DLAMCH( CMACH )
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLAMCH determines double precision machine parameters.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] CMACH
|
||||
*> \verbatim
|
||||
*> Specifies the value to be returned by DLAMCH:
|
||||
*> = 'E' or 'e', DLAMCH := eps
|
||||
*> = 'S' or 's , DLAMCH := sfmin
|
||||
*> = 'B' or 'b', DLAMCH := base
|
||||
*> = 'P' or 'p', DLAMCH := eps*base
|
||||
*> = 'N' or 'n', DLAMCH := t
|
||||
*> = 'R' or 'r', DLAMCH := rnd
|
||||
*> = 'M' or 'm', DLAMCH := emin
|
||||
*> = 'U' or 'u', DLAMCH := rmin
|
||||
*> = 'L' or 'l', DLAMCH := emax
|
||||
*> = 'O' or 'o', DLAMCH := rmax
|
||||
*> where
|
||||
*> eps = relative machine precision
|
||||
*> sfmin = safe minimum, such that 1/sfmin does not overflow
|
||||
*> base = base of the machine
|
||||
*> prec = eps*base
|
||||
*> t = number of (base) digits in the mantissa
|
||||
*> rnd = 1.0 when rounding occurs in addition, 0.0 otherwise
|
||||
*> emin = minimum exponent before (gradual) underflow
|
||||
*> rmin = underflow threshold - base**(emin-1)
|
||||
*> emax = largest exponent before overflow
|
||||
*> rmax = overflow threshold - (base**emax)*(1-eps)
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date November 2011
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
DOUBLE PRECISION FUNCTION DLAMCH( CMACH )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.0) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* November 2011
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
CHARACTER CMACH
|
||||
* ..
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
DOUBLE PRECISION A, B
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ONE, ZERO
|
||||
PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
DOUBLE PRECISION RND, EPS, SFMIN, SMALL, RMACH
|
||||
* ..
|
||||
* .. External Functions ..
|
||||
LOGICAL LSAME
|
||||
EXTERNAL LSAME
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC DIGITS, EPSILON, HUGE, MAXEXPONENT,
|
||||
$ MINEXPONENT, RADIX, TINY
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
*
|
||||
* Assume rounding, not chopping. Always.
|
||||
*
|
||||
RND = ONE
|
||||
*
|
||||
IF( ONE.EQ.RND ) THEN
|
||||
EPS = EPSILON(ZERO) * 0.5
|
||||
ELSE
|
||||
EPS = EPSILON(ZERO)
|
||||
END IF
|
||||
*
|
||||
IF( LSAME( CMACH, 'E' ) ) THEN
|
||||
RMACH = EPS
|
||||
ELSE IF( LSAME( CMACH, 'S' ) ) THEN
|
||||
SFMIN = TINY(ZERO)
|
||||
SMALL = ONE / HUGE(ZERO)
|
||||
IF( SMALL.GE.SFMIN ) THEN
|
||||
*
|
||||
* Use SMALL plus a bit, to avoid the possibility of rounding
|
||||
* causing overflow when computing 1/sfmin.
|
||||
*
|
||||
SFMIN = SMALL*( ONE+EPS )
|
||||
END IF
|
||||
RMACH = SFMIN
|
||||
ELSE IF( LSAME( CMACH, 'B' ) ) THEN
|
||||
RMACH = RADIX(ZERO)
|
||||
ELSE IF( LSAME( CMACH, 'P' ) ) THEN
|
||||
RMACH = EPS * RADIX(ZERO)
|
||||
ELSE IF( LSAME( CMACH, 'N' ) ) THEN
|
||||
RMACH = DIGITS(ZERO)
|
||||
ELSE IF( LSAME( CMACH, 'R' ) ) THEN
|
||||
RMACH = RND
|
||||
ELSE IF( LSAME( CMACH, 'M' ) ) THEN
|
||||
RMACH = MINEXPONENT(ZERO)
|
||||
ELSE IF( LSAME( CMACH, 'U' ) ) THEN
|
||||
RMACH = tiny(zero)
|
||||
ELSE IF( LSAME( CMACH, 'L' ) ) THEN
|
||||
RMACH = MAXEXPONENT(ZERO)
|
||||
ELSE IF( LSAME( CMACH, 'O' ) ) THEN
|
||||
RMACH = HUGE(ZERO)
|
||||
ELSE
|
||||
RMACH = ZERO
|
||||
END IF
|
||||
*
|
||||
DLAMCH = RMACH
|
||||
RETURN
|
||||
*
|
||||
* End of DLAMCH
|
||||
*
|
||||
END
|
||||
************************************************************************
|
||||
*> \brief \b DLAMC3
|
||||
*> \details
|
||||
*> \b Purpose:
|
||||
*> \verbatim
|
||||
*> DLAMC3 is intended to force A and B to be stored prior to doing
|
||||
*> the addition of A and B , for use in situations where optimizers
|
||||
*> might hold one of these in a register.
|
||||
*> \endverbatim
|
||||
*> \author LAPACK is a software package provided by Univ. of Tennessee, Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..
|
||||
*> \date November 2011
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*>
|
||||
*> \param[in] A
|
||||
*> \verbatim
|
||||
*> A is a DOUBLE PRECISION
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] B
|
||||
*> \verbatim
|
||||
*> B is a DOUBLE PRECISION
|
||||
*> The values A and B.
|
||||
*> \endverbatim
|
||||
*>
|
||||
DOUBLE PRECISION FUNCTION DLAMC3( A, B )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.0) --
|
||||
* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
|
||||
* November 2010
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
DOUBLE PRECISION A, B
|
||||
* ..
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
DLAMC3 = A + B
|
||||
*
|
||||
RETURN
|
||||
*
|
||||
* End of DLAMC3
|
||||
*
|
||||
END
|
||||
*
|
||||
************************************************************************
|
186
internal/testdata/dsterftest/dlanst.f
vendored
Normal file
186
internal/testdata/dsterftest/dlanst.f
vendored
Normal file
@@ -0,0 +1,186 @@
|
||||
*> \brief \b DLANST returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a real symmetric tridiagonal matrix.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLANST + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlanst.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlanst.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlanst.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* DOUBLE PRECISION FUNCTION DLANST( NORM, N, D, E )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* CHARACTER NORM
|
||||
* INTEGER N
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
* DOUBLE PRECISION D( * ), E( * )
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLANST returns the value of the one norm, or the Frobenius norm, or
|
||||
*> the infinity norm, or the element of largest absolute value of a
|
||||
*> real symmetric tridiagonal matrix A.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \return DLANST
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLANST = ( max(abs(A(i,j))), NORM = 'M' or 'm'
|
||||
*> (
|
||||
*> ( norm1(A), NORM = '1', 'O' or 'o'
|
||||
*> (
|
||||
*> ( normI(A), NORM = 'I' or 'i'
|
||||
*> (
|
||||
*> ( normF(A), NORM = 'F', 'f', 'E' or 'e'
|
||||
*>
|
||||
*> where norm1 denotes the one norm of a matrix (maximum column sum),
|
||||
*> normI denotes the infinity norm of a matrix (maximum row sum) and
|
||||
*> normF denotes the Frobenius norm of a matrix (square root of sum of
|
||||
*> squares). Note that max(abs(A(i,j))) is not a consistent matrix norm.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] NORM
|
||||
*> \verbatim
|
||||
*> NORM is CHARACTER*1
|
||||
*> Specifies the value to be returned in DLANST as described
|
||||
*> above.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] N
|
||||
*> \verbatim
|
||||
*> N is INTEGER
|
||||
*> The order of the matrix A. N >= 0. When N = 0, DLANST is
|
||||
*> set to zero.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] D
|
||||
*> \verbatim
|
||||
*> D is DOUBLE PRECISION array, dimension (N)
|
||||
*> The diagonal elements of A.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] E
|
||||
*> \verbatim
|
||||
*> E is DOUBLE PRECISION array, dimension (N-1)
|
||||
*> The (n-1) sub-diagonal or super-diagonal elements of A.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
DOUBLE PRECISION FUNCTION DLANST( NORM, N, D, E )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
CHARACTER NORM
|
||||
INTEGER N
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
DOUBLE PRECISION D( * ), E( * )
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ONE, ZERO
|
||||
PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
INTEGER I
|
||||
DOUBLE PRECISION ANORM, SCALE, SUM
|
||||
* ..
|
||||
* .. External Functions ..
|
||||
LOGICAL LSAME, DISNAN
|
||||
EXTERNAL LSAME, DISNAN
|
||||
* ..
|
||||
* .. External Subroutines ..
|
||||
EXTERNAL DLASSQ
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ABS, SQRT
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
IF( N.LE.0 ) THEN
|
||||
ANORM = ZERO
|
||||
ELSE IF( LSAME( NORM, 'M' ) ) THEN
|
||||
*
|
||||
* Find max(abs(A(i,j))).
|
||||
*
|
||||
ANORM = ABS( D( N ) )
|
||||
DO 10 I = 1, N - 1
|
||||
SUM = ABS( D( I ) )
|
||||
IF( ANORM .LT. SUM .OR. DISNAN( SUM ) ) ANORM = SUM
|
||||
SUM = ABS( E( I ) )
|
||||
IF( ANORM .LT. SUM .OR. DISNAN( SUM ) ) ANORM = SUM
|
||||
10 CONTINUE
|
||||
ELSE IF( LSAME( NORM, 'O' ) .OR. NORM.EQ.'1' .OR.
|
||||
$ LSAME( NORM, 'I' ) ) THEN
|
||||
*
|
||||
* Find norm1(A).
|
||||
*
|
||||
IF( N.EQ.1 ) THEN
|
||||
ANORM = ABS( D( 1 ) )
|
||||
ELSE
|
||||
ANORM = ABS( D( 1 ) )+ABS( E( 1 ) )
|
||||
SUM = ABS( E( N-1 ) )+ABS( D( N ) )
|
||||
IF( ANORM .LT. SUM .OR. DISNAN( SUM ) ) ANORM = SUM
|
||||
DO 20 I = 2, N - 1
|
||||
SUM = ABS( D( I ) )+ABS( E( I ) )+ABS( E( I-1 ) )
|
||||
IF( ANORM .LT. SUM .OR. DISNAN( SUM ) ) ANORM = SUM
|
||||
20 CONTINUE
|
||||
END IF
|
||||
ELSE IF( ( LSAME( NORM, 'F' ) ) .OR. ( LSAME( NORM, 'E' ) ) ) THEN
|
||||
*
|
||||
* Find normF(A).
|
||||
*
|
||||
SCALE = ZERO
|
||||
SUM = ONE
|
||||
IF( N.GT.1 ) THEN
|
||||
CALL DLASSQ( N-1, E, 1, SCALE, SUM )
|
||||
SUM = 2*SUM
|
||||
END IF
|
||||
CALL DLASSQ( N, D, 1, SCALE, SUM )
|
||||
ANORM = SCALE*SQRT( SUM )
|
||||
END IF
|
||||
*
|
||||
DLANST = ANORM
|
||||
RETURN
|
||||
*
|
||||
* End of DLANST
|
||||
*
|
||||
END
|
104
internal/testdata/dsterftest/dlapy2.f
vendored
Normal file
104
internal/testdata/dsterftest/dlapy2.f
vendored
Normal file
@@ -0,0 +1,104 @@
|
||||
*> \brief \b DLAPY2 returns sqrt(x2+y2).
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLAPY2 + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlapy2.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlapy2.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlapy2.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* DOUBLE PRECISION FUNCTION DLAPY2( X, Y )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* DOUBLE PRECISION X, Y
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLAPY2 returns sqrt(x**2+y**2), taking care not to cause unnecessary
|
||||
*> overflow.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] X
|
||||
*> \verbatim
|
||||
*> X is DOUBLE PRECISION
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] Y
|
||||
*> \verbatim
|
||||
*> Y is DOUBLE PRECISION
|
||||
*> X and Y specify the values x and y.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
DOUBLE PRECISION FUNCTION DLAPY2( X, Y )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
DOUBLE PRECISION X, Y
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ZERO
|
||||
PARAMETER ( ZERO = 0.0D0 )
|
||||
DOUBLE PRECISION ONE
|
||||
PARAMETER ( ONE = 1.0D0 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
DOUBLE PRECISION W, XABS, YABS, Z
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ABS, MAX, MIN, SQRT
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
XABS = ABS( X )
|
||||
YABS = ABS( Y )
|
||||
W = MAX( XABS, YABS )
|
||||
Z = MIN( XABS, YABS )
|
||||
IF( Z.EQ.ZERO ) THEN
|
||||
DLAPY2 = W
|
||||
ELSE
|
||||
DLAPY2 = W*SQRT( ONE+( Z / W )**2 )
|
||||
END IF
|
||||
RETURN
|
||||
*
|
||||
* End of DLAPY2
|
||||
*
|
||||
END
|
364
internal/testdata/dsterftest/dlascl.f
vendored
Normal file
364
internal/testdata/dsterftest/dlascl.f
vendored
Normal file
@@ -0,0 +1,364 @@
|
||||
*> \brief \b DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLASCL + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlascl.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlascl.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlascl.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* SUBROUTINE DLASCL( TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* CHARACTER TYPE
|
||||
* INTEGER INFO, KL, KU, LDA, M, N
|
||||
* DOUBLE PRECISION CFROM, CTO
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
* DOUBLE PRECISION A( LDA, * )
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLASCL multiplies the M by N real matrix A by the real scalar
|
||||
*> CTO/CFROM. This is done without over/underflow as long as the final
|
||||
*> result CTO*A(I,J)/CFROM does not over/underflow. TYPE specifies that
|
||||
*> A may be full, upper triangular, lower triangular, upper Hessenberg,
|
||||
*> or banded.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] TYPE
|
||||
*> \verbatim
|
||||
*> TYPE is CHARACTER*1
|
||||
*> TYPE indices the storage type of the input matrix.
|
||||
*> = 'G': A is a full matrix.
|
||||
*> = 'L': A is a lower triangular matrix.
|
||||
*> = 'U': A is an upper triangular matrix.
|
||||
*> = 'H': A is an upper Hessenberg matrix.
|
||||
*> = 'B': A is a symmetric band matrix with lower bandwidth KL
|
||||
*> and upper bandwidth KU and with the only the lower
|
||||
*> half stored.
|
||||
*> = 'Q': A is a symmetric band matrix with lower bandwidth KL
|
||||
*> and upper bandwidth KU and with the only the upper
|
||||
*> half stored.
|
||||
*> = 'Z': A is a band matrix with lower bandwidth KL and upper
|
||||
*> bandwidth KU. See DGBTRF for storage details.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] KL
|
||||
*> \verbatim
|
||||
*> KL is INTEGER
|
||||
*> The lower bandwidth of A. Referenced only if TYPE = 'B',
|
||||
*> 'Q' or 'Z'.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] KU
|
||||
*> \verbatim
|
||||
*> KU is INTEGER
|
||||
*> The upper bandwidth of A. Referenced only if TYPE = 'B',
|
||||
*> 'Q' or 'Z'.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] CFROM
|
||||
*> \verbatim
|
||||
*> CFROM is DOUBLE PRECISION
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] CTO
|
||||
*> \verbatim
|
||||
*> CTO is DOUBLE PRECISION
|
||||
*>
|
||||
*> The matrix A is multiplied by CTO/CFROM. A(I,J) is computed
|
||||
*> without over/underflow if the final result CTO*A(I,J)/CFROM
|
||||
*> can be represented without over/underflow. CFROM must be
|
||||
*> nonzero.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] M
|
||||
*> \verbatim
|
||||
*> M is INTEGER
|
||||
*> The number of rows of the matrix A. M >= 0.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] N
|
||||
*> \verbatim
|
||||
*> N is INTEGER
|
||||
*> The number of columns of the matrix A. N >= 0.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in,out] A
|
||||
*> \verbatim
|
||||
*> A is DOUBLE PRECISION array, dimension (LDA,N)
|
||||
*> The matrix to be multiplied by CTO/CFROM. See TYPE for the
|
||||
*> storage type.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] LDA
|
||||
*> \verbatim
|
||||
*> LDA is INTEGER
|
||||
*> The leading dimension of the array A. LDA >= max(1,M).
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[out] INFO
|
||||
*> \verbatim
|
||||
*> INFO is INTEGER
|
||||
*> 0 - successful exit
|
||||
*> <0 - if INFO = -i, the i-th argument had an illegal value.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
SUBROUTINE DLASCL( TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
CHARACTER TYPE
|
||||
INTEGER INFO, KL, KU, LDA, M, N
|
||||
DOUBLE PRECISION CFROM, CTO
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
DOUBLE PRECISION A( LDA, * )
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ZERO, ONE
|
||||
PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
LOGICAL DONE
|
||||
INTEGER I, ITYPE, J, K1, K2, K3, K4
|
||||
DOUBLE PRECISION BIGNUM, CFROM1, CFROMC, CTO1, CTOC, MUL, SMLNUM
|
||||
* ..
|
||||
* .. External Functions ..
|
||||
LOGICAL LSAME, DISNAN
|
||||
DOUBLE PRECISION DLAMCH
|
||||
EXTERNAL LSAME, DLAMCH, DISNAN
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ABS, MAX, MIN
|
||||
* ..
|
||||
* .. External Subroutines ..
|
||||
EXTERNAL XERBLA
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
* Test the input arguments
|
||||
*
|
||||
INFO = 0
|
||||
*
|
||||
IF( LSAME( TYPE, 'G' ) ) THEN
|
||||
ITYPE = 0
|
||||
ELSE IF( LSAME( TYPE, 'L' ) ) THEN
|
||||
ITYPE = 1
|
||||
ELSE IF( LSAME( TYPE, 'U' ) ) THEN
|
||||
ITYPE = 2
|
||||
ELSE IF( LSAME( TYPE, 'H' ) ) THEN
|
||||
ITYPE = 3
|
||||
ELSE IF( LSAME( TYPE, 'B' ) ) THEN
|
||||
ITYPE = 4
|
||||
ELSE IF( LSAME( TYPE, 'Q' ) ) THEN
|
||||
ITYPE = 5
|
||||
ELSE IF( LSAME( TYPE, 'Z' ) ) THEN
|
||||
ITYPE = 6
|
||||
ELSE
|
||||
ITYPE = -1
|
||||
END IF
|
||||
*
|
||||
IF( ITYPE.EQ.-1 ) THEN
|
||||
INFO = -1
|
||||
ELSE IF( CFROM.EQ.ZERO .OR. DISNAN(CFROM) ) THEN
|
||||
INFO = -4
|
||||
ELSE IF( DISNAN(CTO) ) THEN
|
||||
INFO = -5
|
||||
ELSE IF( M.LT.0 ) THEN
|
||||
INFO = -6
|
||||
ELSE IF( N.LT.0 .OR. ( ITYPE.EQ.4 .AND. N.NE.M ) .OR.
|
||||
$ ( ITYPE.EQ.5 .AND. N.NE.M ) ) THEN
|
||||
INFO = -7
|
||||
ELSE IF( ITYPE.LE.3 .AND. LDA.LT.MAX( 1, M ) ) THEN
|
||||
INFO = -9
|
||||
ELSE IF( ITYPE.GE.4 ) THEN
|
||||
IF( KL.LT.0 .OR. KL.GT.MAX( M-1, 0 ) ) THEN
|
||||
INFO = -2
|
||||
ELSE IF( KU.LT.0 .OR. KU.GT.MAX( N-1, 0 ) .OR.
|
||||
$ ( ( ITYPE.EQ.4 .OR. ITYPE.EQ.5 ) .AND. KL.NE.KU ) )
|
||||
$ THEN
|
||||
INFO = -3
|
||||
ELSE IF( ( ITYPE.EQ.4 .AND. LDA.LT.KL+1 ) .OR.
|
||||
$ ( ITYPE.EQ.5 .AND. LDA.LT.KU+1 ) .OR.
|
||||
$ ( ITYPE.EQ.6 .AND. LDA.LT.2*KL+KU+1 ) ) THEN
|
||||
INFO = -9
|
||||
END IF
|
||||
END IF
|
||||
*
|
||||
IF( INFO.NE.0 ) THEN
|
||||
CALL XERBLA( 'DLASCL', -INFO )
|
||||
RETURN
|
||||
END IF
|
||||
*
|
||||
* Quick return if possible
|
||||
*
|
||||
IF( N.EQ.0 .OR. M.EQ.0 )
|
||||
$ RETURN
|
||||
*
|
||||
* Get machine parameters
|
||||
*
|
||||
SMLNUM = DLAMCH( 'S' )
|
||||
BIGNUM = ONE / SMLNUM
|
||||
*
|
||||
CFROMC = CFROM
|
||||
CTOC = CTO
|
||||
*
|
||||
10 CONTINUE
|
||||
CFROM1 = CFROMC*SMLNUM
|
||||
IF( CFROM1.EQ.CFROMC ) THEN
|
||||
! CFROMC is an inf. Multiply by a correctly signed zero for
|
||||
! finite CTOC, or a NaN if CTOC is infinite.
|
||||
MUL = CTOC / CFROMC
|
||||
DONE = .TRUE.
|
||||
CTO1 = CTOC
|
||||
ELSE
|
||||
CTO1 = CTOC / BIGNUM
|
||||
IF( CTO1.EQ.CTOC ) THEN
|
||||
! CTOC is either 0 or an inf. In both cases, CTOC itself
|
||||
! serves as the correct multiplication factor.
|
||||
MUL = CTOC
|
||||
DONE = .TRUE.
|
||||
CFROMC = ONE
|
||||
ELSE IF( ABS( CFROM1 ).GT.ABS( CTOC ) .AND. CTOC.NE.ZERO ) THEN
|
||||
MUL = SMLNUM
|
||||
DONE = .FALSE.
|
||||
CFROMC = CFROM1
|
||||
ELSE IF( ABS( CTO1 ).GT.ABS( CFROMC ) ) THEN
|
||||
MUL = BIGNUM
|
||||
DONE = .FALSE.
|
||||
CTOC = CTO1
|
||||
ELSE
|
||||
MUL = CTOC / CFROMC
|
||||
DONE = .TRUE.
|
||||
END IF
|
||||
END IF
|
||||
*
|
||||
IF( ITYPE.EQ.0 ) THEN
|
||||
*
|
||||
* Full matrix
|
||||
*
|
||||
DO 30 J = 1, N
|
||||
DO 20 I = 1, M
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
20 CONTINUE
|
||||
30 CONTINUE
|
||||
*
|
||||
ELSE IF( ITYPE.EQ.1 ) THEN
|
||||
*
|
||||
* Lower triangular matrix
|
||||
*
|
||||
DO 50 J = 1, N
|
||||
DO 40 I = J, M
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
40 CONTINUE
|
||||
50 CONTINUE
|
||||
*
|
||||
ELSE IF( ITYPE.EQ.2 ) THEN
|
||||
*
|
||||
* Upper triangular matrix
|
||||
*
|
||||
DO 70 J = 1, N
|
||||
DO 60 I = 1, MIN( J, M )
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
60 CONTINUE
|
||||
70 CONTINUE
|
||||
*
|
||||
ELSE IF( ITYPE.EQ.3 ) THEN
|
||||
*
|
||||
* Upper Hessenberg matrix
|
||||
*
|
||||
DO 90 J = 1, N
|
||||
DO 80 I = 1, MIN( J+1, M )
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
80 CONTINUE
|
||||
90 CONTINUE
|
||||
*
|
||||
ELSE IF( ITYPE.EQ.4 ) THEN
|
||||
*
|
||||
* Lower half of a symmetric band matrix
|
||||
*
|
||||
K3 = KL + 1
|
||||
K4 = N + 1
|
||||
DO 110 J = 1, N
|
||||
DO 100 I = 1, MIN( K3, K4-J )
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
100 CONTINUE
|
||||
110 CONTINUE
|
||||
*
|
||||
ELSE IF( ITYPE.EQ.5 ) THEN
|
||||
*
|
||||
* Upper half of a symmetric band matrix
|
||||
*
|
||||
K1 = KU + 2
|
||||
K3 = KU + 1
|
||||
DO 130 J = 1, N
|
||||
DO 120 I = MAX( K1-J, 1 ), K3
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
120 CONTINUE
|
||||
130 CONTINUE
|
||||
*
|
||||
ELSE IF( ITYPE.EQ.6 ) THEN
|
||||
*
|
||||
* Band matrix
|
||||
*
|
||||
K1 = KL + KU + 2
|
||||
K2 = KL + 1
|
||||
K3 = 2*KL + KU + 1
|
||||
K4 = KL + KU + 1 + M
|
||||
DO 150 J = 1, N
|
||||
DO 140 I = MAX( K1-J, K2 ), MIN( K3, K4-J )
|
||||
A( I, J ) = A( I, J )*MUL
|
||||
140 CONTINUE
|
||||
150 CONTINUE
|
||||
*
|
||||
END IF
|
||||
*
|
||||
IF( .NOT.DONE )
|
||||
$ GO TO 10
|
||||
*
|
||||
RETURN
|
||||
*
|
||||
* End of DLASCL
|
||||
*
|
||||
END
|
303
internal/testdata/dsterftest/dlasrt.f
vendored
Normal file
303
internal/testdata/dsterftest/dlasrt.f
vendored
Normal file
@@ -0,0 +1,303 @@
|
||||
*> \brief \b DLASRT sorts numbers in increasing or decreasing order.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLASRT + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlasrt.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlasrt.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasrt.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* SUBROUTINE DLASRT( ID, N, D, INFO )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* CHARACTER ID
|
||||
* INTEGER INFO, N
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
* DOUBLE PRECISION D( * )
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> Sort the numbers in D in increasing order (if ID = 'I') or
|
||||
*> in decreasing order (if ID = 'D' ).
|
||||
*>
|
||||
*> Use Quick Sort, reverting to Insertion sort on arrays of
|
||||
*> size <= 20. Dimension of STACK limits N to about 2**32.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] ID
|
||||
*> \verbatim
|
||||
*> ID is CHARACTER*1
|
||||
*> = 'I': sort D in increasing order;
|
||||
*> = 'D': sort D in decreasing order.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] N
|
||||
*> \verbatim
|
||||
*> N is INTEGER
|
||||
*> The length of the array D.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in,out] D
|
||||
*> \verbatim
|
||||
*> D is DOUBLE PRECISION array, dimension (N)
|
||||
*> On entry, the array to be sorted.
|
||||
*> On exit, D has been sorted into increasing order
|
||||
*> (D(1) <= ... <= D(N) ) or into decreasing order
|
||||
*> (D(1) >= ... >= D(N) ), depending on ID.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[out] INFO
|
||||
*> \verbatim
|
||||
*> INFO is INTEGER
|
||||
*> = 0: successful exit
|
||||
*> < 0: if INFO = -i, the i-th argument had an illegal value
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERcomputational
|
||||
*
|
||||
* =====================================================================
|
||||
SUBROUTINE DLASRT( ID, N, D, INFO )
|
||||
*
|
||||
* -- LAPACK computational routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
CHARACTER ID
|
||||
INTEGER INFO, N
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
DOUBLE PRECISION D( * )
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
INTEGER SELECT
|
||||
PARAMETER ( SELECT = 20 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
INTEGER DIR, ENDD, I, J, START, STKPNT
|
||||
DOUBLE PRECISION D1, D2, D3, DMNMX, TMP
|
||||
* ..
|
||||
* .. Local Arrays ..
|
||||
INTEGER STACK( 2, 32 )
|
||||
* ..
|
||||
* .. External Functions ..
|
||||
LOGICAL LSAME
|
||||
EXTERNAL LSAME
|
||||
* ..
|
||||
* .. External Subroutines ..
|
||||
EXTERNAL XERBLA
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
* Test the input paramters.
|
||||
*
|
||||
INFO = 0
|
||||
DIR = -1
|
||||
IF( LSAME( ID, 'D' ) ) THEN
|
||||
DIR = 0
|
||||
ELSE IF( LSAME( ID, 'I' ) ) THEN
|
||||
DIR = 1
|
||||
END IF
|
||||
IF( DIR.EQ.-1 ) THEN
|
||||
INFO = -1
|
||||
ELSE IF( N.LT.0 ) THEN
|
||||
INFO = -2
|
||||
END IF
|
||||
IF( INFO.NE.0 ) THEN
|
||||
CALL XERBLA( 'DLASRT', -INFO )
|
||||
RETURN
|
||||
END IF
|
||||
*
|
||||
* Quick return if possible
|
||||
*
|
||||
IF( N.LE.1 )
|
||||
$ RETURN
|
||||
*
|
||||
STKPNT = 1
|
||||
STACK( 1, 1 ) = 1
|
||||
STACK( 2, 1 ) = N
|
||||
10 CONTINUE
|
||||
START = STACK( 1, STKPNT )
|
||||
ENDD = STACK( 2, STKPNT )
|
||||
STKPNT = STKPNT - 1
|
||||
IF( ENDD-START.LE.SELECT .AND. ENDD-START.GT.0 ) THEN
|
||||
*
|
||||
* Do Insertion sort on D( START:ENDD )
|
||||
*
|
||||
IF( DIR.EQ.0 ) THEN
|
||||
*
|
||||
* Sort into decreasing order
|
||||
*
|
||||
DO 30 I = START + 1, ENDD
|
||||
DO 20 J = I, START + 1, -1
|
||||
IF( D( J ).GT.D( J-1 ) ) THEN
|
||||
DMNMX = D( J )
|
||||
D( J ) = D( J-1 )
|
||||
D( J-1 ) = DMNMX
|
||||
ELSE
|
||||
GO TO 30
|
||||
END IF
|
||||
20 CONTINUE
|
||||
30 CONTINUE
|
||||
*
|
||||
ELSE
|
||||
*
|
||||
* Sort into increasing order
|
||||
*
|
||||
DO 50 I = START + 1, ENDD
|
||||
DO 40 J = I, START + 1, -1
|
||||
IF( D( J ).LT.D( J-1 ) ) THEN
|
||||
DMNMX = D( J )
|
||||
D( J ) = D( J-1 )
|
||||
D( J-1 ) = DMNMX
|
||||
ELSE
|
||||
GO TO 50
|
||||
END IF
|
||||
40 CONTINUE
|
||||
50 CONTINUE
|
||||
*
|
||||
END IF
|
||||
*
|
||||
ELSE IF( ENDD-START.GT.SELECT ) THEN
|
||||
*
|
||||
* Partition D( START:ENDD ) and stack parts, largest one first
|
||||
*
|
||||
* Choose partition entry as median of 3
|
||||
*
|
||||
D1 = D( START )
|
||||
D2 = D( ENDD )
|
||||
I = ( START+ENDD ) / 2
|
||||
D3 = D( I )
|
||||
IF( D1.LT.D2 ) THEN
|
||||
IF( D3.LT.D1 ) THEN
|
||||
DMNMX = D1
|
||||
ELSE IF( D3.LT.D2 ) THEN
|
||||
DMNMX = D3
|
||||
ELSE
|
||||
DMNMX = D2
|
||||
END IF
|
||||
ELSE
|
||||
IF( D3.LT.D2 ) THEN
|
||||
DMNMX = D2
|
||||
ELSE IF( D3.LT.D1 ) THEN
|
||||
DMNMX = D3
|
||||
ELSE
|
||||
DMNMX = D1
|
||||
END IF
|
||||
END IF
|
||||
*
|
||||
IF( DIR.EQ.0 ) THEN
|
||||
*
|
||||
* Sort into decreasing order
|
||||
*
|
||||
I = START - 1
|
||||
J = ENDD + 1
|
||||
60 CONTINUE
|
||||
70 CONTINUE
|
||||
J = J - 1
|
||||
IF( D( J ).LT.DMNMX )
|
||||
$ GO TO 70
|
||||
80 CONTINUE
|
||||
I = I + 1
|
||||
IF( D( I ).GT.DMNMX )
|
||||
$ GO TO 80
|
||||
IF( I.LT.J ) THEN
|
||||
TMP = D( I )
|
||||
D( I ) = D( J )
|
||||
D( J ) = TMP
|
||||
GO TO 60
|
||||
END IF
|
||||
IF( J-START.GT.ENDD-J-1 ) THEN
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = START
|
||||
STACK( 2, STKPNT ) = J
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = J + 1
|
||||
STACK( 2, STKPNT ) = ENDD
|
||||
ELSE
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = J + 1
|
||||
STACK( 2, STKPNT ) = ENDD
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = START
|
||||
STACK( 2, STKPNT ) = J
|
||||
END IF
|
||||
ELSE
|
||||
*
|
||||
* Sort into increasing order
|
||||
*
|
||||
I = START - 1
|
||||
J = ENDD + 1
|
||||
90 CONTINUE
|
||||
100 CONTINUE
|
||||
J = J - 1
|
||||
IF( D( J ).GT.DMNMX )
|
||||
$ GO TO 100
|
||||
110 CONTINUE
|
||||
I = I + 1
|
||||
IF( D( I ).LT.DMNMX )
|
||||
$ GO TO 110
|
||||
IF( I.LT.J ) THEN
|
||||
TMP = D( I )
|
||||
D( I ) = D( J )
|
||||
D( J ) = TMP
|
||||
GO TO 90
|
||||
END IF
|
||||
IF( J-START.GT.ENDD-J-1 ) THEN
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = START
|
||||
STACK( 2, STKPNT ) = J
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = J + 1
|
||||
STACK( 2, STKPNT ) = ENDD
|
||||
ELSE
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = J + 1
|
||||
STACK( 2, STKPNT ) = ENDD
|
||||
STKPNT = STKPNT + 1
|
||||
STACK( 1, STKPNT ) = START
|
||||
STACK( 2, STKPNT ) = J
|
||||
END IF
|
||||
END IF
|
||||
END IF
|
||||
IF( STKPNT.GT.0 )
|
||||
$ GO TO 10
|
||||
RETURN
|
||||
*
|
||||
* End of DLASRT
|
||||
*
|
||||
END
|
155
internal/testdata/dsterftest/dlassq.f
vendored
Normal file
155
internal/testdata/dsterftest/dlassq.f
vendored
Normal file
@@ -0,0 +1,155 @@
|
||||
*> \brief \b DLASSQ updates a sum of squares represented in scaled form.
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DLASSQ + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlassq.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlassq.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlassq.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* SUBROUTINE DLASSQ( N, X, INCX, SCALE, SUMSQ )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* INTEGER INCX, N
|
||||
* DOUBLE PRECISION SCALE, SUMSQ
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
* DOUBLE PRECISION X( * )
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DLASSQ returns the values scl and smsq such that
|
||||
*>
|
||||
*> ( scl**2 )*smsq = x( 1 )**2 +...+ x( n )**2 + ( scale**2 )*sumsq,
|
||||
*>
|
||||
*> where x( i ) = X( 1 + ( i - 1 )*INCX ). The value of sumsq is
|
||||
*> assumed to be non-negative and scl returns the value
|
||||
*>
|
||||
*> scl = max( scale, abs( x( i ) ) ).
|
||||
*>
|
||||
*> scale and sumsq must be supplied in SCALE and SUMSQ and
|
||||
*> scl and smsq are overwritten on SCALE and SUMSQ respectively.
|
||||
*>
|
||||
*> The routine makes only one pass through the vector x.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] N
|
||||
*> \verbatim
|
||||
*> N is INTEGER
|
||||
*> The number of elements to be used from the vector X.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] X
|
||||
*> \verbatim
|
||||
*> X is DOUBLE PRECISION array, dimension (N)
|
||||
*> The vector for which a scaled sum of squares is computed.
|
||||
*> x( i ) = X( 1 + ( i - 1 )*INCX ), 1 <= i <= n.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] INCX
|
||||
*> \verbatim
|
||||
*> INCX is INTEGER
|
||||
*> The increment between successive values of the vector X.
|
||||
*> INCX > 0.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in,out] SCALE
|
||||
*> \verbatim
|
||||
*> SCALE is DOUBLE PRECISION
|
||||
*> On entry, the value scale in the equation above.
|
||||
*> On exit, SCALE is overwritten with scl , the scaling factor
|
||||
*> for the sum of squares.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in,out] SUMSQ
|
||||
*> \verbatim
|
||||
*> SUMSQ is DOUBLE PRECISION
|
||||
*> On entry, the value sumsq in the equation above.
|
||||
*> On exit, SUMSQ is overwritten with smsq , the basic sum of
|
||||
*> squares from which scl has been factored out.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date September 2012
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
SUBROUTINE DLASSQ( N, X, INCX, SCALE, SUMSQ )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.2) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* September 2012
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
INTEGER INCX, N
|
||||
DOUBLE PRECISION SCALE, SUMSQ
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
DOUBLE PRECISION X( * )
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ZERO
|
||||
PARAMETER ( ZERO = 0.0D+0 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
INTEGER IX
|
||||
DOUBLE PRECISION ABSXI
|
||||
* ..
|
||||
* .. External Functions ..
|
||||
LOGICAL DISNAN
|
||||
EXTERNAL DISNAN
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ABS
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
IF( N.GT.0 ) THEN
|
||||
DO 10 IX = 1, 1 + ( N-1 )*INCX, INCX
|
||||
ABSXI = ABS( X( IX ) )
|
||||
IF( ABSXI.GT.ZERO.OR.DISNAN( ABSXI ) ) THEN
|
||||
IF( SCALE.LT.ABSXI ) THEN
|
||||
SUMSQ = 1 + SUMSQ*( SCALE / ABSXI )**2
|
||||
SCALE = ABSXI
|
||||
ELSE
|
||||
SUMSQ = SUMSQ + ( ABSXI / SCALE )**2
|
||||
END IF
|
||||
END IF
|
||||
10 CONTINUE
|
||||
END IF
|
||||
RETURN
|
||||
*
|
||||
* End of DLASSQ
|
||||
*
|
||||
END
|
448
internal/testdata/dsterftest/dsterf.f
vendored
Normal file
448
internal/testdata/dsterftest/dsterf.f
vendored
Normal file
@@ -0,0 +1,448 @@
|
||||
*> \brief \b DSTERF
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download DSTERF + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsterf.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsterf.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsterf.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* SUBROUTINE DSTERF( N, D, E, INFO )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* INTEGER INFO, N
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
* DOUBLE PRECISION D( * ), E( * )
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> DSTERF computes all eigenvalues of a symmetric tridiagonal matrix
|
||||
*> using the Pal-Walker-Kahan variant of the QL or QR algorithm.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] N
|
||||
*> \verbatim
|
||||
*> N is INTEGER
|
||||
*> The order of the matrix. N >= 0.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in,out] D
|
||||
*> \verbatim
|
||||
*> D is DOUBLE PRECISION array, dimension (N)
|
||||
*> On entry, the n diagonal elements of the tridiagonal matrix.
|
||||
*> On exit, if INFO = 0, the eigenvalues in ascending order.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in,out] E
|
||||
*> \verbatim
|
||||
*> E is DOUBLE PRECISION array, dimension (N-1)
|
||||
*> On entry, the (n-1) subdiagonal elements of the tridiagonal
|
||||
*> matrix.
|
||||
*> On exit, E has been destroyed.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[out] INFO
|
||||
*> \verbatim
|
||||
*> INFO is INTEGER
|
||||
*> = 0: successful exit
|
||||
*> < 0: if INFO = -i, the i-th argument had an illegal value
|
||||
*> > 0: the algorithm failed to find all of the eigenvalues in
|
||||
*> a total of 30*N iterations; if INFO = i, then i
|
||||
*> elements of E have not converged to zero.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date November 2011
|
||||
*
|
||||
*> \ingroup auxOTHERcomputational
|
||||
*
|
||||
* =====================================================================
|
||||
SUBROUTINE DSTERF( N, D, E, INFO )
|
||||
*
|
||||
* -- LAPACK computational routine (version 3.4.0) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* November 2011
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
INTEGER INFO, N
|
||||
* ..
|
||||
* .. Array Arguments ..
|
||||
DOUBLE PRECISION D( * ), E( * )
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Parameters ..
|
||||
DOUBLE PRECISION ZERO, ONE, TWO, THREE
|
||||
PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0,
|
||||
$ THREE = 3.0D0 )
|
||||
INTEGER MAXIT
|
||||
PARAMETER ( MAXIT = 30 )
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
INTEGER I, ISCALE, JTOT, L, L1, LEND, LENDSV, LSV, M,
|
||||
$ NMAXIT
|
||||
DOUBLE PRECISION ALPHA, ANORM, BB, C, EPS, EPS2, GAMMA, OLDC,
|
||||
$ OLDGAM, P, R, RT1, RT2, RTE, S, SAFMAX, SAFMIN,
|
||||
$ SIGMA, SSFMAX, SSFMIN, RMAX
|
||||
* ..
|
||||
* .. External Functions ..
|
||||
DOUBLE PRECISION DLAMCH, DLANST, DLAPY2
|
||||
EXTERNAL DLAMCH, DLANST, DLAPY2
|
||||
* ..
|
||||
* .. External Subroutines ..
|
||||
EXTERNAL DLAE2, DLASCL, DLASRT, XERBLA
|
||||
* ..
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ABS, SIGN, SQRT
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
* Test the input parameters.
|
||||
*
|
||||
INFO = 0
|
||||
*
|
||||
* Quick return if possible
|
||||
*
|
||||
IF( N.LT.0 ) THEN
|
||||
INFO = -1
|
||||
CALL XERBLA( 'DSTERF', -INFO )
|
||||
RETURN
|
||||
END IF
|
||||
IF( N.LE.1 )
|
||||
$ RETURN
|
||||
*
|
||||
* Determine the unit roundoff for this environment.
|
||||
*
|
||||
EPS = DLAMCH( 'E' )
|
||||
EPS2 = EPS**2
|
||||
SAFMIN = DLAMCH( 'S' )
|
||||
SAFMAX = ONE / SAFMIN
|
||||
SSFMAX = SQRT( SAFMAX ) / THREE
|
||||
SSFMIN = SQRT( SAFMIN ) / EPS2
|
||||
RMAX = DLAMCH( 'O' )
|
||||
*
|
||||
* Compute the eigenvalues of the tridiagonal matrix.
|
||||
*
|
||||
NMAXIT = N*MAXIT
|
||||
SIGMA = ZERO
|
||||
JTOT = 0
|
||||
*
|
||||
* Determine where the matrix splits and choose QL or QR iteration
|
||||
* for each block, according to whether top or bottom diagonal
|
||||
* element is smaller.
|
||||
*
|
||||
L1 = 1
|
||||
*
|
||||
10 CONTINUE
|
||||
print *, "l1 = ", l1
|
||||
IF( L1.GT.N ) THEN
|
||||
print *, "going to 170"
|
||||
GO TO 170
|
||||
end if
|
||||
IF( L1.GT.1 )
|
||||
$ E( L1-1 ) = ZERO
|
||||
DO 20 M = L1, N - 1
|
||||
IF( ABS( E( M ) ).LE.( SQRT( ABS( D( M ) ) )*SQRT( ABS( D( M+
|
||||
$ 1 ) ) ) )*EPS ) THEN
|
||||
E( M ) = ZERO
|
||||
GO TO 30
|
||||
END IF
|
||||
20 CONTINUE
|
||||
M = N
|
||||
*
|
||||
30 CONTINUE
|
||||
print *, "30, d"
|
||||
print *, d(1:n)
|
||||
L = L1
|
||||
LSV = L
|
||||
LEND = M
|
||||
LENDSV = LEND
|
||||
L1 = M + 1
|
||||
IF( LEND.EQ.L )
|
||||
$ GO TO 10
|
||||
*
|
||||
* Scale submatrix in rows and columns L to LEND
|
||||
*
|
||||
ANORM = DLANST( 'M', LEND-L+1, D( L ), E( L ) )
|
||||
ISCALE = 0
|
||||
IF( ANORM.EQ.ZERO )
|
||||
$ GO TO 10
|
||||
IF( (ANORM.GT.SSFMAX) ) THEN
|
||||
ISCALE = 1
|
||||
CALL DLASCL( 'G', 0, 0, ANORM, SSFMAX, LEND-L+1, 1, D( L ), N,
|
||||
$ INFO )
|
||||
CALL DLASCL( 'G', 0, 0, ANORM, SSFMAX, LEND-L, 1, E( L ), N,
|
||||
$ INFO )
|
||||
ELSE IF( ANORM.LT.SSFMIN ) THEN
|
||||
ISCALE = 2
|
||||
CALL DLASCL( 'G', 0, 0, ANORM, SSFMIN, LEND-L+1, 1, D( L ), N,
|
||||
$ INFO )
|
||||
CALL DLASCL( 'G', 0, 0, ANORM, SSFMIN, LEND-L, 1, E( L ), N,
|
||||
$ INFO )
|
||||
END IF
|
||||
*
|
||||
DO 40 I = L, LEND - 1
|
||||
E( I ) = E( I )**2
|
||||
40 CONTINUE
|
||||
*
|
||||
* Choose between QL and QR iteration
|
||||
*
|
||||
IF( ABS( D( LEND ) ).LT.ABS( D( L ) ) ) THEN
|
||||
LEND = LSV
|
||||
L = LENDSV
|
||||
END IF
|
||||
*
|
||||
IF( LEND.GE.L ) THEN
|
||||
print *, "ql, d"
|
||||
print *, d(1:n)
|
||||
*
|
||||
* QL Iteration
|
||||
*
|
||||
* Look for small subdiagonal element.
|
||||
*
|
||||
50 CONTINUE
|
||||
IF( L.NE.LEND ) THEN
|
||||
DO 60 M = L, LEND - 1
|
||||
IF( ABS( E( M ) ).LE.EPS2*ABS( D( M )*D( M+1 ) ) )
|
||||
$ GO TO 70
|
||||
60 CONTINUE
|
||||
END IF
|
||||
M = LEND
|
||||
*
|
||||
70 CONTINUE
|
||||
IF( M.LT.LEND )
|
||||
$ E( M ) = ZERO
|
||||
P = D( L )
|
||||
IF( M.EQ.L )
|
||||
$ GO TO 90
|
||||
*
|
||||
* If remaining matrix is 2 by 2, use DLAE2 to compute its
|
||||
* eigenvalues.
|
||||
*
|
||||
IF( M.EQ.L+1 ) THEN
|
||||
RTE = SQRT( E( L ) )
|
||||
CALL DLAE2( D( L ), RTE, D( L+1 ), RT1, RT2 )
|
||||
D( L ) = RT1
|
||||
D( L+1 ) = RT2
|
||||
E( L ) = ZERO
|
||||
L = L + 2
|
||||
IF( L.LE.LEND )
|
||||
$ GO TO 50
|
||||
GO TO 150
|
||||
END IF
|
||||
*
|
||||
IF( JTOT.EQ.NMAXIT )
|
||||
$ GO TO 150
|
||||
JTOT = JTOT + 1
|
||||
*
|
||||
* Form shift.
|
||||
*
|
||||
RTE = SQRT( E( L ) )
|
||||
SIGMA = ( D( L+1 )-P ) / ( TWO*RTE )
|
||||
R = DLAPY2( SIGMA, ONE )
|
||||
SIGMA = P - ( RTE / ( SIGMA+SIGN( R, SIGMA ) ) )
|
||||
*
|
||||
C = ONE
|
||||
S = ZERO
|
||||
GAMMA = D( M ) - SIGMA
|
||||
P = GAMMA*GAMMA
|
||||
*
|
||||
* Inner loop
|
||||
*
|
||||
print *, "inner loop d before"
|
||||
print *, d(1:n)
|
||||
|
||||
DO 80 I = M - 1, L, -1
|
||||
print *, "inner loop"
|
||||
print *, "ei", e(i)
|
||||
BB = E( I )
|
||||
R = P + BB
|
||||
print *, "bb,p,r"
|
||||
print *, bb,p,r
|
||||
IF( I.NE.M-1 ) THEN
|
||||
print *, s,r
|
||||
E( I+1 ) = S*R
|
||||
end if
|
||||
OLDC = C
|
||||
C = P / R
|
||||
S = BB / R
|
||||
OLDGAM = GAMMA
|
||||
print *, "di", d(i)
|
||||
ALPHA = D( I )
|
||||
GAMMA = C*( ALPHA-SIGMA ) - S*OLDGAM
|
||||
print *,"og, a, ga", OLDGAM, ALPHA, GAMMA
|
||||
D( I+1 ) = OLDGAM + ( ALPHA-GAMMA )
|
||||
IF( C.NE.ZERO ) THEN
|
||||
P = ( GAMMA*GAMMA ) / C
|
||||
ELSE
|
||||
P = OLDC*BB
|
||||
END IF
|
||||
print *, "p, gamma = ", p,GAMMA
|
||||
80 CONTINUE
|
||||
*
|
||||
E( L ) = S*P
|
||||
D( L ) = SIGMA + GAMMA
|
||||
|
||||
print *, "inner loop d after"
|
||||
print *, d(1:n)
|
||||
GO TO 50
|
||||
*
|
||||
* Eigenvalue found.
|
||||
*
|
||||
90 CONTINUE
|
||||
D( L ) = P
|
||||
*
|
||||
L = L + 1
|
||||
IF( L.LE.LEND )
|
||||
$ GO TO 50
|
||||
GO TO 150
|
||||
*
|
||||
ELSE
|
||||
*
|
||||
* QR Iteration
|
||||
*
|
||||
* Look for small superdiagonal element.
|
||||
*
|
||||
100 CONTINUE
|
||||
DO 110 M = L, LEND + 1, -1
|
||||
IF( ABS( E( M-1 ) ).LE.EPS2*ABS( D( M )*D( M-1 ) ) )
|
||||
$ GO TO 120
|
||||
110 CONTINUE
|
||||
M = LEND
|
||||
*
|
||||
120 CONTINUE
|
||||
IF( M.GT.LEND )
|
||||
$ E( M-1 ) = ZERO
|
||||
P = D( L )
|
||||
IF( M.EQ.L )
|
||||
$ GO TO 140
|
||||
*
|
||||
* If remaining matrix is 2 by 2, use DLAE2 to compute its
|
||||
* eigenvalues.
|
||||
*
|
||||
IF( M.EQ.L-1 ) THEN
|
||||
RTE = SQRT( E( L-1 ) )
|
||||
CALL DLAE2( D( L ), RTE, D( L-1 ), RT1, RT2 )
|
||||
D( L ) = RT1
|
||||
D( L-1 ) = RT2
|
||||
E( L-1 ) = ZERO
|
||||
L = L - 2
|
||||
IF( L.GE.LEND )
|
||||
$ GO TO 100
|
||||
GO TO 150
|
||||
END IF
|
||||
*
|
||||
IF( JTOT.EQ.NMAXIT )
|
||||
$ GO TO 150
|
||||
JTOT = JTOT + 1
|
||||
*
|
||||
* Form shift.
|
||||
*
|
||||
RTE = SQRT( E( L-1 ) )
|
||||
SIGMA = ( D( L-1 )-P ) / ( TWO*RTE )
|
||||
R = DLAPY2( SIGMA, ONE )
|
||||
SIGMA = P - ( RTE / ( SIGMA+SIGN( R, SIGMA ) ) )
|
||||
*
|
||||
C = ONE
|
||||
S = ZERO
|
||||
GAMMA = D( M ) - SIGMA
|
||||
P = GAMMA*GAMMA
|
||||
*
|
||||
* Inner loop
|
||||
*
|
||||
DO 130 I = M, L - 1
|
||||
BB = E( I )
|
||||
R = P + BB
|
||||
IF( I.NE.M )
|
||||
$ E( I-1 ) = S*R
|
||||
OLDC = C
|
||||
C = P / R
|
||||
S = BB / R
|
||||
OLDGAM = GAMMA
|
||||
ALPHA = D( I+1 )
|
||||
GAMMA = C*( ALPHA-SIGMA ) - S*OLDGAM
|
||||
D( I ) = OLDGAM + ( ALPHA-GAMMA )
|
||||
IF( C.NE.ZERO ) THEN
|
||||
P = ( GAMMA*GAMMA ) / C
|
||||
ELSE
|
||||
P = OLDC*BB
|
||||
END IF
|
||||
130 CONTINUE
|
||||
*
|
||||
E( L-1 ) = S*P
|
||||
D( L ) = SIGMA + GAMMA
|
||||
GO TO 100
|
||||
*
|
||||
* Eigenvalue found.
|
||||
*
|
||||
140 CONTINUE
|
||||
D( L ) = P
|
||||
*
|
||||
L = L - 1
|
||||
IF( L.GE.LEND )
|
||||
$ GO TO 100
|
||||
GO TO 150
|
||||
*
|
||||
END IF
|
||||
*
|
||||
* Undo scaling if necessary
|
||||
*
|
||||
150 CONTINUE
|
||||
IF( ISCALE.EQ.1 )
|
||||
$ CALL DLASCL( 'G', 0, 0, SSFMAX, ANORM, LENDSV-LSV+1, 1,
|
||||
$ D( LSV ), N, INFO )
|
||||
IF( ISCALE.EQ.2 )
|
||||
$ CALL DLASCL( 'G', 0, 0, SSFMIN, ANORM, LENDSV-LSV+1, 1,
|
||||
$ D( LSV ), N, INFO )
|
||||
*
|
||||
* Check for no convergence to an eigenvalue after a total
|
||||
* of N*MAXIT iterations.
|
||||
*
|
||||
IF( JTOT.LT.NMAXIT )
|
||||
$ GO TO 10
|
||||
DO 160 I = 1, N - 1
|
||||
IF( E( I ).NE.ZERO )
|
||||
$ INFO = INFO + 1
|
||||
160 CONTINUE
|
||||
GO TO 180
|
||||
*
|
||||
* Sort eigenvalues in increasing order.
|
||||
*
|
||||
170 CONTINUE
|
||||
CALL DLASRT( 'I', N, D, INFO )
|
||||
*
|
||||
180 CONTINUE
|
||||
RETURN
|
||||
*
|
||||
* End of DSTERF
|
||||
*
|
||||
END
|
125
internal/testdata/dsterftest/lsame.f
vendored
Normal file
125
internal/testdata/dsterftest/lsame.f
vendored
Normal file
@@ -0,0 +1,125 @@
|
||||
*> \brief \b LSAME
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* LOGICAL FUNCTION LSAME( CA, CB )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* CHARACTER CA, CB
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> LSAME returns .TRUE. if CA is the same letter as CB regardless of
|
||||
*> case.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] CA
|
||||
*> \verbatim
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] CB
|
||||
*> \verbatim
|
||||
*> CA and CB specify the single characters to be compared.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date November 2011
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
LOGICAL FUNCTION LSAME( CA, CB )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.0) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* November 2011
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
CHARACTER CA, CB
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC ICHAR
|
||||
* ..
|
||||
* .. Local Scalars ..
|
||||
INTEGER INTA, INTB, ZCODE
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
* Test if the characters are equal
|
||||
*
|
||||
LSAME = CA.EQ.CB
|
||||
IF( LSAME )
|
||||
$ RETURN
|
||||
*
|
||||
* Now test for equivalence if both characters are alphabetic.
|
||||
*
|
||||
ZCODE = ICHAR( 'Z' )
|
||||
*
|
||||
* Use 'Z' rather than 'A' so that ASCII can be detected on Prime
|
||||
* machines, on which ICHAR returns a value with bit 8 set.
|
||||
* ICHAR('A') on Prime machines returns 193 which is the same as
|
||||
* ICHAR('A') on an EBCDIC machine.
|
||||
*
|
||||
INTA = ICHAR( CA )
|
||||
INTB = ICHAR( CB )
|
||||
*
|
||||
IF( ZCODE.EQ.90 .OR. ZCODE.EQ.122 ) THEN
|
||||
*
|
||||
* ASCII is assumed - ZCODE is the ASCII code of either lower or
|
||||
* upper case 'Z'.
|
||||
*
|
||||
IF( INTA.GE.97 .AND. INTA.LE.122 ) INTA = INTA - 32
|
||||
IF( INTB.GE.97 .AND. INTB.LE.122 ) INTB = INTB - 32
|
||||
*
|
||||
ELSE IF( ZCODE.EQ.233 .OR. ZCODE.EQ.169 ) THEN
|
||||
*
|
||||
* EBCDIC is assumed - ZCODE is the EBCDIC code of either lower or
|
||||
* upper case 'Z'.
|
||||
*
|
||||
IF( INTA.GE.129 .AND. INTA.LE.137 .OR.
|
||||
$ INTA.GE.145 .AND. INTA.LE.153 .OR.
|
||||
$ INTA.GE.162 .AND. INTA.LE.169 ) INTA = INTA + 64
|
||||
IF( INTB.GE.129 .AND. INTB.LE.137 .OR.
|
||||
$ INTB.GE.145 .AND. INTB.LE.153 .OR.
|
||||
$ INTB.GE.162 .AND. INTB.LE.169 ) INTB = INTB + 64
|
||||
*
|
||||
ELSE IF( ZCODE.EQ.218 .OR. ZCODE.EQ.250 ) THEN
|
||||
*
|
||||
* ASCII is assumed, on Prime machines - ZCODE is the ASCII code
|
||||
* plus 128 of either lower or upper case 'Z'.
|
||||
*
|
||||
IF( INTA.GE.225 .AND. INTA.LE.250 ) INTA = INTA - 32
|
||||
IF( INTB.GE.225 .AND. INTB.LE.250 ) INTB = INTB - 32
|
||||
END IF
|
||||
LSAME = INTA.EQ.INTB
|
||||
*
|
||||
* RETURN
|
||||
*
|
||||
* End of LSAME
|
||||
*
|
||||
END
|
15
internal/testdata/dsterftest/testdsterf.f90
vendored
Normal file
15
internal/testdata/dsterftest/testdsterf.f90
vendored
Normal file
@@ -0,0 +1,15 @@
|
||||
program testdsterf
|
||||
implicit none
|
||||
integer, parameter :: n = 4
|
||||
real(kind=8), dimension(n) :: d
|
||||
real(kind=8), dimension(n-1) :: e
|
||||
integer :: info,i
|
||||
|
||||
d(1:4) = (/1D+00, 3D+00, 4D+00, 6D+00/)
|
||||
e(1:3) = (/2D+00, 4D+00, 5D+00/)
|
||||
|
||||
call dsterf(n,d,e,info)
|
||||
DO i = 1, n
|
||||
print *, d(i)
|
||||
end do
|
||||
end
|
99
internal/testdata/dsterftest/xerbla.f
vendored
Normal file
99
internal/testdata/dsterftest/xerbla.f
vendored
Normal file
@@ -0,0 +1,99 @@
|
||||
*> \brief \b XERBLA
|
||||
*
|
||||
* =========== DOCUMENTATION ===========
|
||||
*
|
||||
* Online html documentation available at
|
||||
* http://www.netlib.org/lapack/explore-html/
|
||||
*
|
||||
*> \htmlonly
|
||||
*> Download XERBLA + dependencies
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/xerbla.f">
|
||||
*> [TGZ]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/xerbla.f">
|
||||
*> [ZIP]</a>
|
||||
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/xerbla.f">
|
||||
*> [TXT]</a>
|
||||
*> \endhtmlonly
|
||||
*
|
||||
* Definition:
|
||||
* ===========
|
||||
*
|
||||
* SUBROUTINE XERBLA( SRNAME, INFO )
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
* CHARACTER*(*) SRNAME
|
||||
* INTEGER INFO
|
||||
* ..
|
||||
*
|
||||
*
|
||||
*> \par Purpose:
|
||||
* =============
|
||||
*>
|
||||
*> \verbatim
|
||||
*>
|
||||
*> XERBLA is an error handler for the LAPACK routines.
|
||||
*> It is called by an LAPACK routine if an input parameter has an
|
||||
*> invalid value. A message is printed and execution stops.
|
||||
*>
|
||||
*> Installers may consider modifying the STOP statement in order to
|
||||
*> call system-specific exception-handling facilities.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Arguments:
|
||||
* ==========
|
||||
*
|
||||
*> \param[in] SRNAME
|
||||
*> \verbatim
|
||||
*> SRNAME is CHARACTER*(*)
|
||||
*> The name of the routine which called XERBLA.
|
||||
*> \endverbatim
|
||||
*>
|
||||
*> \param[in] INFO
|
||||
*> \verbatim
|
||||
*> INFO is INTEGER
|
||||
*> The position of the invalid parameter in the parameter list
|
||||
*> of the calling routine.
|
||||
*> \endverbatim
|
||||
*
|
||||
* Authors:
|
||||
* ========
|
||||
*
|
||||
*> \author Univ. of Tennessee
|
||||
*> \author Univ. of California Berkeley
|
||||
*> \author Univ. of Colorado Denver
|
||||
*> \author NAG Ltd.
|
||||
*
|
||||
*> \date November 2011
|
||||
*
|
||||
*> \ingroup auxOTHERauxiliary
|
||||
*
|
||||
* =====================================================================
|
||||
SUBROUTINE XERBLA( SRNAME, INFO )
|
||||
*
|
||||
* -- LAPACK auxiliary routine (version 3.4.0) --
|
||||
* -- LAPACK is a software package provided by Univ. of Tennessee, --
|
||||
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
|
||||
* November 2011
|
||||
*
|
||||
* .. Scalar Arguments ..
|
||||
CHARACTER*(*) SRNAME
|
||||
INTEGER INFO
|
||||
* ..
|
||||
*
|
||||
* =====================================================================
|
||||
*
|
||||
* .. Intrinsic Functions ..
|
||||
INTRINSIC LEN_TRIM
|
||||
* ..
|
||||
* .. Executable Statements ..
|
||||
*
|
||||
WRITE( *, FMT = 9999 )SRNAME( 1:LEN_TRIM( SRNAME ) ), INFO
|
||||
*
|
||||
STOP
|
||||
*
|
||||
9999 FORMAT( ' ** On entry to ', A, ' parameter number ', I2, ' had ',
|
||||
$ 'an illegal value' )
|
||||
*
|
||||
* End of XERBLA
|
||||
*
|
||||
END
|
295
native/dsterf.go
Normal file
295
native/dsterf.go
Normal file
@@ -0,0 +1,295 @@
|
||||
// Copyright ©2016 The gonum Authors. All rights reserved.
|
||||
// Use of this source code is governed by a BSD-style
|
||||
// license that can be found in the LICENSE file.
|
||||
|
||||
package native
|
||||
|
||||
import (
|
||||
"math"
|
||||
|
||||
"github.com/gonum/lapack"
|
||||
)
|
||||
|
||||
// Dsterf computes all eigenvalues of a symmetric tridiagonal matrix using the
|
||||
// Pal-Walker-Kahan variant of the QL or QR algorithm.
|
||||
//
|
||||
// d contains the diagonal elements of the tridiagonal matrix on entry, and
|
||||
// contains the eigenvalues in ascending order on exit. d must have length at
|
||||
// least n, or Dsterf will panic.
|
||||
//
|
||||
// e contains the off-digonal elements of the tridiagonal matrix on entry, and is
|
||||
// overwritten during the call to Dsterf. e must have length of at least n-1 or
|
||||
// Dsterf will panic.
|
||||
func (impl Implementation) Dsterf(n int, d, e []float64) (ok bool) {
|
||||
if n < 0 {
|
||||
panic(nLT0)
|
||||
}
|
||||
if n == 0 {
|
||||
return true
|
||||
}
|
||||
if len(d) < n {
|
||||
panic(badD)
|
||||
}
|
||||
if len(e) < n-1 {
|
||||
panic(badE)
|
||||
}
|
||||
|
||||
const (
|
||||
none = 0 // The values are not scaled.
|
||||
down = 1 // The values are scaled below ssfmax threshhold.
|
||||
up = 2 // The values are scaled below ssfmin threshhold.
|
||||
)
|
||||
|
||||
// Determine the unit roundoff for this environment.
|
||||
eps := dlamchE
|
||||
eps2 := eps * eps
|
||||
safmin := dlamchS
|
||||
safmax := 1 / safmin
|
||||
ssfmax := math.Sqrt(safmax) / 3
|
||||
ssfmin := math.Sqrt(safmin) / eps2
|
||||
|
||||
// Compute the eigenvalues of the tridiagonal matrix.
|
||||
maxit := 30
|
||||
nmaxit := n * maxit
|
||||
jtot := 0
|
||||
|
||||
l1 := 0
|
||||
|
||||
// TODO(btracey): Define these closer to use when gotos are removed.
|
||||
var anorm, c, gamma, r, rte, s, sigma float64
|
||||
var iscale, l, lend, lendsv, lsv, m int
|
||||
var el []float64
|
||||
|
||||
// TOOD(btracey): Replace these goto statements with imperative flow control
|
||||
// structures.
|
||||
Ten:
|
||||
if l1 > n-1 {
|
||||
goto OneSeventy
|
||||
}
|
||||
if l1 > 0 {
|
||||
e[l1-1] = 0
|
||||
}
|
||||
for m = l1; m < n-1; m++ {
|
||||
if math.Abs(e[m]) <= math.Sqrt(math.Abs(d[m]))*math.Sqrt(math.Abs(d[m+1]))*eps {
|
||||
e[m] = 0
|
||||
goto Thirty
|
||||
}
|
||||
}
|
||||
m = n - 1
|
||||
|
||||
Thirty:
|
||||
l = l1
|
||||
lsv = l
|
||||
lend = m
|
||||
lendsv = lend
|
||||
l1 = m + 1
|
||||
if lend == 0 {
|
||||
goto Ten
|
||||
}
|
||||
|
||||
// Scale submatrix in rows and columns l to lend.
|
||||
anorm = impl.Dlanst(lapack.MaxAbs, lend-l+1, d[l:], e[l:])
|
||||
iscale = none
|
||||
if anorm == 0 {
|
||||
goto Ten
|
||||
}
|
||||
if anorm > ssfmax {
|
||||
iscale = down
|
||||
impl.Dlascl(lapack.General, 0, 0, anorm, ssfmax, lend-l+1, 1, d[l:], n)
|
||||
impl.Dlascl(lapack.General, 0, 0, anorm, ssfmax, lend-l, 1, e[l:], n)
|
||||
} else if anorm < ssfmin {
|
||||
iscale = up
|
||||
impl.Dlascl(lapack.General, 0, 0, anorm, ssfmin, lend-l+1, 1, d[l:], n)
|
||||
impl.Dlascl(lapack.General, 0, 0, anorm, ssfmin, lend-l, 1, e[l:], n)
|
||||
}
|
||||
|
||||
el = e[l:lend]
|
||||
for i, v := range el {
|
||||
el[i] *= v
|
||||
}
|
||||
|
||||
// Choose between QL and QR iteration.
|
||||
if math.Abs(d[lend]) < math.Abs(d[l]) {
|
||||
lend = lsv
|
||||
l = lendsv
|
||||
}
|
||||
if lend >= l {
|
||||
// QL Iteration.
|
||||
// Look for small subdiagonal element.
|
||||
Fifty:
|
||||
if l != lend {
|
||||
for m = l; m < lend; m++ {
|
||||
if math.Abs(e[m]) <= eps2*(math.Abs(d[m]*d[m+1])) {
|
||||
goto Seventy
|
||||
}
|
||||
}
|
||||
}
|
||||
m = lend
|
||||
Seventy:
|
||||
if m < lend {
|
||||
e[m] = 0
|
||||
}
|
||||
p := d[l]
|
||||
if m == l {
|
||||
goto Ninety
|
||||
}
|
||||
// If remaining matrix is 2 by 2, use Dlae2 to compute its eigenvalues.
|
||||
if m == l+1 {
|
||||
rte = math.Sqrt(e[l])
|
||||
d[l], d[l+1] = impl.Dlae2(d[l], rte, d[l+1])
|
||||
e[l] = 0
|
||||
l += 2
|
||||
if l <= lend {
|
||||
goto Fifty
|
||||
}
|
||||
goto OneFifty
|
||||
}
|
||||
if jtot == nmaxit {
|
||||
goto OneFifty
|
||||
}
|
||||
jtot++
|
||||
|
||||
// Form shift.
|
||||
rte = math.Sqrt(e[l])
|
||||
sigma = (d[l+1] - p) / (2 * rte)
|
||||
r = impl.Dlapy2(sigma, 1)
|
||||
sigma = p - (rte / (sigma + math.Copysign(r, sigma)))
|
||||
|
||||
c = 1
|
||||
s = 0
|
||||
gamma = d[m] - sigma
|
||||
p = gamma * gamma
|
||||
|
||||
// Inner loop.
|
||||
for i := m - 1; i >= l; i-- {
|
||||
bb := e[i]
|
||||
r := p + bb
|
||||
if i != m-1 {
|
||||
e[i+1] = s * r
|
||||
}
|
||||
oldc := c
|
||||
c = p / r
|
||||
s = bb / r
|
||||
oldgam := gamma
|
||||
alpha := d[i]
|
||||
gamma = c*(alpha-sigma) - s*oldgam
|
||||
d[i+1] = oldgam + (alpha - gamma)
|
||||
if c != 0 {
|
||||
p = (gamma * gamma) / c
|
||||
} else {
|
||||
p = oldc * bb
|
||||
}
|
||||
}
|
||||
e[l] = s * p
|
||||
d[l] = sigma + gamma
|
||||
goto Fifty
|
||||
|
||||
Ninety:
|
||||
// Eigenvalue found.
|
||||
d[l] = p
|
||||
l++
|
||||
if l <= lend {
|
||||
goto Fifty
|
||||
}
|
||||
goto OneFifty
|
||||
} else {
|
||||
OneHundred:
|
||||
// QR Iteration.
|
||||
// Look for small superdiagonal element.
|
||||
for m = l; m >= lend+1; m-- {
|
||||
if math.Abs(e[m-1]) <= eps2*math.Abs(d[m]*d[m-1]) {
|
||||
goto OneTwenty
|
||||
}
|
||||
}
|
||||
m = lend
|
||||
OneTwenty:
|
||||
if m > lend {
|
||||
e[m-1] = 0
|
||||
}
|
||||
p := d[l]
|
||||
if m == l {
|
||||
goto OneFourty
|
||||
}
|
||||
|
||||
// If remaining matrix is 2 by 2, use Dlae2 to compute its eigenvalues.
|
||||
if m == l-1 {
|
||||
rte = math.Sqrt(e[l-1])
|
||||
d[l], d[l-1] = impl.Dlae2(d[l], rte, d[l-1])
|
||||
e[l-1] = 0
|
||||
l -= 2
|
||||
if l >= lend {
|
||||
goto OneHundred
|
||||
}
|
||||
goto OneFifty
|
||||
}
|
||||
if jtot == nmaxit {
|
||||
goto OneFifty
|
||||
}
|
||||
jtot++
|
||||
|
||||
// Form shift.
|
||||
rte = math.Sqrt(e[l-1])
|
||||
sigma = (d[l-1] - p) / (2 * rte)
|
||||
r = impl.Dlapy2(sigma, 1)
|
||||
sigma = p - (rte / (sigma + math.Copysign(r, sigma)))
|
||||
|
||||
c = 1
|
||||
s = 0
|
||||
gamma = d[m] - sigma
|
||||
p = gamma * gamma
|
||||
|
||||
// Inner loop.
|
||||
for i := m; i < l; i++ {
|
||||
bb := e[i]
|
||||
r := p + bb
|
||||
if i != m {
|
||||
e[i-1] = s * r
|
||||
}
|
||||
oldc := c
|
||||
c = p / r
|
||||
s = bb / r
|
||||
oldgam := gamma
|
||||
alpha := d[i+1]
|
||||
gamma = c*(alpha-sigma) - s*oldgam
|
||||
d[i] = oldgam + alpha - gamma
|
||||
if c != 0 {
|
||||
p = (gamma * gamma) / c
|
||||
} else {
|
||||
p = oldc * bb
|
||||
}
|
||||
}
|
||||
e[l-1] = s * p
|
||||
d[l] = sigma + gamma
|
||||
goto OneHundred
|
||||
|
||||
OneFourty:
|
||||
// Eigenvalue found.
|
||||
d[l] = p
|
||||
l--
|
||||
if l >= lend {
|
||||
goto OneHundred
|
||||
}
|
||||
goto OneFifty
|
||||
}
|
||||
OneFifty:
|
||||
// Undo scaling if necessary
|
||||
switch iscale {
|
||||
case down:
|
||||
impl.Dlascl(lapack.General, 0, 0, ssfmax, anorm, lendsv-lsv+1, 1, d[lsv:], n)
|
||||
case up:
|
||||
impl.Dlascl(lapack.General, 0, 0, ssfmin, anorm, lendsv-lsv+1, 1, d[lsv:], n)
|
||||
}
|
||||
|
||||
// Check for no convergence to an eigenvalue after a total of n*maxit iterations.
|
||||
if jtot < nmaxit {
|
||||
goto Ten
|
||||
}
|
||||
for _, v := range e[:n-1] {
|
||||
if v != 0 {
|
||||
return false
|
||||
}
|
||||
}
|
||||
OneSeventy:
|
||||
impl.Dlasrt(lapack.SortIncreasing, n, d)
|
||||
return true
|
||||
}
|
@@ -208,6 +208,10 @@ func TestDrscl(t *testing.T) {
|
||||
testlapack.DrsclTest(t, impl)
|
||||
}
|
||||
|
||||
func TestDsterf(t *testing.T) {
|
||||
testlapack.DsterfTest(t, impl)
|
||||
}
|
||||
|
||||
func TestDsytd2(t *testing.T) {
|
||||
testlapack.Dsytd2Test(t, impl)
|
||||
}
|
||||
|
125
testlapack/dsterf.go
Normal file
125
testlapack/dsterf.go
Normal file
@@ -0,0 +1,125 @@
|
||||
// Copyright ©2016 The gonum Authors. All rights reserved.
|
||||
// Use of this source code is governed by a BSD-style
|
||||
// license that can be found in the LICENSE file.
|
||||
|
||||
package testlapack
|
||||
|
||||
import (
|
||||
"math"
|
||||
"math/rand"
|
||||
"sort"
|
||||
"testing"
|
||||
|
||||
"github.com/gonum/floats"
|
||||
)
|
||||
|
||||
type Dsterfer interface {
|
||||
Dgetrfer
|
||||
Dsterf(n int, d, e []float64) (ok bool)
|
||||
}
|
||||
|
||||
func DsterfTest(t *testing.T, impl Dsterfer) {
|
||||
// Hand coded tests.
|
||||
for cas, test := range []struct {
|
||||
d []float64
|
||||
e []float64
|
||||
n int
|
||||
|
||||
ans []float64
|
||||
}{
|
||||
// Computed from Fortran code.
|
||||
{
|
||||
d: []float64{1, 3, 4, 6},
|
||||
e: []float64{2, 4, 5},
|
||||
n: 4,
|
||||
ans: []float64{11.046227528488854, 4.795922173417400, -2.546379458290125, 0.704229756383872},
|
||||
},
|
||||
} {
|
||||
n := test.n
|
||||
d := make([]float64, len(test.d))
|
||||
copy(d, test.d)
|
||||
e := make([]float64, len(test.e))
|
||||
copy(e, test.e)
|
||||
ok := impl.Dsterf(n, d, e)
|
||||
if !ok {
|
||||
t.Errorf("Case %d, Eigenvalue decomposition failed", cas)
|
||||
continue
|
||||
}
|
||||
ans := make([]float64, len(test.ans))
|
||||
copy(ans, test.ans)
|
||||
sort.Float64s(ans)
|
||||
if !floats.EqualApprox(ans, d, 1e-10) {
|
||||
t.Errorf("eigenvalue mismatch")
|
||||
}
|
||||
}
|
||||
|
||||
// Probabilistic tests.
|
||||
for _, n := range []int{4, 6, 10} {
|
||||
for cas := 0; cas < 10; cas++ {
|
||||
d := make([]float64, n)
|
||||
for i := range d {
|
||||
d[i] = rand.NormFloat64()
|
||||
}
|
||||
dCopy := make([]float64, len(d))
|
||||
copy(dCopy, d)
|
||||
e := make([]float64, n-1)
|
||||
for i := range e {
|
||||
e[i] = rand.NormFloat64()
|
||||
}
|
||||
eCopy := make([]float64, len(e))
|
||||
copy(eCopy, e)
|
||||
|
||||
ok := impl.Dsterf(n, d, e)
|
||||
if !ok {
|
||||
t.Errorf("Eigenvalue decomposition failed")
|
||||
continue
|
||||
}
|
||||
|
||||
// Test that the eigenvalues are sorted.
|
||||
if !sort.Float64sAreSorted(d) {
|
||||
t.Errorf("Values are not sorted")
|
||||
}
|
||||
|
||||
// Construct original tridagional matrix.
|
||||
lda := n
|
||||
a := make([]float64, n*lda)
|
||||
for i := 0; i < n; i++ {
|
||||
a[i*lda+i] = dCopy[i]
|
||||
if i != n-1 {
|
||||
a[i*lda+i+1] = eCopy[i]
|
||||
a[(i+1)*lda+i] = eCopy[i]
|
||||
}
|
||||
}
|
||||
|
||||
asub := make([]float64, len(a))
|
||||
ipiv := make([]int, n)
|
||||
|
||||
// Test that they are actually eigenvalues by computing the
|
||||
// determinant of A - λI.
|
||||
// TODO(btracey): Replace this test with a more numerically stable
|
||||
// test.
|
||||
for _, lambda := range d {
|
||||
copy(asub, a)
|
||||
for i := 0; i < n; i++ {
|
||||
asub[i*lda+i] -= lambda
|
||||
}
|
||||
|
||||
// Compute LU.
|
||||
ok := impl.Dgetrf(n, n, asub, lda, ipiv)
|
||||
if !ok {
|
||||
// Definitely singular.
|
||||
continue
|
||||
}
|
||||
// Compute determinant.
|
||||
var logdet float64
|
||||
for i := 0; i < n; i++ {
|
||||
v := asub[i*lda+i]
|
||||
logdet += math.Log(math.Abs(v))
|
||||
}
|
||||
if math.Exp(logdet) > 2 {
|
||||
t.Errorf("Incorrect singular value. n = %d, cas = %d, det = %v", n, cas, math.Exp(logdet))
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
||||
}
|
Reference in New Issue
Block a user