LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dlarhs.f
Go to the documentation of this file.
1 *> \brief \b DLARHS
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE DLARHS( PATH, XTYPE, UPLO, TRANS, M, N, KL, KU, NRHS,
12 * A, LDA, X, LDX, B, LDB, ISEED, INFO )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER TRANS, UPLO, XTYPE
16 * CHARACTER*3 PATH
17 * INTEGER INFO, KL, KU, LDA, LDB, LDX, M, N, NRHS
18 * ..
19 * .. Array Arguments ..
20 * INTEGER ISEED( 4 )
21 * DOUBLE PRECISION A( LDA, * ), B( LDB, * ), X( LDX, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> DLARHS chooses a set of NRHS random solution vectors and sets
31 *> up the right hand sides for the linear system
32 *> op( A ) * X = B,
33 *> where op( A ) may be A or A' (transpose of A).
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] PATH
40 *> \verbatim
41 *> PATH is CHARACTER*3
42 *> The type of the real matrix A. PATH may be given in any
43 *> combination of upper and lower case. Valid types include
44 *> xGE: General m x n matrix
45 *> xGB: General banded matrix
46 *> xPO: Symmetric positive definite, 2-D storage
47 *> xPP: Symmetric positive definite packed
48 *> xPB: Symmetric positive definite banded
49 *> xSY: Symmetric indefinite, 2-D storage
50 *> xSP: Symmetric indefinite packed
51 *> xSB: Symmetric indefinite banded
52 *> xTR: Triangular
53 *> xTP: Triangular packed
54 *> xTB: Triangular banded
55 *> xQR: General m x n matrix
56 *> xLQ: General m x n matrix
57 *> xQL: General m x n matrix
58 *> xRQ: General m x n matrix
59 *> where the leading character indicates the precision.
60 *> \endverbatim
61 *>
62 *> \param[in] XTYPE
63 *> \verbatim
64 *> XTYPE is CHARACTER*1
65 *> Specifies how the exact solution X will be determined:
66 *> = 'N': New solution; generate a random X.
67 *> = 'C': Computed; use value of X on entry.
68 *> \endverbatim
69 *>
70 *> \param[in] UPLO
71 *> \verbatim
72 *> UPLO is CHARACTER*1
73 *> Specifies whether the upper or lower triangular part of the
74 *> matrix A is stored, if A is symmetric.
75 *> = 'U': Upper triangular
76 *> = 'L': Lower triangular
77 *> \endverbatim
78 *>
79 *> \param[in] TRANS
80 *> \verbatim
81 *> TRANS is CHARACTER*1
82 *> Specifies the operation applied to the matrix A.
83 *> = 'N': System is A * x = b
84 *> = 'T': System is A'* x = b
85 *> = 'C': System is A'* x = b
86 *> \endverbatim
87 *>
88 *> \param[in] M
89 *> \verbatim
90 *> M is INTEGER
91 *> The number or rows of the matrix A. M >= 0.
92 *> \endverbatim
93 *>
94 *> \param[in] N
95 *> \verbatim
96 *> N is INTEGER
97 *> The number of columns of the matrix A. N >= 0.
98 *> \endverbatim
99 *>
100 *> \param[in] KL
101 *> \verbatim
102 *> KL is INTEGER
103 *> Used only if A is a band matrix; specifies the number of
104 *> subdiagonals of A if A is a general band matrix or if A is
105 *> symmetric or triangular and UPLO = 'L'; specifies the number
106 *> of superdiagonals of A if A is symmetric or triangular and
107 *> UPLO = 'U'. 0 <= KL <= M-1.
108 *> \endverbatim
109 *>
110 *> \param[in] KU
111 *> \verbatim
112 *> KU is INTEGER
113 *> Used only if A is a general band matrix or if A is
114 *> triangular.
115 *>
116 *> If PATH = xGB, specifies the number of superdiagonals of A,
117 *> and 0 <= KU <= N-1.
118 *>
119 *> If PATH = xTR, xTP, or xTB, specifies whether or not the
120 *> matrix has unit diagonal:
121 *> = 1: matrix has non-unit diagonal (default)
122 *> = 2: matrix has unit diagonal
123 *> \endverbatim
124 *>
125 *> \param[in] NRHS
126 *> \verbatim
127 *> NRHS is INTEGER
128 *> The number of right hand side vectors in the system A*X = B.
129 *> \endverbatim
130 *>
131 *> \param[in] A
132 *> \verbatim
133 *> A is DOUBLE PRECISION array, dimension (LDA,N)
134 *> The test matrix whose type is given by PATH.
135 *> \endverbatim
136 *>
137 *> \param[in] LDA
138 *> \verbatim
139 *> LDA is INTEGER
140 *> The leading dimension of the array A.
141 *> If PATH = xGB, LDA >= KL+KU+1.
142 *> If PATH = xPB, xSB, xHB, or xTB, LDA >= KL+1.
143 *> Otherwise, LDA >= max(1,M).
144 *> \endverbatim
145 *>
146 *> \param[in,out] X
147 *> \verbatim
148 *> X is or output) DOUBLE PRECISION array, dimension(LDX,NRHS)
149 *> On entry, if XTYPE = 'C' (for 'Computed'), then X contains
150 *> the exact solution to the system of linear equations.
151 *> On exit, if XTYPE = 'N' (for 'New'), then X is initialized
152 *> with random values.
153 *> \endverbatim
154 *>
155 *> \param[in] LDX
156 *> \verbatim
157 *> LDX is INTEGER
158 *> The leading dimension of the array X. If TRANS = 'N',
159 *> LDX >= max(1,N); if TRANS = 'T', LDX >= max(1,M).
160 *> \endverbatim
161 *>
162 *> \param[out] B
163 *> \verbatim
164 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
165 *> The right hand side vector(s) for the system of equations,
166 *> computed from B = op(A) * X, where op(A) is determined by
167 *> TRANS.
168 *> \endverbatim
169 *>
170 *> \param[in] LDB
171 *> \verbatim
172 *> LDB is INTEGER
173 *> The leading dimension of the array B. If TRANS = 'N',
174 *> LDB >= max(1,M); if TRANS = 'T', LDB >= max(1,N).
175 *> \endverbatim
176 *>
177 *> \param[in,out] ISEED
178 *> \verbatim
179 *> ISEED is INTEGER array, dimension (4)
180 *> The seed vector for the random number generator (used in
181 *> DLATMS). Modified on exit.
182 *> \endverbatim
183 *>
184 *> \param[out] INFO
185 *> \verbatim
186 *> INFO is INTEGER
187 *> = 0: successful exit
188 *> < 0: if INFO = -i, the i-th argument had an illegal value
189 *> \endverbatim
190 *
191 * Authors:
192 * ========
193 *
194 *> \author Univ. of Tennessee
195 *> \author Univ. of California Berkeley
196 *> \author Univ. of Colorado Denver
197 *> \author NAG Ltd.
198 *
199 *> \date November 2011
200 *
201 *> \ingroup double_eig
202 *
203 * =====================================================================
204  SUBROUTINE dlarhs( PATH, XTYPE, UPLO, TRANS, M, N, KL, KU, NRHS,
205  $ a, lda, x, ldx, b, ldb, iseed, info )
206 *
207 * -- LAPACK test routine (version 3.4.0) --
208 * -- LAPACK is a software package provided by Univ. of Tennessee, --
209 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
210 * November 2011
211 *
212 * .. Scalar Arguments ..
213  CHARACTER trans, uplo, xtype
214  CHARACTER*3 path
215  INTEGER info, kl, ku, lda, ldb, ldx, m, n, nrhs
216 * ..
217 * .. Array Arguments ..
218  INTEGER iseed( 4 )
219  DOUBLE PRECISION a( lda, * ), b( ldb, * ), x( ldx, * )
220 * ..
221 *
222 * =====================================================================
223 *
224 * .. Parameters ..
225  DOUBLE PRECISION one, zero
226  parameter( one = 1.0d+0, zero = 0.0d+0 )
227 * ..
228 * .. Local Scalars ..
229  LOGICAL band, gen, notran, qrs, sym, tran, tri
230  CHARACTER c1, diag
231  CHARACTER*2 c2
232  INTEGER j, mb, nx
233 * ..
234 * .. External Functions ..
235  LOGICAL lsame, lsamen
236  EXTERNAL lsame, lsamen
237 * ..
238 * .. External Subroutines ..
239  EXTERNAL dgbmv, dgemm, dlacpy, dlarnv, dsbmv, dspmv,
241 * ..
242 * .. Intrinsic Functions ..
243  INTRINSIC max
244 * ..
245 * .. Executable Statements ..
246 *
247 * Test the input parameters.
248 *
249  info = 0
250  c1 = path( 1: 1 )
251  c2 = path( 2: 3 )
252  tran = lsame( trans, 'T' ) .OR. lsame( trans, 'C' )
253  notran = .NOT.tran
254  gen = lsame( path( 2: 2 ), 'G' )
255  qrs = lsame( path( 2: 2 ), 'Q' ) .OR. lsame( path( 3: 3 ), 'Q' )
256  sym = lsame( path( 2: 2 ), 'P' ) .OR. lsame( path( 2: 2 ), 'S' )
257  tri = lsame( path( 2: 2 ), 'T' )
258  band = lsame( path( 3: 3 ), 'B' )
259  IF( .NOT.lsame( c1, 'Double precision' ) ) THEN
260  info = -1
261  ELSE IF( .NOT.( lsame( xtype, 'N' ) .OR. lsame( xtype, 'C' ) ) )
262  $ THEN
263  info = -2
264  ELSE IF( ( sym .OR. tri ) .AND. .NOT.
265  $ ( lsame( uplo, 'U' ) .OR. lsame( uplo, 'L' ) ) ) THEN
266  info = -3
267  ELSE IF( ( gen .OR. qrs ) .AND. .NOT.
268  $ ( tran .OR. lsame( trans, 'N' ) ) ) THEN
269  info = -4
270  ELSE IF( m.LT.0 ) THEN
271  info = -5
272  ELSE IF( n.LT.0 ) THEN
273  info = -6
274  ELSE IF( band .AND. kl.LT.0 ) THEN
275  info = -7
276  ELSE IF( band .AND. ku.LT.0 ) THEN
277  info = -8
278  ELSE IF( nrhs.LT.0 ) THEN
279  info = -9
280  ELSE IF( ( .NOT.band .AND. lda.LT.max( 1, m ) ) .OR.
281  $ ( band .AND. ( sym .OR. tri ) .AND. lda.LT.kl+1 ) .OR.
282  $ ( band .AND. gen .AND. lda.LT.kl+ku+1 ) ) THEN
283  info = -11
284  ELSE IF( ( notran .AND. ldx.LT.max( 1, n ) ) .OR.
285  $ ( tran .AND. ldx.LT.max( 1, m ) ) ) THEN
286  info = -13
287  ELSE IF( ( notran .AND. ldb.LT.max( 1, m ) ) .OR.
288  $ ( tran .AND. ldb.LT.max( 1, n ) ) ) THEN
289  info = -15
290  END IF
291  IF( info.NE.0 ) THEN
292  CALL xerbla( 'DLARHS', -info )
293  return
294  END IF
295 *
296 * Initialize X to NRHS random vectors unless XTYPE = 'C'.
297 *
298  IF( tran ) THEN
299  nx = m
300  mb = n
301  ELSE
302  nx = n
303  mb = m
304  END IF
305  IF( .NOT.lsame( xtype, 'C' ) ) THEN
306  DO 10 j = 1, nrhs
307  CALL dlarnv( 2, iseed, n, x( 1, j ) )
308  10 continue
309  END IF
310 *
311 * Multiply X by op( A ) using an appropriate
312 * matrix multiply routine.
313 *
314  IF( lsamen( 2, c2, 'GE' ) .OR. lsamen( 2, c2, 'QR' ) .OR.
315  $ lsamen( 2, c2, 'LQ' ) .OR. lsamen( 2, c2, 'QL' ) .OR.
316  $ lsamen( 2, c2, 'RQ' ) ) THEN
317 *
318 * General matrix
319 *
320  CALL dgemm( trans, 'N', mb, nrhs, nx, one, a, lda, x, ldx,
321  $ zero, b, ldb )
322 *
323  ELSE IF( lsamen( 2, c2, 'PO' ) .OR. lsamen( 2, c2, 'SY' ) ) THEN
324 *
325 * Symmetric matrix, 2-D storage
326 *
327  CALL dsymm( 'Left', uplo, n, nrhs, one, a, lda, x, ldx, zero,
328  $ b, ldb )
329 *
330  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
331 *
332 * General matrix, band storage
333 *
334  DO 20 j = 1, nrhs
335  CALL dgbmv( trans, mb, nx, kl, ku, one, a, lda, x( 1, j ),
336  $ 1, zero, b( 1, j ), 1 )
337  20 continue
338 *
339  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
340 *
341 * Symmetric matrix, band storage
342 *
343  DO 30 j = 1, nrhs
344  CALL dsbmv( uplo, n, kl, one, a, lda, x( 1, j ), 1, zero,
345  $ b( 1, j ), 1 )
346  30 continue
347 *
348  ELSE IF( lsamen( 2, c2, 'PP' ) .OR. lsamen( 2, c2, 'SP' ) ) THEN
349 *
350 * Symmetric matrix, packed storage
351 *
352  DO 40 j = 1, nrhs
353  CALL dspmv( uplo, n, one, a, x( 1, j ), 1, zero, b( 1, j ),
354  $ 1 )
355  40 continue
356 *
357  ELSE IF( lsamen( 2, c2, 'TR' ) ) THEN
358 *
359 * Triangular matrix. Note that for triangular matrices,
360 * KU = 1 => non-unit triangular
361 * KU = 2 => unit triangular
362 *
363  CALL dlacpy( 'Full', n, nrhs, x, ldx, b, ldb )
364  IF( ku.EQ.2 ) THEN
365  diag = 'U'
366  ELSE
367  diag = 'N'
368  END IF
369  CALL dtrmm( 'Left', uplo, trans, diag, n, nrhs, one, a, lda, b,
370  $ ldb )
371 *
372  ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
373 *
374 * Triangular matrix, packed storage
375 *
376  CALL dlacpy( 'Full', n, nrhs, x, ldx, b, ldb )
377  IF( ku.EQ.2 ) THEN
378  diag = 'U'
379  ELSE
380  diag = 'N'
381  END IF
382  DO 50 j = 1, nrhs
383  CALL dtpmv( uplo, trans, diag, n, a, b( 1, j ), 1 )
384  50 continue
385 *
386  ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
387 *
388 * Triangular matrix, banded storage
389 *
390  CALL dlacpy( 'Full', n, nrhs, x, ldx, b, ldb )
391  IF( ku.EQ.2 ) THEN
392  diag = 'U'
393  ELSE
394  diag = 'N'
395  END IF
396  DO 60 j = 1, nrhs
397  CALL dtbmv( uplo, trans, diag, n, kl, a, lda, b( 1, j ), 1 )
398  60 continue
399 *
400  ELSE
401 *
402 * If PATH is none of the above, return with an error code.
403 *
404  info = -1
405  CALL xerbla( 'DLARHS', -info )
406  END IF
407 *
408  return
409 *
410 * End of DLARHS
411 *
412  END