~ubuntu-branches/ubuntu/utopic/nwchem/utopic

« back to all changes in this revision

Viewing changes to src/lapack/single/cunmbr.f

  • Committer: Package Import Robot
  • Author(s): Michael Banck, Daniel Leidert, Andreas Tille, Michael Banck
  • Date: 2013-07-04 12:14:55 UTC
  • mfrom: (1.1.2)
  • Revision ID: package-import@ubuntu.com-20130704121455-5tvsx2qabor3nrui
Tags: 6.3-1
* New upstream release.
* Fixes anisotropic properties (Closes: #696361).
* New features include:
  + Multi-reference coupled cluster (MRCC) approaches
  + Hybrid DFT calculations with short-range HF 
  + New density-functionals including Minnesota (M08, M11) and HSE hybrid
    functionals
  + X-ray absorption spectroscopy (XAS) with TDDFT
  + Analytical gradients for the COSMO solvation model
  + Transition densities from TDDFT 
  + DFT+U and Electron-Transfer (ET) methods for plane wave calculations
  + Exploitation of space group symmetry in plane wave geometry optimizations
  + Local density of states (LDOS) collective variable added to Metadynamics
  + Various new XC functionals added for plane wave calculations, including
    hybrid and range-corrected ones
  + Electric field gradients with relativistic corrections 
  + Nudged Elastic Band optimization method
  + Updated basis sets and ECPs 

[ Daniel Leidert ]
* debian/watch: Fixed.

[ Andreas Tille ]
* debian/upstream: References

[ Michael Banck ]
* debian/upstream (Name): New field.
* debian/patches/02_makefile_flags.patch: Refreshed.
* debian/patches/06_statfs_kfreebsd.patch: Likewise.
* debian/patches/07_ga_target_force_linux.patch: Likewise.
* debian/patches/05_avoid_inline_assembler.patch: Removed, no longer needed.
* debian/patches/09_backported_6.1.1_fixes.patch: Likewise.
* debian/control (Build-Depends): Added gfortran-4.7 and gcc-4.7.
* debian/patches/10_force_gcc-4.7.patch: New patch, explicitly sets
  gfortran-4.7 and gcc-4.7, fixes test suite hang with gcc-4.8 (Closes:
  #701328, #713262).
* debian/testsuite: Added tests for COSMO analytical gradients and MRCC.
* debian/rules (MRCC_METHODS): New variable, required to enable MRCC methods.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
*> \brief \b CUNMBR
 
2
*
 
3
*  =========== DOCUMENTATION ===========
 
4
*
 
5
* Online html documentation available at 
 
6
*            http://www.netlib.org/lapack/explore-html/ 
 
7
*
 
8
*> \htmlonly
 
9
*> Download CUNMBR + dependencies 
 
10
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cunmbr.f"> 
 
11
*> [TGZ]</a> 
 
12
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cunmbr.f"> 
 
13
*> [ZIP]</a> 
 
14
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cunmbr.f"> 
 
15
*> [TXT]</a>
 
16
*> \endhtmlonly 
 
17
*
 
18
*  Definition:
 
19
*  ===========
 
20
*
 
21
*       SUBROUTINE CUNMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
 
22
*                          LDC, WORK, LWORK, INFO )
 
23
 
24
*       .. Scalar Arguments ..
 
25
*       CHARACTER          SIDE, TRANS, VECT
 
26
*       INTEGER            INFO, K, LDA, LDC, LWORK, M, N
 
27
*       ..
 
28
*       .. Array Arguments ..
 
29
*       COMPLEX            A( LDA, * ), C( LDC, * ), TAU( * ),
 
30
*      $                   WORK( * )
 
31
*       ..
 
32
*  
 
33
*
 
34
*> \par Purpose:
 
35
*  =============
 
36
*>
 
37
*> \verbatim
 
38
*>
 
39
*> If VECT = 'Q', CUNMBR overwrites the general complex M-by-N matrix C
 
40
*> with
 
41
*>                 SIDE = 'L'     SIDE = 'R'
 
42
*> TRANS = 'N':      Q * C          C * Q
 
43
*> TRANS = 'C':      Q**H * C       C * Q**H
 
44
*>
 
45
*> If VECT = 'P', CUNMBR overwrites the general complex M-by-N matrix C
 
46
*> with
 
47
*>                 SIDE = 'L'     SIDE = 'R'
 
48
*> TRANS = 'N':      P * C          C * P
 
49
*> TRANS = 'C':      P**H * C       C * P**H
 
50
*>
 
51
*> Here Q and P**H are the unitary matrices determined by CGEBRD when
 
52
*> reducing a complex matrix A to bidiagonal form: A = Q * B * P**H. Q
 
53
*> and P**H are defined as products of elementary reflectors H(i) and
 
54
*> G(i) respectively.
 
55
*>
 
56
*> Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the
 
57
*> order of the unitary matrix Q or P**H that is applied.
 
58
*>
 
59
*> If VECT = 'Q', A is assumed to have been an NQ-by-K matrix:
 
60
*> if nq >= k, Q = H(1) H(2) . . . H(k);
 
61
*> if nq < k, Q = H(1) H(2) . . . H(nq-1).
 
62
*>
 
63
*> If VECT = 'P', A is assumed to have been a K-by-NQ matrix:
 
64
*> if k < nq, P = G(1) G(2) . . . G(k);
 
65
*> if k >= nq, P = G(1) G(2) . . . G(nq-1).
 
66
*> \endverbatim
 
67
*
 
68
*  Arguments:
 
69
*  ==========
 
70
*
 
71
*> \param[in] VECT
 
72
*> \verbatim
 
73
*>          VECT is CHARACTER*1
 
74
*>          = 'Q': apply Q or Q**H;
 
75
*>          = 'P': apply P or P**H.
 
76
*> \endverbatim
 
77
*>
 
78
*> \param[in] SIDE
 
79
*> \verbatim
 
80
*>          SIDE is CHARACTER*1
 
81
*>          = 'L': apply Q, Q**H, P or P**H from the Left;
 
82
*>          = 'R': apply Q, Q**H, P or P**H from the Right.
 
83
*> \endverbatim
 
84
*>
 
85
*> \param[in] TRANS
 
86
*> \verbatim
 
87
*>          TRANS is CHARACTER*1
 
88
*>          = 'N':  No transpose, apply Q or P;
 
89
*>          = 'C':  Conjugate transpose, apply Q**H or P**H.
 
90
*> \endverbatim
 
91
*>
 
92
*> \param[in] M
 
93
*> \verbatim
 
94
*>          M is INTEGER
 
95
*>          The number of rows of the matrix C. M >= 0.
 
96
*> \endverbatim
 
97
*>
 
98
*> \param[in] N
 
99
*> \verbatim
 
100
*>          N is INTEGER
 
101
*>          The number of columns of the matrix C. N >= 0.
 
102
*> \endverbatim
 
103
*>
 
104
*> \param[in] K
 
105
*> \verbatim
 
106
*>          K is INTEGER
 
107
*>          If VECT = 'Q', the number of columns in the original
 
108
*>          matrix reduced by CGEBRD.
 
109
*>          If VECT = 'P', the number of rows in the original
 
110
*>          matrix reduced by CGEBRD.
 
111
*>          K >= 0.
 
112
*> \endverbatim
 
113
*>
 
114
*> \param[in] A
 
115
*> \verbatim
 
116
*>          A is COMPLEX array, dimension
 
117
*>                                (LDA,min(nq,K)) if VECT = 'Q'
 
118
*>                                (LDA,nq)        if VECT = 'P'
 
119
*>          The vectors which define the elementary reflectors H(i) and
 
120
*>          G(i), whose products determine the matrices Q and P, as
 
121
*>          returned by CGEBRD.
 
122
*> \endverbatim
 
123
*>
 
124
*> \param[in] LDA
 
125
*> \verbatim
 
126
*>          LDA is INTEGER
 
127
*>          The leading dimension of the array A.
 
128
*>          If VECT = 'Q', LDA >= max(1,nq);
 
129
*>          if VECT = 'P', LDA >= max(1,min(nq,K)).
 
130
*> \endverbatim
 
131
*>
 
132
*> \param[in] TAU
 
133
*> \verbatim
 
134
*>          TAU is COMPLEX array, dimension (min(nq,K))
 
135
*>          TAU(i) must contain the scalar factor of the elementary
 
136
*>          reflector H(i) or G(i) which determines Q or P, as returned
 
137
*>          by CGEBRD in the array argument TAUQ or TAUP.
 
138
*> \endverbatim
 
139
*>
 
140
*> \param[in,out] C
 
141
*> \verbatim
 
142
*>          C is COMPLEX array, dimension (LDC,N)
 
143
*>          On entry, the M-by-N matrix C.
 
144
*>          On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q
 
145
*>          or P*C or P**H*C or C*P or C*P**H.
 
146
*> \endverbatim
 
147
*>
 
148
*> \param[in] LDC
 
149
*> \verbatim
 
150
*>          LDC is INTEGER
 
151
*>          The leading dimension of the array C. LDC >= max(1,M).
 
152
*> \endverbatim
 
153
*>
 
154
*> \param[out] WORK
 
155
*> \verbatim
 
156
*>          WORK is COMPLEX array, dimension (MAX(1,LWORK))
 
157
*>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
 
158
*> \endverbatim
 
159
*>
 
160
*> \param[in] LWORK
 
161
*> \verbatim
 
162
*>          LWORK is INTEGER
 
163
*>          The dimension of the array WORK.
 
164
*>          If SIDE = 'L', LWORK >= max(1,N);
 
165
*>          if SIDE = 'R', LWORK >= max(1,M);
 
166
*>          if N = 0 or M = 0, LWORK >= 1.
 
167
*>          For optimum performance LWORK >= max(1,N*NB) if SIDE = 'L',
 
168
*>          and LWORK >= max(1,M*NB) if SIDE = 'R', where NB is the
 
169
*>          optimal blocksize. (NB = 0 if M = 0 or N = 0.)
 
170
*>
 
171
*>          If LWORK = -1, then a workspace query is assumed; the routine
 
172
*>          only calculates the optimal size of the WORK array, returns
 
173
*>          this value as the first entry of the WORK array, and no error
 
174
*>          message related to LWORK is issued by XERBLA.
 
175
*> \endverbatim
 
176
*>
 
177
*> \param[out] INFO
 
178
*> \verbatim
 
179
*>          INFO is INTEGER
 
180
*>          = 0:  successful exit
 
181
*>          < 0:  if INFO = -i, the i-th argument had an illegal value
 
182
*> \endverbatim
 
183
*
 
184
*  Authors:
 
185
*  ========
 
186
*
 
187
*> \author Univ. of Tennessee 
 
188
*> \author Univ. of California Berkeley 
 
189
*> \author Univ. of Colorado Denver 
 
190
*> \author NAG Ltd. 
 
191
*
 
192
*> \date November 2011
 
193
*
 
194
*> \ingroup complexOTHERcomputational
 
195
*
 
196
*  =====================================================================
 
197
      SUBROUTINE CUNMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
 
198
     $                   LDC, WORK, LWORK, INFO )
 
