--- rpl/lapack/lapack/dgsvj0.f 2016/08/27 15:34:24 1.15 +++ rpl/lapack/lapack/dgsvj0.f 2023/08/07 08:38:51 1.21 @@ -2,25 +2,25 @@ * * =========== DOCUMENTATION =========== * -* Online html documentation available at -* http://www.netlib.org/lapack/explore-html/ +* Online html documentation available at +* http://www.netlib.org/lapack/explore-html/ * *> \htmlonly -*> Download DGSVJ0 + dependencies -*> -*> [TGZ] -*> -*> [ZIP] -*> +*> Download DGSVJ0 + dependencies +*> +*> [TGZ] +*> +*> [ZIP] +*> *> [TXT] -*> \endhtmlonly +*> \endhtmlonly * * Definition: * =========== * * SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS, * SFMIN, TOL, NSWEEP, WORK, LWORK, INFO ) -* +* * .. Scalar Arguments .. * INTEGER INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP * DOUBLE PRECISION EPS, SFMIN, TOL @@ -30,7 +30,7 @@ * DOUBLE PRECISION A( LDA, * ), SVA( N ), D( N ), V( LDV, * ), * $ WORK( LWORK ) * .. -* +* * *> \par Purpose: * ============= @@ -117,7 +117,7 @@ *> \param[in] MV *> \verbatim *> MV is INTEGER -*> If JOBV .EQ. 'A', then MV rows of V are post-multipled by a +*> If JOBV = 'A', then MV rows of V are post-multipled by a *> sequence of Jacobi rotations. *> If JOBV = 'N', then MV is not referenced. *> \endverbatim @@ -125,9 +125,9 @@ *> \param[in,out] V *> \verbatim *> V is DOUBLE PRECISION array, dimension (LDV,N) -*> If JOBV .EQ. 'V' then N rows of V are post-multipled by a +*> If JOBV = 'V' then N rows of V are post-multipled by a *> sequence of Jacobi rotations. -*> If JOBV .EQ. 'A' then MV rows of V are post-multipled by a +*> If JOBV = 'A' then MV rows of V are post-multipled by a *> sequence of Jacobi rotations. *> If JOBV = 'N', then V is not referenced. *> \endverbatim @@ -136,8 +136,8 @@ *> \verbatim *> LDV is INTEGER *> The leading dimension of the array V, LDV >= 1. -*> If JOBV = 'V', LDV .GE. N. -*> If JOBV = 'A', LDV .GE. MV. +*> If JOBV = 'V', LDV >= N. +*> If JOBV = 'A', LDV >= MV. *> \endverbatim *> *> \param[in] EPS @@ -157,7 +157,7 @@ *> TOL is DOUBLE PRECISION *> TOL is the threshold for Jacobi rotations. For a pair *> A(:,p), A(:,q) of pivot columns, the Jacobi rotation is -*> applied only if DABS(COS(angle(A(:,p),A(:,q)))) .GT. TOL. +*> applied only if DABS(COS(angle(A(:,p),A(:,q)))) > TOL. *> \endverbatim *> *> \param[in] NSWEEP @@ -175,25 +175,23 @@ *> \param[in] LWORK *> \verbatim *> LWORK is INTEGER -*> LWORK is the dimension of WORK. LWORK .GE. M. +*> LWORK is the dimension of WORK. LWORK >= M. *> \endverbatim *> *> \param[out] INFO *> \verbatim *> INFO is INTEGER -*> = 0 : successful exit. -*> < 0 : if INFO = -i, then the i-th argument had an illegal value +*> = 0: successful exit. +*> < 0: if INFO = -i, then 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 November 2015 +*> \author Univ. of Tennessee +*> \author Univ. of California Berkeley +*> \author Univ. of Colorado Denver +*> \author NAG Ltd. * *> \ingroup doubleOTHERcomputational * @@ -218,10 +216,9 @@ SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS, $ SFMIN, TOL, NSWEEP, WORK, LWORK, INFO ) * -* -- LAPACK computational routine (version 3.6.0) -- +* -- LAPACK computational routine -- * -- LAPACK is a software package provided by Univ. of Tennessee, -- * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- -* November 2015 * * .. Scalar Arguments .. INTEGER INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP @@ -262,7 +259,8 @@ EXTERNAL IDAMAX, LSAME, DDOT, DNRM2 * .. * .. External Subroutines .. - EXTERNAL DAXPY, DCOPY, DLASCL, DLASSQ, DROTM, DSWAP + EXTERNAL DAXPY, DCOPY, DLASCL, DLASSQ, DROTM, DSWAP, + $ XERBLA * .. * .. Executable Statements .. * @@ -280,7 +278,7 @@ INFO = -5 ELSE IF( ( RSVEC.OR.APPLV ) .AND. ( MV.LT.0 ) ) THEN INFO = -8 - ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR. + ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR. $ ( APPLV.AND.( LDV.LT.MV ) ) ) THEN INFO = -10 ELSE IF( TOL.LE.EPS ) THEN @@ -391,7 +389,7 @@ * Some BLAS implementations compute DNRM2(M,A(1,p),1) * as DSQRT(DDOT(M,A(1,p),1,A(1,p),1)), which may result in * overflow for ||A(:,p)||_2 > DSQRT(overflow_threshold), and -* undeflow for ||A(:,p)||_2 < DSQRT(underflow_threshold). +* underflow for ||A(:,p)||_2 < DSQRT(underflow_threshold). * Hence, DNRM2 cannot be trusted, not even in the case when * the true norm is far from the under(over)flow boundaries. * If properly implemented DNRM2 is available, the IF-THEN-ELSE @@ -485,7 +483,7 @@ $ FASTR ) SVA( q ) = AAQQ*DSQRT( MAX( ZERO, $ ONE+T*APOAQ*AAPQ ) ) - AAPP = AAPP*DSQRT( MAX( ZERO, + AAPP = AAPP*DSQRT( MAX( ZERO, $ ONE-T*AQOAP*AAPQ ) ) MXSINJ = MAX( MXSINJ, DABS( T ) ) * @@ -800,7 +798,7 @@ MXSINJ = MAX( MXSINJ, DABS( SN ) ) SVA( q ) = AAQQ*DSQRT( MAX( ZERO, $ ONE+T*APOAQ*AAPQ ) ) - AAPP = AAPP*DSQRT( MAX( ZERO, + AAPP = AAPP*DSQRT( MAX( ZERO, $ ONE-T*AQOAP*AAPQ ) ) * APOAQ = D( p ) / D( q ) @@ -1044,7 +1042,7 @@ 1993 CONTINUE * end i=1:NSWEEP loop -* #:) Reaching this point means that the procedure has comleted the given +* #:) Reaching this point means that the procedure has completed the given * number of iterations. INFO = NSWEEP - 1 GO TO 1995