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

« back to all changes in this revision

Viewing changes to src/lapack/double/dormlq.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 DORMLQ
 
2
*
 
3
*  =========== DOCUMENTATION ===========
 
4
*
 
5
* Online html documentation available at 
 
6
*            http://www.netlib.org/lapack/explore-html/ 
 
7
*
 
8
*> \htmlonly
 
9
*> Download DORMLQ + dependencies 
 
10
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dormlq.f"> 
 
11
*> [TGZ]</a> 
 
12
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dormlq.f"> 
 
13
*> [ZIP]</a> 
 
14
*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dormlq.f"> 
 
15
*> [TXT]</a>
 
16
*> \endhtmlonly 
 
17
*
 
18
*  Definition:
 
19
*  ===========
 
20
*
 
21
*       SUBROUTINE DORMLQ( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
 
22
*                          WORK, LWORK, INFO )
 
23
 
24
*       .. Scalar Arguments ..
 
25
*       CHARACTER          SIDE, TRANS
 
26
*       INTEGER            INFO, K, LDA, LDC, LWORK, M, N
 
27
*       ..
 
28
*       .. Array Arguments ..
 
29
*       DOUBLE PRECISION   A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
 
30
*       ..
 
31
*  
 
32
*
 
33
*> \par Purpose:
 
34
*  =============
 
35
*>
 
36
*> \verbatim
 
37
*>
 
38
*> DORMLQ overwrites the general real M-by-N matrix C with
 
39
*>
 
40
*>                 SIDE = 'L'     SIDE = 'R'
 
41
*> TRANS = 'N':      Q * C          C * Q
 
42
*> TRANS = 'T':      Q**T * C       C * Q**T
 
43
*>
 
44
*> where Q is a real orthogonal matrix defined as the product of k
 
45
*> elementary reflectors
 
46
*>
 
47
*>       Q = H(k) . . . H(2) H(1)
 
48
*>
 
49
*> as returned by DGELQF. Q is of order M if SIDE = 'L' and of order N
 
50
*> if SIDE = 'R'.
 
51
*> \endverbatim
 
52
*
 
53
*  Arguments:
 
54
*  ==========
 
55
*
 
56
*> \param[in] SIDE
 
57
*> \verbatim
 
58
*>          SIDE is CHARACTER*1
 
59
*>          = 'L': apply Q or Q**T from the Left;
 
60
*>          = 'R': apply Q or Q**T from the Right.
 
61
*> \endverbatim
 
62
*>
 
63
*> \param[in] TRANS
 
64
*> \verbatim
 
65
*>          TRANS is CHARACTER*1
 
66
*>          = 'N':  No transpose, apply Q;
 
67
*>          = 'T':  Transpose, apply Q**T.
 
68
*> \endverbatim
 
69
*>
 
70
*> \param[in] M
 
71
*> \verbatim
 
72
*>          M is INTEGER
 
73
*>          The number of rows of the matrix C. M >= 0.
 
74
*> \endverbatim
 
75
*>
 
76
*> \param[in] N
 
77
*> \verbatim
 
78
*>          N is INTEGER
 
79
*>          The number of columns of the matrix C. N >= 0.
 
80
*> \endverbatim
 
81
*>
 
82
*> \param[in] K
 
83
*> \verbatim
 
84
*>          K is INTEGER
 
85
*>          The number of elementary reflectors whose product defines
 
86
*>          the matrix Q.
 
87
*>          If SIDE = 'L', M >= K >= 0;
 
88
*>          if SIDE = 'R', N >= K >= 0.
 
89
*> \endverbatim
 
90
*>
 
91
*> \param[in] A
 
92
*> \verbatim
 
93
*>          A is DOUBLE PRECISION array, dimension
 
94
*>                               (LDA,M) if SIDE = 'L',
 
95
*>                               (LDA,N) if SIDE = 'R'
 
96
*>          The i-th row must contain the vector which defines the
 
97
*>          elementary reflector H(i), for i = 1,2,...,k, as returned by
 
