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
derrqr.f
Go to the documentation of this file.
1  SUBROUTINE derrqr( PATH, NUNIT )
2 *
3  include 'plasmaf.h'
4 *
5 * -- LAPACK test routine (version 3.1) --
6 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
7 * November 2006
8 *
9 * .. Scalar Arguments ..
10  CHARACTER*3 path
11  INTEGER nunit
12 * ..
13 *
14 * Purpose
15 * =======
16 *
17 * DERRQR tests the error exits for the DOUBLE PRECISION routines
18 * that use the QR decomposition of a general matrix.
19 *
20 * Arguments
21 * =========
22 *
23 * PATH (input) CHARACTER*3
24 * The LAPACK path name for the routines to be tested.
25 *
26 * NUNIT (input) INTEGER
27 * The unit number for output.
28 *
29 * =====================================================================
30 *
31 * .. Parameters ..
32  INTEGER nmax
33  parameter( nmax = 2 )
34 * ..
35 * .. Local Scalars ..
36  INTEGER i, info, j
37 * ..
38 * .. Local Arrays ..
39  DOUBLE PRECISION a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
40  $ w( nmax ), x( nmax )
41  INTEGER ht( 2 )
42 * ..
43 * .. External Subroutines ..
44  EXTERNAL alaesm, chkxer, dgeqr2, dgeqrf, dorg2r,
45  $ dorgqr, dorm2r, dormqr
46 * ..
47 * .. Scalars in Common ..
48  LOGICAL lerr, ok
49  CHARACTER*32 srnamt
50  INTEGER infot, nout
51 * ..
52 * .. Common blocks ..
53  common / infoc / infot, nout, ok, lerr
54  common / srnamc / srnamt
55 * ..
56 * .. Intrinsic Functions ..
57  INTRINSIC dble
58 * ..
59 * .. Executable Statements ..
60 *
61  nout = nunit
62  WRITE( nout, fmt = * )
63 *
64 * Disable PLASMA warnings/errors
65 *
66  CALL plasma_disable( plasma_warnings, info )
67  CALL plasma_disable( plasma_errors, info )
68 *
69 * Set the variables to innocuous values.
70 *
71  DO 20 j = 1, nmax
72  DO 10 i = 1, nmax
73  a( i, j ) = 1.d0 / dble( i+j )
74  af( i, j ) = 1.d0 / dble( i+j )
75  10 continue
76  b( j ) = 0.d0
77  w( j ) = 0.d0
78  x( j ) = 0.d0
79  20 continue
80  ok = .true.
81 *
82 * Allocate HT
83 *
84  CALL plasma_alloc_workspace_dgeqrf( 2, 2, ht, info )
85 
86 *
87 * Error exits for QR factorization
88 *
89 * PLASMA_DGEQRF
90 *
91  srnamt = 'DGEQRF'
92  infot = 1
93  CALL plasma_dgeqrf( -1, 0, a, 1, ht, info )
94  CALL chkxer( 'DGEQRF', infot, nout, info, ok )
95  infot = 2
96  CALL plasma_dgeqrf( 0, -1, a, 1, ht, info )
97  CALL chkxer( 'DGEQRF', infot, nout, info, ok )
98  infot = 4
99  CALL plasma_dgeqrf( 2, 1, a, 1, ht, info )
100  CALL chkxer( 'DGEQRF', infot, nout, info, ok )
101 *
102 * DGEQRS
103 *
104  srnamt = 'DGEQRS'
105  infot = 1
106  CALL plasma_dgeqrs( -1, 0, 0, a, 1, ht, b, 1, info )
107  CALL chkxer( 'DGEQRS', infot, nout, info, ok )
108  infot = 2
109  CALL plasma_dgeqrs( 0, -1, 0, a, 1, ht, b, 1, info )
110  CALL chkxer( 'DGEQRS', infot, nout, info, ok )
111  infot = 2
112  CALL plasma_dgeqrs( 1, 2, 0, a, 2, ht, b, 2, info )
113  CALL chkxer( 'DGEQRS', infot, nout, info, ok )
114  infot = 3
115  CALL plasma_dgeqrs( 0, 0, -1, a, 1, ht, b, 1, info )
116  CALL chkxer( 'DGEQRS', infot, nout, info, ok )
117  infot = 5
118  CALL plasma_dgeqrs( 2, 1, 0, a, 1, ht, b, 2, info )
119  CALL chkxer( 'DGEQRS', infot, nout, info, ok )
120  infot = 8
121  CALL plasma_dgeqrs( 2, 1, 0, a, 2, ht, b, 1, info )
122  CALL chkxer( 'DGEQRS', infot, nout, info, ok )
123 *
124 * DORGQR
125 *
126  srnamt = 'DORGQR'
127  infot = 1
128  CALL plasma_dorgqr( -1, 0, 0, a, 1, ht, w, 1, info )
129  CALL chkxer( 'DORGQR', infot, nout, info, ok )
130  infot = 2
131  CALL plasma_dorgqr( 0, -1, 0, a, 1, ht, w, 1, info )
132  CALL chkxer( 'DORGQR', infot, nout, info, ok )
133  infot = 2
134  CALL plasma_dorgqr( 1, 2, 0, a, 1, ht, w, 2, info )
135  CALL chkxer( 'DORGQR', infot, nout, info, ok )
136  infot = 3
137  CALL plasma_dorgqr( 0, 0, -1, a, 1, ht, w, 1, info )
138  CALL chkxer( 'DORGQR', infot, nout, info, ok )
139  infot = 3
140  CALL plasma_dorgqr( 1, 1, 2, a, 1, ht, w, 1, info )
141  CALL chkxer( 'DORGQR', infot, nout, info, ok )
142  infot = 5
143  CALL plasma_dorgqr( 2, 2, 0, a, 1, ht, w, 2, info )
144  CALL chkxer( 'DORGQR', infot, nout, info, ok )
145  infot = 8
146  CALL plasma_dorgqr( 2, 2, 0, a, 2, ht, w, 1, info )
147  CALL chkxer( 'DORGQR', infot, nout, info, ok )
148 *
149 * PLASMA_DORMQR
150 *
151  srnamt = 'DORMQR'
152  infot = 1
153  CALL plasma_dormqr( '/', plasmatrans, 0, 0, 0, a, 1, ht, af, 1,
154  $ info )
155  CALL chkxer( 'DORMQR', infot, nout, info, ok )
156  infot = 2
157  CALL plasma_dormqr( plasmaleft, '/', 0, 0, 0, a, 1, ht, af, 1,
158  $ info )
159  CALL chkxer( 'DORMQR', infot, nout, info, ok )
160  infot = 3
161  CALL plasma_dormqr( plasmaleft, plasmatrans, -1, 0, 0, a, 1, ht,
162  $ af, 1, info )
163  CALL chkxer( 'DORMQR', infot, nout, info, ok )
164  infot = 4
165  CALL plasma_dormqr( plasmaleft, plasmatrans, 0, -1, 0, a, 1, ht,
166  $ af, 1, info )
167  CALL chkxer( 'DORMQR', infot, nout, info, ok )
168  infot = 5
169  CALL plasma_dormqr( plasmaleft, plasmatrans, 0, 0, -1, a, 1, ht,
170  $ af, 1, info )
171  CALL chkxer( 'DORMQR', infot, nout, info, ok )
172 * INFOT = 5
173 * CALL PLASMA_DORMQR( PLASMALEFT, PLASMATRANS, 0, 1, 1, A, 1, HT,
174 * 4 AF, 1, INFO )
175 * CALL CHKXER( 'DORMQR', INFOT, NOUT, INFO, OK )
176 * INFOT = 5
177 * CALL PLASMA_DORMQR( PLASMALEFT, PLASMATRANS, 1, 0, 1, A, 1, HT,
178 * 4 AF, 1, INFO )
179 * CALL CHKXER( 'DORMQR', INFOT, NOUT, INFO, OK )
180 * INFOT = 7
181 * CALL PLASMA_DORMQR( PLASMALEFT, PLASMATRANS, 2, 1, 0, A, 1, HT,
182 * 4 AF, 2, INFO )
183 * CALL CHKXER( 'DORMQR', INFOT, NOUT, INFO, OK )
184 * INFOT = 7
185 * CALL PLASMA_DORMQR( PLASMALEFT, PLASMATRANS, 1, 2, 0, A, 1, HT,
186 * 4 AF, 1, INFO )
187 * CALL CHKXER( 'DORMQR', INFOT, NOUT, INFO, OK )
188 * INFOT = 10
189 * CALL PLASMA_DORMQR( PLASMALEFT, PLASMATRANS, 1, 2, 0, A, 1, HT,
190 * 4 AF, 1, INFO )
191 * CALL CHKXER( 'DORMQR', INFOT, NOUT, INFO, OK )
192 * INFOT = 10
193 * CALL PLASMA_DORMQR( PLASMALEFT, PLASMATRANS, 2, 1, 0, A, 1, HT,
194 * 4 AF, 2, INFO )
195 * CALL CHKXER( 'DORMQR', INFOT, NOUT, INFO, OK )
196 *
197 * Print a summary line.
198 *
199  CALL alaesm( path, ok, nout )
200 *
201 * Deallocate HT
202 *
203  CALL plasma_dealloc_handle( ht, info )
204 *
205 * Enable PLASMA warnings/errors
206 *
207  CALL plasma_enable( plasma_warnings, info )
208  CALL plasma_enable( plasma_errors, info )
209 *
210  return
211 *
212 * End of DERRQR
213 *
214  END