199
*
 
200
*  -- LAPACK computational routine (version 3.4.0) --
 
201
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 
202
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 
203
*     November 2011
 
204
*
 
205
*     .. Scalar Arguments ..
 
206
      CHARACTER          SIDE, TRANS, VECT
 
207
      INTEGER            INFO, K, LDA, LDC, LWORK, M, N
 
208
*     ..
 
209
*     .. Array Arguments ..
 
210
      COMPLEX            A( LDA, * ), C( LDC, * ), TAU( * ),
 
211
     $                   WORK( * )
 
212
*     ..
 
213
*
 
214
*  =====================================================================
 
215
*
 
216
*     .. Local Scalars ..
 
217
      LOGICAL            APPLYQ, LEFT, LQUERY, NOTRAN
 
218
      CHARACTER          TRANST
 
219
      INTEGER            I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
 
220
*     ..
 
221
*     .. External Functions ..
 
222
      LOGICAL            LSAME
 
223
      INTEGER            ILAENV
 
224
      EXTERNAL           ILAENV, LSAME
 
225
*     ..
 
226
*     .. External Subroutines ..
 
227
      EXTERNAL           CUNMLQ, CUNMQR, XERBLA
 
228
*     ..
 
229
*     .. Intrinsic Functions ..
 
230
      INTRINSIC          MAX, MIN
 
