PLASMA  2.4.5
PLASMA - Parallel Linear Algebra for Scalable Multi-core Architectures
 All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Groups
dlatrs.f
Go to the documentation of this file.
1  SUBROUTINE dlatrs( UPLO, TRANS, DIAG, NORMIN, N, A, LDA, X, SCALE,
2  $ cnorm, info )
3 *
4 * -- LAPACK auxiliary routine (version 3.2) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9  CHARACTER diag, normin, trans, uplo
10  INTEGER info, lda, n
11  DOUBLE PRECISION scale
12 * ..
13 * .. Array Arguments ..
14  DOUBLE PRECISION a( lda, * ), cnorm( * ), x( * )
15 * ..
16 *
17 * Purpose
18 * =======
19 *
20 * DLATRS solves one of the triangular systems
21 *
22 * A *x = s*b or A'*x = s*b
23 *
24 * with scaling to prevent overflow. Here A is an upper or lower
25 * triangular matrix, A' denotes the transpose of A, x and b are
26 * n-element vectors, and s is a scaling factor, usually less than
27 * or equal to 1, chosen so that the components of x will be less than
28 * the overflow threshold. If the unscaled problem will not cause
29 * overflow, the Level 2 BLAS routine DTRSV is called. If the matrix A
30 * is singular (A(j,j) = 0 for some j), then s is set to 0 and a
31 * non-trivial solution to A*x = 0 is returned.
32 *
33 * Arguments
34 * =========
35 *
36 * UPLO (input) CHARACTER*1
37 * Specifies whether the matrix A is upper or lower triangular.
38 * = 'U': Upper triangular
39 * = 'L': Lower triangular
40 *
41 * TRANS (input) CHARACTER*1
42 * Specifies the operation applied to A.
43 * = 'N': Solve A * x = s*b (No transpose)
44 * = 'T': Solve A'* x = s*b (Transpose)
45 * = 'C': Solve A'* x = s*b (Conjugate transpose = Transpose)
46 *
47 * DIAG (input) CHARACTER*1
48 * Specifies whether or not the matrix A is unit triangular.
49 * = 'N': Non-unit triangular
50 * = 'U': Unit triangular
51 *
52 * NORMIN (input) CHARACTER*1
53 * Specifies whether CNORM has been set or not.
54 * = 'Y': CNORM contains the column norms on entry
55 * = 'N': CNORM is not set on entry. On exit, the norms will
56 * be computed and stored in CNORM.
57 *
58 * N (input) INTEGER
59 * The order of the matrix A. N >= 0.
60 *
61 * A (input) DOUBLE PRECISION array, dimension (LDA,N)
62 * The triangular matrix A. If UPLO = 'U', the leading n by n
63 * upper triangular part of the array A contains the upper
64 * triangular matrix, and the strictly lower triangular part of
65 * A is not referenced. If UPLO = 'L', the leading n by n lower
66 * triangular part of the array A contains the lower triangular
67 * matrix, and the strictly upper triangular part of A is not
68 * referenced. If DIAG = 'U', the diagonal elements of A are
69 * also not referenced and are assumed to be 1.
70 *
71 * LDA (input) INTEGER
72 * The leading dimension of the array A. LDA >= max (1,N).
73 *
74 * X (input/output) DOUBLE PRECISION array, dimension (N)
75 * On entry, the right hand side b of the triangular system.
76 * On exit, X is overwritten by the solution vector x.
77 *
78 * SCALE (output) DOUBLE PRECISION
79 * The scaling factor s for the triangular system
80 * A * x = s*b or A'* x = s*b.
81 * If SCALE = 0, the matrix A is singular or badly scaled, and
82 * the vector x is an exact or approximate solution to A*x = 0.
83 *
84 * CNORM (input or output) DOUBLE PRECISION array, dimension (N)
85 *
86 * If NORMIN = 'Y', CNORM is an input argument and CNORM(j)
87 * contains the norm of the off-diagonal part of the j-th column
88 * of A. If TRANS = 'N', CNORM(j) must be greater than or equal
89 * to the infinity-norm, and if TRANS = 'T' or 'C', CNORM(j)
90 * must be greater than or equal to the 1-norm.
91 *
92 * If NORMIN = 'N', CNORM is an output argument and CNORM(j)
93 * returns the 1-norm of the offdiagonal part of the j-th column
94 * of A.
95 *
96 * INFO (output) INTEGER
97 * = 0: successful exit
98 * < 0: if INFO = -k, the k-th argument had an illegal value
99 *
100 * Further Details
101 * ======= =======
102 *
103 * A rough bound on x is computed; if that is less than overflow, DTRSV
104 * is called, otherwise, specific code is used which checks for possible
105 * overflow or divide-by-zero at every operation.
106 *
107 * A columnwise scheme is used for solving A*x = b. The basic algorithm
108 * if A is lower triangular is
109 *
110 * x[1:n] := b[1:n]
111 * for j = 1, ..., n
112 * x(j) := x(j) / A(j,j)
113 * x[j+1:n] := x[j+1:n] - x(j) * A[j+1:n,j]
114 * end
115 *
116 * Define bounds on the components of x after j iterations of the loop:
117 * M(j) = bound on x[1:j]
118 * G(j) = bound on x[j+1:n]
119 * Initially, let M(0) = 0 and G(0) = max{x(i), i=1,...,n}.
120 *
121 * Then for iteration j+1 we have
122 * M(j+1) <= G(j) / | A(j+1,j+1) |
123 * G(j+1) <= G(j) + M(j+1) * | A[j+2:n,j+1] |
124 * <= G(j) ( 1 + CNORM(j+1) / | A(j+1,j+1) | )
125 *
126 * where CNORM(j+1) is greater than or equal to the infinity-norm of
127 * column j+1 of A, not counting the diagonal. Hence
128 *
129 * G(j) <= G(0) product ( 1 + CNORM(i) / | A(i,i) | )
130 * 1<=i<=j
131 * and
132 *
133 * |x(j)| <= ( G(0) / |A(j,j)| ) product ( 1 + CNORM(i) / |A(i,i)| )
134 * 1<=i< j
135 *
136 * Since |x(j)| <= M(j), we use the Level 2 BLAS routine DTRSV if the
137 * reciprocal of the largest M(j), j=1,..,n, is larger than
138 * max(underflow, 1/overflow).
139 *
140 * The bound on x(j) is also used to determine when a step in the
141 * columnwise method can be performed without fear of overflow. If
142 * the computed bound is greater than a large constant, x is scaled to
143 * prevent overflow, but if the bound overflows, x is set to 0, x(j) to
144 * 1, and scale to 0, and a non-trivial solution to A*x = 0 is found.
145 *
146 * Similarly, a row-wise scheme is used to solve A'*x = b. The basic
147 * algorithm for A upper triangular is
148 *
149 * for j = 1, ..., n
150 * x(j) := ( b(j) - A[1:j-1,j]' * x[1:j-1] ) / A(j,j)
151 * end
152 *
153 * We simultaneously compute two bounds
154 * G(j) = bound on ( b(i) - A[1:i-1,i]' * x[1:i-1] ), 1<=i<=j
155 * M(j) = bound on x(i), 1<=i<=j
156 *
157 * The initial values are G(0) = 0, M(0) = max{b(i), i=1,..,n}, and we
158 * add the constraint G(j) >= G(j-1) and M(j) >= M(j-1) for j >= 1.
159 * Then the bound on x(j) is
160 *
161 * M(j) <= M(j-1) * ( 1 + CNORM(j) ) / | A(j,j) |
162 *
163 * <= M(0) * product ( ( 1 + CNORM(i) ) / |A(i,i)| )
164 * 1<=i<=j
165 *
166 * and we can safely call DTRSV if 1/M(n) and 1/G(n) are both greater
167 * than max(underflow, 1/overflow).
168 *
169 * =====================================================================
170 *
171 * .. Parameters ..
172  DOUBLE PRECISION zero, half, one
173  parameter( zero = 0.0d+0, half = 0.5d+0, one = 1.0d+0 )
174 * ..
175 * .. Local Scalars ..
176  LOGICAL notran, nounit, upper
177  INTEGER i, imax, j, jfirst, jinc, jlast
178  DOUBLE PRECISION bignum, grow, rec, smlnum, sumj, tjj, tjjs,
179  $ tmax, tscal, uscal, xbnd, xj, xmax
180 * ..
181 * .. External Functions ..
182  LOGICAL lsame
183  INTEGER idamax
184  DOUBLE PRECISION dasum, ddot, dlamch
185  EXTERNAL lsame, idamax, dasum, ddot, dlamch
186 * ..
187 * .. External Subroutines ..
188  EXTERNAL daxpy, dscal, dtrsv, xerbla
189 * ..
190 * .. Intrinsic Functions ..
191  INTRINSIC abs, max, min
192 * ..
193 * .. Executable Statements ..
194 *
195  info = 0
196  upper = lsame( uplo, 'U' )
197  notran = lsame( trans, 'N' )
198  nounit = lsame( diag, 'N' )
199 *
200 * Test the input parameters.
201 *
202  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
203  info = -1
204  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) .AND. .NOT.
205  $ lsame( trans, 'C' ) ) THEN
206  info = -2
207  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
208  info = -3
209  ELSE IF( .NOT.lsame( normin, 'Y' ) .AND. .NOT.
210  $ lsame( normin, 'N' ) ) THEN
211  info = -4
212  ELSE IF( n.LT.0 ) THEN
213  info = -5
214  ELSE IF( lda.LT.max( 1, n ) ) THEN
215  info = -7
216  END IF
217  IF( info.NE.0 ) THEN
218  CALL xerbla( 'DLATRS', -info )
219  return
220  END IF
221 *
222 * Quick return if possible
223 *
224  IF( n.EQ.0 )
225  $ return
226 *
227 * Determine machine dependent parameters to control overflow.
228 *
229  smlnum = dlamch( 'Safe minimum' ) / dlamch( 'Precision' )
230  bignum = one / smlnum
231  scale = one
232 *
233  IF( lsame( normin, 'N' ) ) THEN
234 *
235 * Compute the 1-norm of each column, not including the diagonal.
236 *
237  IF( upper ) THEN
238 *
239 * A is upper triangular.
240 *
241  DO 10 j = 1, n
242  cnorm( j ) = dasum( j-1, a( 1, j ), 1 )
243  10 continue
244  ELSE
245 *
246 * A is lower triangular.
247 *
248  DO 20 j = 1, n - 1
249  cnorm( j ) = dasum( n-j, a( j+1, j ), 1 )
250  20 continue
251  cnorm( n ) = zero
252  END IF
253  END IF
254 *
255 * Scale the column norms by TSCAL if the maximum element in CNORM is
256 * greater than BIGNUM.
257 *
258  imax = idamax( n, cnorm, 1 )
259  tmax = cnorm( imax )
260  IF( tmax.LE.bignum ) THEN
261  tscal = one
262  ELSE
263  tscal = one / ( smlnum*tmax )
264  CALL dscal( n, tscal, cnorm, 1 )
265  END IF
266 *
267 * Compute a bound on the computed solution vector to see if the
268 * Level 2 BLAS routine DTRSV can be used.
269 *
270  j = idamax( n, x, 1 )
271  xmax = abs( x( j ) )
272  xbnd = xmax
273  IF( notran ) THEN
274 *
275 * Compute the growth in A * x = b.
276 *
277  IF( upper ) THEN
278  jfirst = n
279  jlast = 1
280  jinc = -1
281  ELSE
282  jfirst = 1
283  jlast = n
284  jinc = 1
285  END IF
286 *
287  IF( tscal.NE.one ) THEN
288  grow = zero
289  go to 50
290  END IF
291 *
292  IF( nounit ) THEN
293 *
294 * A is non-unit triangular.
295 *
296 * Compute GROW = 1/G(j) and XBND = 1/M(j).
297 * Initially, G(0) = max{x(i), i=1,...,n}.
298 *
299  grow = one / max( xbnd, smlnum )
300  xbnd = grow
301  DO 30 j = jfirst, jlast, jinc
302 *
303 * Exit the loop if the growth factor is too small.
304 *
305  IF( grow.LE.smlnum )
306  $ go to 50
307 *
308 * M(j) = G(j-1) / abs(A(j,j))
309 *
310  tjj = abs( a( j, j ) )
311  xbnd = min( xbnd, min( one, tjj )*grow )
312  IF( tjj+cnorm( j ).GE.smlnum ) THEN
313 *
314 * G(j) = G(j-1)*( 1 + CNORM(j) / abs(A(j,j)) )
315 *
316  grow = grow*( tjj / ( tjj+cnorm( j ) ) )
317  ELSE
318 *
319 * G(j) could overflow, set GROW to 0.
320 *
321  grow = zero
322  END IF
323  30 continue
324  grow = xbnd
325  ELSE
326 *
327 * A is unit triangular.
328 *
329 * Compute GROW = 1/G(j), where G(0) = max{x(i), i=1,...,n}.
330 *
331  grow = min( one, one / max( xbnd, smlnum ) )
332  DO 40 j = jfirst, jlast, jinc
333 *
334 * Exit the loop if the growth factor is too small.
335 *
336  IF( grow.LE.smlnum )
337  $ go to 50
338 *
339 * G(j) = G(j-1)*( 1 + CNORM(j) )
340 *
341  grow = grow*( one / ( one+cnorm( j ) ) )
342  40 continue
343  END IF
344  50 continue
345 *
346  ELSE
347 *
348 * Compute the growth in A' * x = b.
349 *
350  IF( upper ) THEN
351  jfirst = 1
352  jlast = n
353  jinc = 1
354  ELSE
355  jfirst = n
356  jlast = 1
357  jinc = -1
358  END IF
359 *
360  IF( tscal.NE.one ) THEN
361  grow = zero
362  go to 80
363  END IF
364 *
365  IF( nounit ) THEN
366 *
367 * A is non-unit triangular.
368 *
369 * Compute GROW = 1/G(j) and XBND = 1/M(j).
370 * Initially, M(0) = max{x(i), i=1,...,n}.
371 *
372  grow = one / max( xbnd, smlnum )
373  xbnd = grow
374  DO 60 j = jfirst, jlast, jinc
375 *
376 * Exit the loop if the growth factor is too small.
377 *
378  IF( grow.LE.smlnum )
379  $ go to 80
380 *
381 * G(j) = max( G(j-1), M(j-1)*( 1 + CNORM(j) ) )
382 *
383  xj = one + cnorm( j )
384  grow = min( grow, xbnd / xj )
385 *
386 * M(j) = M(j-1)*( 1 + CNORM(j) ) / abs(A(j,j))
387 *
388  tjj = abs( a( j, j ) )
389  IF( xj.GT.tjj )
390  $ xbnd = xbnd*( tjj / xj )
391  60 continue
392  grow = min( grow, xbnd )
393  ELSE
394 *
395 * A is unit triangular.
396 *
397 * Compute GROW = 1/G(j), where G(0) = max{x(i), i=1,...,n}.
398 *
399  grow = min( one, one / max( xbnd, smlnum ) )
400  DO 70 j = jfirst, jlast, jinc
401 *
402 * Exit the loop if the growth factor is too small.
403 *
404  IF( grow.LE.smlnum )
405  $ go to 80
406 *
407 * G(j) = ( 1 + CNORM(j) )*G(j-1)
408 *
409  xj = one + cnorm( j )
410  grow = grow / xj
411  70 continue
412  END IF
413  80 continue
414  END IF
415 *
416  IF( ( grow*tscal ).GT.smlnum ) THEN
417 *
418 * Use the Level 2 BLAS solve if the reciprocal of the bound on
419 * elements of X is not too small.
420 *
421  CALL dtrsv( uplo, trans, diag, n, a, lda, x, 1 )
422  ELSE
423 *
424 * Use a Level 1 BLAS solve, scaling intermediate results.
425 *
426  IF( xmax.GT.bignum ) THEN
427 *
428 * Scale X so that its components are less than or equal to
429 * BIGNUM in absolute value.
430 *
431  scale = bignum / xmax
432  CALL dscal( n, scale, x, 1 )
433  xmax = bignum
434  END IF
435 *
436  IF( notran ) THEN
437 *
438 * Solve A * x = b
439 *
440  DO 110 j = jfirst, jlast, jinc
441 *
442 * Compute x(j) = b(j) / A(j,j), scaling x if necessary.
443 *
444  xj = abs( x( j ) )
445  IF( nounit ) THEN
446  tjjs = a( j, j )*tscal
447  ELSE
448  tjjs = tscal
449  IF( tscal.EQ.one )
450  $ go to 100
451  END IF
452  tjj = abs( tjjs )
453  IF( tjj.GT.smlnum ) THEN
454 *
455 * abs(A(j,j)) > SMLNUM:
456 *
457  IF( tjj.LT.one ) THEN
458  IF( xj.GT.tjj*bignum ) THEN
459 *
460 * Scale x by 1/b(j).
461 *
462  rec = one / xj
463  CALL dscal( n, rec, x, 1 )
464  scale = scale*rec
465  xmax = xmax*rec
466  END IF
467  END IF
468  x( j ) = x( j ) / tjjs
469  xj = abs( x( j ) )
470  ELSE IF( tjj.GT.zero ) THEN
471 *
472 * 0 < abs(A(j,j)) <= SMLNUM:
473 *
474  IF( xj.GT.tjj*bignum ) THEN
475 *
476 * Scale x by (1/abs(x(j)))*abs(A(j,j))*BIGNUM
477 * to avoid overflow when dividing by A(j,j).
478 *
479  rec = ( tjj*bignum ) / xj
480  IF( cnorm( j ).GT.one ) THEN
481 *
482 * Scale by 1/CNORM(j) to avoid overflow when
483 * multiplying x(j) times column j.
484 *
485  rec = rec / cnorm( j )
486  END IF
487  CALL dscal( n, rec, x, 1 )
488  scale = scale*rec
489  xmax = xmax*rec
490  END IF
491  x( j ) = x( j ) / tjjs
492  xj = abs( x( j ) )
493  ELSE
494 *
495 * A(j,j) = 0: Set x(1:n) = 0, x(j) = 1, and
496 * scale = 0, and compute a solution to A*x = 0.
497 *
498  DO 90 i = 1, n
499  x( i ) = zero
500  90 continue
501  x( j ) = one
502  xj = one
503  scale = zero
504  xmax = zero
505  END IF
506  100 continue
507 *
508 * Scale x if necessary to avoid overflow when adding a
509 * multiple of column j of A.
510 *
511  IF( xj.GT.one ) THEN
512  rec = one / xj
513  IF( cnorm( j ).GT.( bignum-xmax )*rec ) THEN
514 *
515 * Scale x by 1/(2*abs(x(j))).
516 *
517  rec = rec*half
518  CALL dscal( n, rec, x, 1 )
519  scale = scale*rec
520  END IF
521  ELSE IF( xj*cnorm( j ).GT.( bignum-xmax ) ) THEN
522 *
523 * Scale x by 1/2.
524 *
525  CALL dscal( n, half, x, 1 )
526  scale = scale*half
527  END IF
528 *
529  IF( upper ) THEN
530  IF( j.GT.1 ) THEN
531 *
532 * Compute the update
533 * x(1:j-1) := x(1:j-1) - x(j) * A(1:j-1,j)
534 *
535  CALL daxpy( j-1, -x( j )*tscal, a( 1, j ), 1, x,
536  $ 1 )
537  i = idamax( j-1, x, 1 )
538  xmax = abs( x( i ) )
539  END IF
540  ELSE
541  IF( j.LT.n ) THEN
542 *
543 * Compute the update
544 * x(j+1:n) := x(j+1:n) - x(j) * A(j+1:n,j)
545 *
546  CALL daxpy( n-j, -x( j )*tscal, a( j+1, j ), 1,
547  $ x( j+1 ), 1 )
548  i = j + idamax( n-j, x( j+1 ), 1 )
549  xmax = abs( x( i ) )
550  END IF
551  END IF
552  110 continue
553 *
554  ELSE
555 *
556 * Solve A' * x = b
557 *
558  DO 160 j = jfirst, jlast, jinc
559 *
560 * Compute x(j) = b(j) - sum A(k,j)*x(k).
561 * k<>j
562 *
563  xj = abs( x( j ) )
564  uscal = tscal
565  rec = one / max( xmax, one )
566  IF( cnorm( j ).GT.( bignum-xj )*rec ) THEN
567 *
568 * If x(j) could overflow, scale x by 1/(2*XMAX).
569 *
570  rec = rec*half
571  IF( nounit ) THEN
572  tjjs = a( j, j )*tscal
573  ELSE
574  tjjs = tscal
575  END IF
576  tjj = abs( tjjs )
577  IF( tjj.GT.one ) THEN
578 *
579 * Divide by A(j,j) when scaling x if A(j,j) > 1.
580 *
581  rec = min( one, rec*tjj )
582  uscal = uscal / tjjs
583  END IF
584  IF( rec.LT.one ) THEN
585  CALL dscal( n, rec, x, 1 )
586  scale = scale*rec
587  xmax = xmax*rec
588  END IF
589  END IF
590 *
591  sumj = zero
592  IF( uscal.EQ.one ) THEN
593 *
594 * If the scaling needed for A in the dot product is 1,
595 * call DDOT to perform the dot product.
596 *
597  IF( upper ) THEN
598  sumj = ddot( j-1, a( 1, j ), 1, x, 1 )
599  ELSE IF( j.LT.n ) THEN
600  sumj = ddot( n-j, a( j+1, j ), 1, x( j+1 ), 1 )
601  END IF
602  ELSE
603 *
604 * Otherwise, use in-line code for the dot product.
605 *
606  IF( upper ) THEN
607  DO 120 i = 1, j - 1
608  sumj = sumj + ( a( i, j )*uscal )*x( i )
609  120 continue
610  ELSE IF( j.LT.n ) THEN
611  DO 130 i = j + 1, n
612  sumj = sumj + ( a( i, j )*uscal )*x( i )
613  130 continue
614  END IF
615  END IF
616 *
617  IF( uscal.EQ.tscal ) THEN
618 *
619 * Compute x(j) := ( x(j) - sumj ) / A(j,j) if 1/A(j,j)
620 * was not used to scale the dotproduct.
621 *
622  x( j ) = x( j ) - sumj
623  xj = abs( x( j ) )
624  IF( nounit ) THEN
625  tjjs = a( j, j )*tscal
626  ELSE
627  tjjs = tscal
628  IF( tscal.EQ.one )
629  $ go to 150
630  END IF
631 *
632 * Compute x(j) = x(j) / A(j,j), scaling if necessary.
633 *
634  tjj = abs( tjjs )
635  IF( tjj.GT.smlnum ) THEN
636 *
637 * abs(A(j,j)) > SMLNUM:
638 *
639  IF( tjj.LT.one ) THEN
640  IF( xj.GT.tjj*bignum ) THEN
641 *
642 * Scale X by 1/abs(x(j)).
643 *
644  rec = one / xj
645  CALL dscal( n, rec, x, 1 )
646  scale = scale*rec
647  xmax = xmax*rec
648  END IF
649  END IF
650  x( j ) = x( j ) / tjjs
651  ELSE IF( tjj.GT.zero ) THEN
652 *
653 * 0 < abs(A(j,j)) <= SMLNUM:
654 *
655  IF( xj.GT.tjj*bignum ) THEN
656 *
657 * Scale x by (1/abs(x(j)))*abs(A(j,j))*BIGNUM.
658 *
659  rec = ( tjj*bignum ) / xj
660  CALL dscal( n, rec, x, 1 )
661  scale = scale*rec
662  xmax = xmax*rec
663  END IF
664  x( j ) = x( j ) / tjjs
665  ELSE
666 *
667 * A(j,j) = 0: Set x(1:n) = 0, x(j) = 1, and
668 * scale = 0, and compute a solution to A'*x = 0.
669 *
670  DO 140 i = 1, n
671  x( i ) = zero
672  140 continue
673  x( j ) = one
674  scale = zero
675  xmax = zero
676  END IF
677  150 continue
678  ELSE
679 *
680 * Compute x(j) := x(j) / A(j,j) - sumj if the dot
681 * product has already been divided by 1/A(j,j).
682 *
683  x( j ) = x( j ) / tjjs - sumj
684  END IF
685  xmax = max( xmax, abs( x( j ) ) )
686  160 continue
687  END IF
688  scale = scale / tscal
689  END IF
690 *
691 * Scale the column norms by 1/TSCAL for return.
692 *
693  IF( tscal.NE.one ) THEN
694  CALL dscal( n, one / tscal, cnorm, 1 )
695  END IF
696 *
697  return
698 *
699 * End of DLATRS
700 *
701  END