98
*>          DGELQF in the first k rows of its array argument A.
 
99
*> \endverbatim
 
100
*>
 
101
*> \param[in] LDA
 
102
*> \verbatim
 
103
*>          LDA is INTEGER
 
104
*>          The leading dimension of the array A. LDA >= max(1,K).
 
105
*> \endverbatim
 
106
*>
 
107
*> \param[in] TAU
 
108
*> \verbatim
 
109
*>          TAU is DOUBLE PRECISION array, dimension (K)
 
110
*>          TAU(i) must contain the scalar factor of the elementary
 
111
*>          reflector H(i), as returned by DGELQF.
 
112
*> \endverbatim
 
113
*>
 
114
*> \param[in,out] C
 
115
*> \verbatim
 
116
*>          C is DOUBLE PRECISION array, dimension (LDC,N)
 
117
*>          On entry, the M-by-N matrix C.
 
118
*>          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
 
119
*> \endverbatim
 
120
*>
 
121
*> \param[in] LDC
 
122
*> \verbatim
 
123
*>          LDC is INTEGER
 
124
*>          The leading dimension of the array C. LDC >= max(1,M).
 
125
*> \endverbatim
 
126
*>
 
127
*> \param[out] WORK
 
128
*> \verbatim
 
129
*>          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
 
130
*>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
 
131
*> \endverbatim
 
132
*>
 
133
*> \param[in] LWORK
 
134
*> \verbatim
 
135
*>          LWORK is INTEGER
 
136
*>          The dimension of the array WORK.
 
137
*>          If SIDE = 'L', LWORK >= max(1,N);
 
138
*>          if SIDE = 'R', LWORK >= max(1,M).
 
139
*>          For optimum performance LWORK >= N*NB if SIDE = 'L', and
 
140
*>          LWORK >= M*NB if SIDE = 'R', where NB is the optimal
 
141
*>          blocksize.
 
142
*>
 
143
*>          If LWORK = -1, then a workspace query is assumed; the routine
 
144
*>          only calculates the optimal size of the WORK array, returns
 
145
*>          this value as the first entry of the WORK array, and no error
 
146
*>          message related to LWORK is issued by XERBLA.
 
147
*> \endverbatim
 
148
*>
 
149
*> \param[out] INFO
 
150
*> \verbatim
 
151
*>          INFO is INTEGER
 
152
*>          = 0:  successful exit
 
153
*>          < 0:  if INFO = -i, the i-th argument had an illegal value
 
154
*> \endverbatim
 
155
*
 
156
*  Authors:
 
157
*  ========
 
158
*
 
159
*> \author Univ. of Tennessee 
 
160
*> \author Univ. of California Berkeley 
 
161
*> \author Univ. of Colorado Denver 
 
162
*> \author NAG Ltd. 
 
163
*
 
164
*> \date November 2011
 
165
*
 
166
*> \ingroup doubleOTHERcomputational
 
167
*
 
168
*  =====================================================================
1
169
      SUBROUTINE DORMLQ( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
2
170
     $                   WORK, LWORK, INFO )
3
171
*
4
 
*  -- LAPACK routine (version 2.0) --
5
 
*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
6
 
*     Courant Institute, Argonne National Lab, and Rice University
7
 
*     September 30, 1994
 
172
*  -- LAPACK computational routine (version 3.4.0) --
 
173
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 
174
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 
175
*     November 2011
8
176
*
9
177
*     .. Scalar Arguments ..
10
178
      CHARACTER          SIDE, TRANS
11
179
      INTEGER            INFO, K, LDA, LDC, LWORK, M, N
12
180
*     ..
13
181
*     .. Array Arguments ..
14
 
      DOUBLE PRECISION   A( LDA, * ), C( LDC, * ), TAU( * ),
15
 
     $                   WORK( LWORK )
 
182
      DOUBLE PRECISION   A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
16
183
*     ..
17
184
*
18
 
c
19
 
* $Id: dormlq.f 19697 2010-10-29 16:57:34Z d3y133 $
20
 
c
21
 
*  Purpose
22
 
