LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ztrsyl.f
Go to the documentation of this file.
1 *> \brief \b ZTRSYL
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZTRSYL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztrsyl.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztrsyl.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztrsyl.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZTRSYL( TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C,
22 * LDC, SCALE, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER TRANA, TRANB
26 * INTEGER INFO, ISGN, LDA, LDB, LDC, M, N
27 * DOUBLE PRECISION SCALE
28 * ..
29 * .. Array Arguments ..
30 * COMPLEX*16 A( LDA, * ), B( LDB, * ), C( LDC, * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> ZTRSYL solves the complex Sylvester matrix equation:
40 *>
41 *> op(A)*X + X*op(B) = scale*C or
42 *> op(A)*X - X*op(B) = scale*C,
43 *>
44 *> where op(A) = A or A**H, and A and B are both upper triangular. A is
45 *> M-by-M and B is N-by-N; the right hand side C and the solution X are
46 *> M-by-N; and scale is an output scale factor, set <= 1 to avoid
47 *> overflow in X.
48 *> \endverbatim
49 *
50 * Arguments:
51 * ==========
52 *
53 *> \param[in] TRANA
54 *> \verbatim
55 *> TRANA is CHARACTER*1
56 *> Specifies the option op(A):
57 *> = 'N': op(A) = A (No transpose)
58 *> = 'C': op(A) = A**H (Conjugate transpose)
59 *> \endverbatim
60 *>
61 *> \param[in] TRANB
62 *> \verbatim
63 *> TRANB is CHARACTER*1
64 *> Specifies the option op(B):
65 *> = 'N': op(B) = B (No transpose)
66 *> = 'C': op(B) = B**H (Conjugate transpose)
67 *> \endverbatim
68 *>
69 *> \param[in] ISGN
70 *> \verbatim
71 *> ISGN is INTEGER
72 *> Specifies the sign in the equation:
73 *> = +1: solve op(A)*X + X*op(B) = scale*C
74 *> = -1: solve op(A)*X - X*op(B) = scale*C
75 *> \endverbatim
76 *>
77 *> \param[in] M
78 *> \verbatim
79 *> M is INTEGER
80 *> The order of the matrix A, and the number of rows in the
81 *> matrices X and C. M >= 0.
82 *> \endverbatim
83 *>
84 *> \param[in] N
85 *> \verbatim
86 *> N is INTEGER
87 *> The order of the matrix B, and the number of columns in the
88 *> matrices X and C. N >= 0.
89 *> \endverbatim
90 *>
91 *> \param[in] A
92 *> \verbatim
93 *> A is COMPLEX*16 array, dimension (LDA,M)
94 *> The upper triangular matrix A.
95 *> \endverbatim
96 *>
97 *> \param[in] LDA
98 *> \verbatim
99 *> LDA is INTEGER
100 *> The leading dimension of the array A. LDA >= max(1,M).
101 *> \endverbatim
102 *>
103 *> \param[in] B
104 *> \verbatim
105 *> B is COMPLEX*16 array, dimension (LDB,N)
106 *> The upper triangular matrix B.
107 *> \endverbatim
108 *>
109 *> \param[in] LDB
110 *> \verbatim
111 *> LDB is INTEGER
112 *> The leading dimension of the array B. LDB >= max(1,N).
113 *> \endverbatim
114 *>
115 *> \param[in,out] C
116 *> \verbatim
117 *> C is COMPLEX*16 array, dimension (LDC,N)
118 *> On entry, the M-by-N right hand side matrix C.
119 *> On exit, C is overwritten by the solution matrix X.
120 *> \endverbatim
121 *>
122 *> \param[in] LDC
123 *> \verbatim
124 *> LDC is INTEGER
125 *> The leading dimension of the array C. LDC >= max(1,M)
126 *> \endverbatim
127 *>
128 *> \param[out] SCALE
129 *> \verbatim
130 *> SCALE is DOUBLE PRECISION
131 *> The scale factor, scale, set <= 1 to avoid overflow in X.
132 *> \endverbatim
133 *>
134 *> \param[out] INFO
135 *> \verbatim
136 *> INFO is INTEGER
137 *> = 0: successful exit
138 *> < 0: if INFO = -i, the i-th argument had an illegal value
139 *> = 1: A and B have common or very close eigenvalues; perturbed
140 *> values were used to solve the equation (but the matrices
141 *> A and B are unchanged).
142 *> \endverbatim
143 *
144 * Authors:
145 * ========
146 *
147 *> \author Univ. of Tennessee
148 *> \author Univ. of California Berkeley
149 *> \author Univ. of Colorado Denver
150 *> \author NAG Ltd.
151 *
152 *> \date November 2011
153 *
154 *> \ingroup complex16SYcomputational
155 *
156 * =====================================================================
157  SUBROUTINE ztrsyl( TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C,
158  $ ldc, scale, info )
159 *
160 * -- LAPACK computational routine (version 3.4.0) --
161 * -- LAPACK is a software package provided by Univ. of Tennessee, --
162 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
163 * November 2011
164 *
165 * .. Scalar Arguments ..
166  CHARACTER trana, tranb
167  INTEGER info, isgn, lda, ldb, ldc, m, n
168  DOUBLE PRECISION scale
169 * ..
170 * .. Array Arguments ..
171  COMPLEX*16 a( lda, * ), b( ldb, * ), c( ldc, * )
172 * ..
173 *
174 * =====================================================================
175 *
176 * .. Parameters ..
177  DOUBLE PRECISION one
178  parameter( one = 1.0d+0 )
179 * ..
180 * .. Local Scalars ..
181  LOGICAL notrna, notrnb
182  INTEGER j, k, l
183  DOUBLE PRECISION bignum, da11, db, eps, scaloc, sgn, smin,
184  $ smlnum
185  COMPLEX*16 a11, suml, sumr, vec, x11
186 * ..
187 * .. Local Arrays ..
188  DOUBLE PRECISION dum( 1 )
189 * ..
190 * .. External Functions ..
191  LOGICAL lsame
192  DOUBLE PRECISION dlamch, zlange
193  COMPLEX*16 zdotc, zdotu, zladiv
194  EXTERNAL lsame, dlamch, zlange, zdotc, zdotu, zladiv
195 * ..
196 * .. External Subroutines ..
197  EXTERNAL dlabad, xerbla, zdscal
198 * ..
199 * .. Intrinsic Functions ..
200  INTRINSIC abs, dble, dcmplx, dconjg, dimag, max, min
201 * ..
202 * .. Executable Statements ..
203 *
204 * Decode and Test input parameters
205 *
206  notrna = lsame( trana, 'N' )
207  notrnb = lsame( tranb, 'N' )
208 *
209  info = 0
210  IF( .NOT.notrna .AND. .NOT.lsame( trana, 'C' ) ) THEN
211  info = -1
212  ELSE IF( .NOT.notrnb .AND. .NOT.lsame( tranb, 'C' ) ) THEN
213  info = -2
214  ELSE IF( isgn.NE.1 .AND. isgn.NE.-1 ) THEN
215  info = -3
216  ELSE IF( m.LT.0 ) THEN
217  info = -4
218  ELSE IF( n.LT.0 ) THEN
219  info = -5
220  ELSE IF( lda.LT.max( 1, m ) ) THEN
221  info = -7
222  ELSE IF( ldb.LT.max( 1, n ) ) THEN
223  info = -9
224  ELSE IF( ldc.LT.max( 1, m ) ) THEN
225  info = -11
226  END IF
227  IF( info.NE.0 ) THEN
228  CALL xerbla( 'ZTRSYL', -info )
229  return
230  END IF
231 *
232 * Quick return if possible
233 *
234  scale = one
235  IF( m.EQ.0 .OR. n.EQ.0 )
236  $ return
237 *
238 * Set constants to control overflow
239 *
240  eps = dlamch( 'P' )
241  smlnum = dlamch( 'S' )
242  bignum = one / smlnum
243  CALL dlabad( smlnum, bignum )
244  smlnum = smlnum*dble( m*n ) / eps
245  bignum = one / smlnum
246  smin = max( smlnum, eps*zlange( 'M', m, m, a, lda, dum ),
247  $ eps*zlange( 'M', n, n, b, ldb, dum ) )
248  sgn = isgn
249 *
250  IF( notrna .AND. notrnb ) THEN
251 *
252 * Solve A*X + ISGN*X*B = scale*C.
253 *
254 * The (K,L)th block of X is determined starting from
255 * bottom-left corner column by column by
256 *
257 * A(K,K)*X(K,L) + ISGN*X(K,L)*B(L,L) = C(K,L) - R(K,L)
258 *
259 * Where
260 * M L-1
261 * R(K,L) = SUM [A(K,I)*X(I,L)] +ISGN*SUM [X(K,J)*B(J,L)].
262 * I=K+1 J=1
263 *
264  DO 30 l = 1, n
265  DO 20 k = m, 1, -1
266 *
267  suml = zdotu( m-k, a( k, min( k+1, m ) ), lda,
268  $ c( min( k+1, m ), l ), 1 )
269  sumr = zdotu( l-1, c( k, 1 ), ldc, b( 1, l ), 1 )
270  vec = c( k, l ) - ( suml+sgn*sumr )
271 *
272  scaloc = one
273  a11 = a( k, k ) + sgn*b( l, l )
274  da11 = abs( dble( a11 ) ) + abs( dimag( a11 ) )
275  IF( da11.LE.smin ) THEN
276  a11 = smin
277  da11 = smin
278  info = 1
279  END IF
280  db = abs( dble( vec ) ) + abs( dimag( vec ) )
281  IF( da11.LT.one .AND. db.GT.one ) THEN
282  IF( db.GT.bignum*da11 )
283  $ scaloc = one / db
284  END IF
285  x11 = zladiv( vec*dcmplx( scaloc ), a11 )
286 *
287  IF( scaloc.NE.one ) THEN
288  DO 10 j = 1, n
289  CALL zdscal( m, scaloc, c( 1, j ), 1 )
290  10 continue
291  scale = scale*scaloc
292  END IF
293  c( k, l ) = x11
294 *
295  20 continue
296  30 continue
297 *
298  ELSE IF( .NOT.notrna .AND. notrnb ) THEN
299 *
300 * Solve A**H *X + ISGN*X*B = scale*C.
301 *
302 * The (K,L)th block of X is determined starting from
303 * upper-left corner column by column by
304 *
305 * A**H(K,K)*X(K,L) + ISGN*X(K,L)*B(L,L) = C(K,L) - R(K,L)
306 *
307 * Where
308 * K-1 L-1
309 * R(K,L) = SUM [A**H(I,K)*X(I,L)] + ISGN*SUM [X(K,J)*B(J,L)]
310 * I=1 J=1
311 *
312  DO 60 l = 1, n
313  DO 50 k = 1, m
314 *
315  suml = zdotc( k-1, a( 1, k ), 1, c( 1, l ), 1 )
316  sumr = zdotu( l-1, c( k, 1 ), ldc, b( 1, l ), 1 )
317  vec = c( k, l ) - ( suml+sgn*sumr )
318 *
319  scaloc = one
320  a11 = dconjg( a( k, k ) ) + sgn*b( l, l )
321  da11 = abs( dble( a11 ) ) + abs( dimag( a11 ) )
322  IF( da11.LE.smin ) THEN
323  a11 = smin
324  da11 = smin
325  info = 1
326  END IF
327  db = abs( dble( vec ) ) + abs( dimag( vec ) )
328  IF( da11.LT.one .AND. db.GT.one ) THEN
329  IF( db.GT.bignum*da11 )
330  $ scaloc = one / db
331  END IF
332 *
333  x11 = zladiv( vec*dcmplx( scaloc ), a11 )
334 *
335  IF( scaloc.NE.one ) THEN
336  DO 40 j = 1, n
337  CALL zdscal( m, scaloc, c( 1, j ), 1 )
338  40 continue
339  scale = scale*scaloc
340  END IF
341  c( k, l ) = x11
342 *
343  50 continue
344  60 continue
345 *
346  ELSE IF( .NOT.notrna .AND. .NOT.notrnb ) THEN
347 *
348 * Solve A**H*X + ISGN*X*B**H = C.
349 *
350 * The (K,L)th block of X is determined starting from
351 * upper-right corner column by column by
352 *
353 * A**H(K,K)*X(K,L) + ISGN*X(K,L)*B**H(L,L) = C(K,L) - R(K,L)
354 *
355 * Where
356 * K-1
357 * R(K,L) = SUM [A**H(I,K)*X(I,L)] +
358 * I=1
359 * N
360 * ISGN*SUM [X(K,J)*B**H(L,J)].
361 * J=L+1
362 *
363  DO 90 l = n, 1, -1
364  DO 80 k = 1, m
365 *
366  suml = zdotc( k-1, a( 1, k ), 1, c( 1, l ), 1 )
367  sumr = zdotc( n-l, c( k, min( l+1, n ) ), ldc,
368  $ b( l, min( l+1, n ) ), ldb )
369  vec = c( k, l ) - ( suml+sgn*dconjg( sumr ) )
370 *
371  scaloc = one
372  a11 = dconjg( a( k, k )+sgn*b( l, l ) )
373  da11 = abs( dble( a11 ) ) + abs( dimag( a11 ) )
374  IF( da11.LE.smin ) THEN
375  a11 = smin
376  da11 = smin
377  info = 1
378  END IF
379  db = abs( dble( vec ) ) + abs( dimag( vec ) )
380  IF( da11.LT.one .AND. db.GT.one ) THEN
381  IF( db.GT.bignum*da11 )
382  $ scaloc = one / db
383  END IF
384 *
385  x11 = zladiv( vec*dcmplx( scaloc ), a11 )
386 *
387  IF( scaloc.NE.one ) THEN
388  DO 70 j = 1, n
389  CALL zdscal( m, scaloc, c( 1, j ), 1 )
390  70 continue
391  scale = scale*scaloc
392  END IF
393  c( k, l ) = x11
394 *
395  80 continue
396  90 continue
397 *
398  ELSE IF( notrna .AND. .NOT.notrnb ) THEN
399 *
400 * Solve A*X + ISGN*X*B**H = C.
401 *
402 * The (K,L)th block of X is determined starting from
403 * bottom-left corner column by column by
404 *
405 * A(K,K)*X(K,L) + ISGN*X(K,L)*B**H(L,L) = C(K,L) - R(K,L)
406 *
407 * Where
408 * M N
409 * R(K,L) = SUM [A(K,I)*X(I,L)] + ISGN*SUM [X(K,J)*B**H(L,J)]
410 * I=K+1 J=L+1
411 *
412  DO 120 l = n, 1, -1
413  DO 110 k = m, 1, -1
414 *
415  suml = zdotu( m-k, a( k, min( k+1, m ) ), lda,
416  $ c( min( k+1, m ), l ), 1 )
417  sumr = zdotc( n-l, c( k, min( l+1, n ) ), ldc,
418  $ b( l, min( l+1, n ) ), ldb )
419  vec = c( k, l ) - ( suml+sgn*dconjg( sumr ) )
420 *
421  scaloc = one
422  a11 = a( k, k ) + sgn*dconjg( b( l, l ) )
423  da11 = abs( dble( a11 ) ) + abs( dimag( a11 ) )
424  IF( da11.LE.smin ) THEN
425  a11 = smin
426  da11 = smin
427  info = 1
428  END IF
429  db = abs( dble( vec ) ) + abs( dimag( vec ) )
430  IF( da11.LT.one .AND. db.GT.one ) THEN
431  IF( db.GT.bignum*da11 )
432  $ scaloc = one / db
433  END IF
434 *
435  x11 = zladiv( vec*dcmplx( scaloc ), a11 )
436 *
437  IF( scaloc.NE.one ) THEN
438  DO 100 j = 1, n
439  CALL zdscal( m, scaloc, c( 1, j ), 1 )
440  100 continue
441  scale = scale*scaloc
442  END IF
443  c( k, l ) = x11
444 *
445  110 continue
446  120 continue
447 *
448  END IF
449 *
450  return
451 *
452 * End of ZTRSYL
453 *
454  END