1 *> \brief \b ZDRSCL multiplies a vector by the reciprocal of a real scalar.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZDRSCL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zdrscl.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zdrscl.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zdrscl.f">
21 * SUBROUTINE ZDRSCL( N, SA, SX, INCX )
23 * .. Scalar Arguments ..
27 * .. Array Arguments ..
37 *> ZDRSCL multiplies an n-element complex vector x by the real scalar
38 *> 1/a. This is done without overflow or underflow as long as
39 *> the final result x/a does not overflow or underflow.
48 *> The number of components of the vector x.
53 *> SA is DOUBLE PRECISION
54 *> The scalar a which is used to divide each component of x.
55 *> SA must be >= 0, or the subroutine will divide by zero.
60 *> SX is COMPLEX*16 array, dimension
61 *> (1+(N-1)*abs(INCX))
62 *> The n-element vector x.
68 *> The increment between successive values of the vector SX.
69 *> > 0: SX(1) = X(1) and SX(1+(i-1)*INCX) = x(i), 1< i<= n
75 *> \author Univ. of Tennessee
76 *> \author Univ. of California Berkeley
77 *> \author Univ. of Colorado Denver
80 *> \date September 2012
82 *> \ingroup complex16OTHERauxiliary
84 * =====================================================================
85 SUBROUTINE ZDRSCL( N, SA, SX, INCX )
87 * -- LAPACK auxiliary routine (version 3.4.2) --
88 * -- LAPACK is a software package provided by Univ. of Tennessee, --
89 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
92 * .. Scalar Arguments ..
96 * .. Array Arguments ..
100 * =====================================================================
103 DOUBLE PRECISION ZERO, ONE
104 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
106 * .. Local Scalars ..
108 DOUBLE PRECISION BIGNUM, CDEN, CDEN1, CNUM, CNUM1, MUL, SMLNUM
110 * .. External Functions ..
111 DOUBLE PRECISION DLAMCH
114 * .. External Subroutines ..
115 EXTERNAL DLABAD, ZDSCAL
117 * .. Intrinsic Functions ..
120 * .. Executable Statements ..
122 * Quick return if possible
127 * Get machine parameters
129 SMLNUM = DLAMCH( 'S' )
130 BIGNUM = ONE / SMLNUM
131 CALL DLABAD( SMLNUM, BIGNUM )
133 * Initialize the denominator to SA and the numerator to 1.
140 CNUM1 = CNUM / BIGNUM
141 IF( ABS( CDEN1 ).GT.ABS( CNUM ) .AND. CNUM.NE.ZERO ) THEN
143 * Pre-multiply X by SMLNUM if CDEN is large compared to CNUM.
148 ELSE IF( ABS( CNUM1 ).GT.ABS( CDEN ) ) THEN
150 * Pre-multiply X by BIGNUM if CDEN is small compared to CNUM.
157 * Multiply X by CNUM / CDEN and return.
163 * Scale the vector X by MUL
165 CALL ZDSCAL( N, MUL, SX, INCX )