*  =======
23
 
*
24
 
*  DORMLQ overwrites the general real M-by-N matrix C with
25
 
*
26
 
*                  SIDE = 'L'     SIDE = 'R'
27
 
*  TRANS = 'N':      Q * C          C * Q
28
 
*  TRANS = 'T':      Q**T * C       C * Q**T
29
 
*
30
 
*  where Q is a real orthogonal matrix defined as the product of k
31
 
*  elementary reflectors
32
 
*
33
 
*        Q = H(k) . . . H(2) H(1)
34
 
*
35
 
*  as returned by DGELQF. Q is of order M if SIDE = 'L' and of order N
36
 
*  if SIDE = 'R'.
37
 
*
38
 
*  Arguments
39
 
*  =========
40
 
*
41
 
*  SIDE    (input) CHARACTER*1
42
 
*          = 'L': apply Q or Q**T from the Left;
43
 
*          = 'R': apply Q or Q**T from the Right.
44
 
*
45
 
*  TRANS   (input) CHARACTER*1
46
 
*          = 'N':  No transpose, apply Q;
47
 
*          = 'T':  Transpose, apply Q**T.
48
 
*
49
 
*  M       (input) INTEGER
50
 
*          The number of rows of the matrix C. M >= 0.
51
 
*
52
 
*  N       (input) INTEGER
53
 
*          The number of columns of the matrix C. N >= 0.
54
 
*
55
 
*  K       (input) INTEGER
56
 
*          The number of elementary reflectors whose product defines
57
 
*          the matrix Q.
58
 
*          If SIDE = 'L', M >= K >= 0;
59
 
*          if SIDE = 'R', N >= K >= 0.
60
 
*
61
 
*  A       (input) DOUBLE PRECISION array, dimension
62
 
*                               (LDA,M) if SIDE = 'L',
63
 
*                               (LDA,N) if SIDE = 'R'
64
 
*          The i-th row must contain the vector which defines the
65
 
*          elementary reflector H(i), for i = 1,2,...,k, as returned by
66
 
*          DGELQF in the first k rows of its array argument A.
67
 
*          A is modified by the routine but restored on exit.
68
 
*
69
 
*  LDA     (input) INTEGER
70
 
*          The leading dimension of the array A. LDA >= max(1,K).
71
 
*
72
 
*  TAU     (input) DOUBLE PRECISION array, dimension (K)
73
 
*          TAU(i) must contain the scalar factor of the elementary
74
 
*          reflector H(i), as returned by DGELQF.
75
 
*
76
 
*  C       (input/output) DOUBLE PRECISION array, dimension (LDC,N)
77
 
*          On entry, the M-by-N matrix C.
78
 
*          On exit, C is overwritten by Q*C or Q**T*C or C*Q**T or C*Q.
79
 
*
80
 
*  LDC     (input) INTEGER
81
 
*          The leading dimension of the array C. LDC >= max(1,M).
82
 
*
83
 
*  WORK    (workspace/output) DOUBLE PRECISION array, dimension (LWORK)
84
 
*          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
85
 
*
86
 
*  LWORK   (input) INTEGER
87
 
*          The dimension of the array WORK.
88
 
*          If SIDE = 'L', LWORK >= max(1,N);
89
 
*          if SIDE = 'R', LWORK >= max(1,M).
90
 
*          For optimum performance LWORK >= N*NB if SIDE = 'L', and
91
 
*          LWORK >= M*NB if SIDE = 'R', where NB is the optimal
92
 
*          blocksize.
93
 
*
94
 
*  INFO    (output) INTEGER
95
 
*          = 0:  successful exit
96
 
*          < 0:  if INFO = -i, the i-th argument had an illegal value
97
 
*
98
185
*  =====================================================================
99
186
*
100
187
*     .. Parameters ..
102
189
      PARAMETER          ( NBMAX = 64, LDT = NBMAX+1 )
103
190
*     ..
104
191
*     .. Local Scalars ..
105
 
      LOGICAL            LEFT, NOTRAN
 
