--- rpl/lapack/lapack/dgsvj1.f 2012/07/31 11:06:35 1.9 +++ rpl/lapack/lapack/dgsvj1.f 2023/08/07 08:38:51 1.22 @@ -1,26 +1,26 @@ -*> \brief \b DGSVJ1 +*> \brief \b DGSVJ1 pre-processor for the routine dgesvj, applies Jacobi rotations targeting only particular pivots. * * =========== 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 DGSVJ1 + dependencies -*> -*> [TGZ] -*> -*> [ZIP] -*> +*> Download DGSVJ1 + dependencies +*> +*> [TGZ] +*> +*> [ZIP] +*> *> [TXT] -*> \endhtmlonly +*> \endhtmlonly * * Definition: * =========== * * SUBROUTINE DGSVJ1( JOBV, M, N, N1, A, LDA, D, SVA, MV, V, LDV, * EPS, SFMIN, TOL, NSWEEP, WORK, LWORK, INFO ) -* +* * .. Scalar Arguments .. * DOUBLE PRECISION EPS, SFMIN, TOL * INTEGER INFO, LDA, LDV, LWORK, M, MV, N, N1, NSWEEP @@ -30,17 +30,17 @@ * DOUBLE PRECISION A( LDA, * ), D( N ), SVA( N ), V( LDV, * ), * $ WORK( LWORK ) * .. -* +* * *> \par Purpose: * ============= *> *> \verbatim *> -*> DGSVJ1 is called from SGESVJ as a pre-processor and that is its main -*> purpose. It applies Jacobi rotations in the same way as SGESVJ does, but +*> DGSVJ1 is called from DGESVJ as a pre-processor and that is its main +*> purpose. It applies Jacobi rotations in the same way as DGESVJ does, but *> it targets only particular pivots and it does not check convergence -*> (stopping criterion). Few tunning parameters (marked by [TP]) are +*> (stopping criterion). Few tuning parameters (marked by [TP]) are *> available for the implementer. *> *> Further Details @@ -61,7 +61,7 @@ *> In terms of the columns of A, the first N1 columns are rotated 'against' *> the remaining N-N1 columns, trying to increase the angle between the *> corresponding subspaces. The off-diagonal block is N1-by(N-N1) and it is -*> tiled using quadratic tiles of side KBL. Here, KBL is a tunning parmeter. +*> tiled using quadratic tiles of side KBL. Here, KBL is a tuning parameter. *> The number of sweeps is given in NSWEEP and the orthogonality threshold *> is given in TOL. *> \endverbatim @@ -147,27 +147,27 @@ *> \param[in] MV *> \verbatim *> MV is INTEGER -*> If JOBV .EQ. 'A', then MV rows of V are post-multipled by a -*> sequence of Jacobi rotations. -*> If JOBV = 'N', then MV is not referenced. +*> 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 *> *> \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 -*> sequence of Jacobi rotations. -*> If JOBV .EQ. 'A' then MV rows of V are post-multipled by a -*> sequence of Jacobi rotations. -*> If JOBV = 'N', then V is not referenced. +*> If JOBV = 'V', then N rows of V are post-multipled by a +*> sequence of Jacobi rotations. +*> 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 *> *> \param[in] LDV *> \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 @@ -187,7 +187,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 @@ -205,25 +205,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 2011 +*> \author Univ. of Tennessee +*> \author Univ. of California Berkeley +*> \author Univ. of Colorado Denver +*> \author NAG Ltd. * *> \ingroup doubleOTHERcomputational * @@ -236,10 +234,9 @@ SUBROUTINE DGSVJ1( JOBV, M, N, N1, A, LDA, D, SVA, MV, V, LDV, $ EPS, SFMIN, TOL, NSWEEP, WORK, LWORK, INFO ) * -* -- LAPACK computational routine (version 3.4.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 2011 * * .. Scalar Arguments .. DOUBLE PRECISION EPS, SFMIN, TOL @@ -271,7 +268,7 @@ DOUBLE PRECISION FASTR( 5 ) * .. * .. Intrinsic Functions .. - INTRINSIC DABS, DMAX1, DBLE, MIN0, DSIGN, DSQRT + INTRINSIC DABS, MAX, DBLE, MIN, DSIGN, DSQRT * .. * .. External Functions .. DOUBLE PRECISION DDOT, DNRM2 @@ -280,7 +277,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 .. * @@ -300,7 +298,7 @@ INFO = -6 ELSE IF( ( RSVEC.OR.APPLV ) .AND. ( MV.LT.0 ) ) THEN INFO = -9 - ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR. + ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR. $ ( APPLV.AND.( LDV.LT.MV ) ) ) THEN INFO = -11 ELSE IF( TOL.LE.EPS ) THEN @@ -345,7 +343,7 @@ * * .. Row-cyclic pivot strategy with de Rijk's pivoting .. * - KBL = MIN0( 8, N ) + KBL = MIN( 8, N ) NBLR = N1 / KBL IF( ( NBLR*KBL ).NE.N1 )NBLR = NBLR + 1 @@ -356,7 +354,7 @@ BLSKIP = ( KBL**2 ) + 1 *[TP] BLKSKIP is a tuning parameter that depends on SWBAND and KBL. - ROWSKIP = MIN0( 5, KBL ) + ROWSKIP = MIN( 5, KBL ) *[TP] ROWSKIP is a tuning parameter. SWBAND = 0 *[TP] SWBAND is a tuning parameter. It is meaningful and effective @@ -399,7 +397,7 @@ * doing the block at ( ibr, jbc ) IJBLSK = 0 - DO 2100 p = igl, MIN0( igl+KBL-1, N1 ) + DO 2100 p = igl, MIN( igl+KBL-1, N1 ) AAPP = SVA( p ) @@ -407,7 +405,7 @@ PSKIPPED = 0 - DO 2200 q = jgl, MIN0( jgl+KBL-1, N ) + DO 2200 q = jgl, MIN( jgl+KBL-1, N ) * AAQQ = SVA( q ) @@ -454,7 +452,7 @@ END IF END IF - MXAAPQ = DMAX1( MXAAPQ, DABS( AAPQ ) ) + MXAAPQ = MAX( MXAAPQ, DABS( AAPQ ) ) * TO rotate or NOT to rotate, THAT is the question ... * @@ -481,11 +479,11 @@ $ V( 1, p ), 1, $ V( 1, q ), 1, $ FASTR ) - SVA( q ) = AAQQ*DSQRT( DMAX1( ZERO, + SVA( q ) = AAQQ*DSQRT( MAX( ZERO, $ ONE+T*APOAQ*AAPQ ) ) - AAPP = AAPP*DSQRT( DMAX1( ZERO, + AAPP = AAPP*DSQRT( MAX( ZERO, $ ONE-T*AQOAP*AAPQ ) ) - MXSINJ = DMAX1( MXSINJ, DABS( T ) ) + MXSINJ = MAX( MXSINJ, DABS( T ) ) ELSE * * .. choose correct signum for THETA and rotate @@ -496,10 +494,10 @@ $ DSQRT( ONE+THETA*THETA ) ) CS = DSQRT( ONE / ( ONE+T*T ) ) SN = T*CS - MXSINJ = DMAX1( MXSINJ, DABS( SN ) ) - SVA( q ) = AAQQ*DSQRT( DMAX1( ZERO, + MXSINJ = MAX( MXSINJ, DABS( SN ) ) + SVA( q ) = AAQQ*DSQRT( MAX( ZERO, $ ONE+T*APOAQ*AAPQ ) ) - AAPP = AAPP*DSQRT( DMAX1( ZERO, + AAPP = AAPP*DSQRT( MAX( ZERO, $ ONE-T*AQOAP*AAPQ ) ) APOAQ = D( p ) / D( q ) @@ -614,9 +612,9 @@ CALL DLASCL( 'G', 0, 0, ONE, AAQQ, $ M, 1, A( 1, q ), LDA, $ IERR ) - SVA( q ) = AAQQ*DSQRT( DMAX1( ZERO, + SVA( q ) = AAQQ*DSQRT( MAX( ZERO, $ ONE-AAPQ*AAPQ ) ) - MXSINJ = DMAX1( MXSINJ, SFMIN ) + MXSINJ = MAX( MXSINJ, SFMIN ) ELSE CALL DCOPY( M, A( 1, q ), 1, WORK, $ 1 ) @@ -631,9 +629,9 @@ CALL DLASCL( 'G', 0, 0, ONE, AAPP, $ M, 1, A( 1, p ), LDA, $ IERR ) - SVA( p ) = AAPP*DSQRT( DMAX1( ZERO, + SVA( p ) = AAPP*DSQRT( MAX( ZERO, $ ONE-AAPQ*AAPQ ) ) - MXSINJ = DMAX1( MXSINJ, SFMIN ) + MXSINJ = MAX( MXSINJ, SFMIN ) END IF END IF * END IF ROTOK THEN ... ELSE @@ -704,7 +702,7 @@ * ELSE IF( AAPP.EQ.ZERO )NOTROT = NOTROT + - $ MIN0( jgl+KBL-1, N ) - jgl + 1 + $ MIN( jgl+KBL-1, N ) - jgl + 1 IF( AAPP.LT.ZERO )NOTROT = 0 *** IF ( NOTROT .GE. EMPTSW ) GO TO 2011 END IF @@ -715,7 +713,7 @@ * end of the jbc-loop 2011 CONTINUE *2011 bailed out of the jbc-loop - DO 2012 p = igl, MIN0( igl+KBL-1, N ) + DO 2012 p = igl, MIN( igl+KBL-1, N ) SVA( p ) = DABS( SVA( p ) ) 2012 CONTINUE *** IF ( NOTROT .GE. EMPTSW ) GO TO 1994