231
*     ..
 
232
*     .. Executable Statements ..
 
233
*
 
234
*     Test the input arguments
 
235
*
 
236
      INFO = 0
 
237
      APPLYQ = LSAME( VECT, 'Q' )
 
238
      LEFT = LSAME( SIDE, 'L' )
 
239
      NOTRAN = LSAME( TRANS, 'N' )
 
240
      LQUERY = ( LWORK.EQ.-1 )
 
241
*
 
242
*     NQ is the order of Q or P and NW is the minimum dimension of WORK
 
243
*
 
244
      IF( LEFT ) THEN
 
245
         NQ = M
 
246
         NW = N
 
247
      ELSE
 
248
         NQ = N
 
249
         NW = M
 
250
      END IF
 
251
      IF( M.EQ.0 .OR. N.EQ.0 ) THEN
 
252
         NW = 0
 
253
      END IF
 
254
      IF( .NOT.APPLYQ .AND. .NOT.LSAME( VECT, 'P' ) ) THEN
 
255
         INFO = -1
 
256
      ELSE IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
 
257
         INFO = -2
 
258
      ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
 
259
         INFO = -3
 
260
      ELSE IF( M.LT.0 ) THEN
 
261
         INFO = -4
 
262
      ELSE IF( N.LT.0 ) THEN
 
263
         INFO = -5
 
264
      ELSE IF( K.LT.0 ) THEN
 
265
         INFO = -6
 