192
      LOGICAL            LEFT, LQUERY, NOTRAN
106
193
      CHARACTER          TRANST
107
194
      INTEGER            I, I1, I2, I3, IB, IC, IINFO, IWS, JC, LDWORK,
108
 
     $                   MI, NB, NBMIN, NI, NQ, NW
 
195
     $                   LWKOPT, MI, NB, NBMIN, NI, NQ, NW
109
196
*     ..
110
197
*     .. Local Arrays ..
111
198
      DOUBLE PRECISION   T( LDT, NBMAX )
128
215
      INFO = 0
129
216
      LEFT = LSAME( SIDE, 'L' )
130
217
      NOTRAN = LSAME( TRANS, 'N' )
 
218
      LQUERY = ( LWORK.EQ.-1 )
131
219
*
132
220
*     NQ is the order of Q and NW is the minimum dimension of WORK
133
221
*
152
240
         INFO = -7
153
241
      ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
154
242
         INFO = -10
155
 
      ELSE IF( LWORK.LT.MAX( 1, NW ) ) THEN
 
243
      ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
156
244
         INFO = -12
157
245
      END IF
 
246
*
 
247
      IF( INFO.EQ.0 ) THEN
 
248
*
 
249
*        Determine the block size.  NB may be at most NBMAX, where NBMAX
 
250
*        is used to define the local array T.
 
251
*
 
252
         NB = MIN( NBMAX, ILAENV( 1, 'DORMLQ', SIDE // TRANS, M, N, K,
 
253
     $        -1 ) )
 
254
         LWKOPT = MAX( 1, NW )*NB
 
255
         WORK( 1 ) = LWKOPT
 
256
      END IF
 
257
*
158
258
      IF( INFO.NE.0 ) THEN
159
259
         CALL XERBLA( 'DORMLQ', -INFO )
160
260
         RETURN
 
261
      ELSE IF( LQUERY ) THEN
 
262
         RETURN
161
263
      END IF
162
264
*
163
265
*     Quick return if possible
167
269
         RETURN
168
270
      END IF
169
271
*
170
 
*     Determine the block size.  NB may be at most NBMAX, where NBMAX
171
 
*     is used to define the local array T.
172
 
*
173
 
      NB = MIN( NBMAX, ILAENV( 1, 'DORMLQ', SIDE // TRANS, M, N, K,
174
 
     $     -1 ) )
175
272
      NBMIN = 2
176
273
      LDWORK = NW
177
274
      IF( NB.GT.1 .AND. NB.LT.K ) THEN
206
303
            I3 = -NB
207
304
         END IF
208
305
*
209
 
*  The following 2 lines are to take care of compiler warnings.
210
 
*
211
 
         IC = 1
212
 
         JC = 1
213
306
         IF( LEFT ) THEN
214
307
            NI = N
215
308
            JC = 1
234
327
     $                   LDA, TAU( I ), T, LDT )
235
328
            IF( LEFT ) THEN
236
329
*
237
 
*              H or H' is applied to C(i:m,1:n)
 
330
*              H or H**T is applied to C(i:m,1:n)
238
331
*
239
332
               MI = M - I + 1
240
333
               IC = I
241
334
            ELSE
242
335
*
243
 
*              H or H' is applied to C(1:m,i:n)
 
336
*              H or H**T is applied to C(1:m,i:n)
244
337
*
245
338
               NI = N - I + 1
246
339
               JC = I
247
340
            END IF
248
341
*
249
 
*           Apply H or H'
 
342
*           Apply H or H**T
250
343
*
251
344
            CALL DLARFB( SIDE, TRANST, 'Forward', 'Rowwise', MI, NI, IB,
252
345
     $                   A( I, I ), LDA, T, LDT, C( IC, JC ), LDC, WORK,
253
346
     $                   LDWORK )
254
347
   10    CONTINUE
255
348
      END IF
256
 
      WORK( 1 ) = IWS
 
349
      WORK( 1 ) = LWKOPT
257
350
      RETURN
258
351
*
259
352
*     End of DORMLQ