266
      ELSE IF( ( APPLYQ .AND. LDA.LT.MAX( 1, NQ ) ) .OR.
 
267
     $         ( .NOT.APPLYQ .AND. LDA.LT.MAX( 1, MIN( NQ, K ) ) ) )
 
268
     $          THEN
 
269
         INFO = -8
 
270
      ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
 
271
         INFO = -11
 
272
      ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
 
273
         INFO = -13
 
274
      END IF
 
275
*
 
276
      IF( INFO.EQ.0 ) THEN
 
277
         IF( NW.GT.0 ) THEN
 
278
            IF( APPLYQ ) THEN
 
279
               IF( LEFT ) THEN
 
280
                  NB = ILAENV( 1, 'CUNMQR', SIDE // TRANS, M-1, N, M-1,
 
281
     $                         -1 )
 
282
               ELSE
 
283
                  NB = ILAENV( 1, 'CUNMQR', SIDE // TRANS, M, N-1, N-1,
 
284
     $                         -1 )
 
285
               END IF
 
286
            ELSE
 
287
               IF( LEFT ) THEN
 
288
                  NB = ILAENV( 1, 'CUNMLQ', SIDE // TRANS, M-1, N, M-1,
 
289
     $                         -1 )
 
290
               ELSE
 
291
                  NB = ILAENV( 1, 'CUNMLQ', SIDE // TRANS, M, N-1, N-1,
 
292
     $                         -1 )
 
293
               END IF
 
294
            END IF
 
295
            LWKOPT = MAX( 1, NW*NB )
 
296
         ELSE
 
297
            LWKOPT = 1
 
298
         END IF
 
299
         WORK( 1 ) = LWKOPT
 
300
      END IF
 
301
*
 
302
      IF( INFO.NE.0 ) THEN
 
303
         CALL XERBLA( 'CUNMBR', -INFO )
 
304
         RETURN
 
305
      ELSE IF( LQUERY ) THEN
 
306
         RETURN
 
307
      END IF
 
308
*
 
309
*     Quick return if possible
 
310
*
 
311
      IF( M.EQ.0 .OR. N.EQ.0 )
 
312
     $   RETURN
 
313
*
 
314
      IF( APPLYQ ) THEN
 
315
*
 
316
*        Apply Q
 
317
*
 
318
         IF( NQ.GE.K ) THEN
 
319
*
 
320
*           Q was determined by a call to CGEBRD with nq >= k
 
321
*
 
322
            CALL CUNMQR( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
 
323
     $                   WORK, LWORK, IINFO )
 
324
         ELSE IF( NQ.GT.1 ) THEN
 
325
*
 
326
*           Q was determined by a call to CGEBRD with nq < k
 
327
*
 
328
            IF( LEFT ) THEN
 
329
               MI = M - 1
 
330
               NI = N
 
331
               I1 = 2
 
332
               I2 = 1
 
333
            ELSE
 
334
               MI = M
 
335
               NI = N - 1
 
336
               I1 = 1
 
337
               I2 = 2
 
338
            END IF
 
339
            CALL CUNMQR( SIDE, TRANS, MI, NI, NQ-1, A( 2, 1 ), LDA, TAU,
 
340
     $                   C( I1, I2 ), LDC, WORK, LWORK, IINFO )
 
341
         END IF
 
342
      ELSE
 
343
*
 
344
*        Apply P
 
345
*
 
346
         IF( NOTRAN ) THEN
 
347
            TRANST = 'C'
 
348
         ELSE
 
349
            TRANST = 'N'
 
350
         END IF
 
351
         IF( NQ.GT.K ) THEN
 
352
*
 
353
*           P was determined by a call to CGEBRD with nq > k
 
354
*
 
355
            CALL CUNMLQ( SIDE, TRANST, M, N, K, A, LDA, TAU, C, LDC,
 
356
     $                   WORK, LWORK, IINFO )
 
357
         ELSE IF( NQ.GT.1 ) THEN
 
358
*
 
359
*           P was determined by a call to CGEBRD with nq <= k
 
360
*
 
361
            IF( LEFT ) THEN
 
362
               MI = M - 1
 
363
               NI = N
 
364
               I1 = 2
 
365
               I2 = 1
 
366
            ELSE
 
367
               MI = M
 
368
               NI = N - 1
 
369
               I1 = 1
 
370
               I2 = 2
 
371
            END IF
 
372
            CALL CUNMLQ( SIDE, TRANST, MI, NI, NQ-1, A( 1, 2 ), LDA,
 
373
     $                   TAU, C( I1, I2 ), LDC, WORK, LWORK, IINFO )
 
374
         END IF
 
375
      END IF
 
376
      WORK( 1 ) = LWKOPT
 
377
      RETURN
 
378
*
 
379
*     End of CUNMBR
 
380
*
 
381
      END