3
4
5
6
7
8
9
10 CHARACTER JOBZ, UPLO
11 INTEGER IA, INFO, IZ, JA, JZ, LWORK, N
12
13
14 INTEGER DESCA( * ), DESCZ( * )
15 DOUBLE PRECISION A( * ), W( * ), WORK( * ), Z( * )
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237 INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
238 $ MB_, NB_, RSRC_, CSRC_, LLD_
239 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
240 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
241 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
242 DOUBLE PRECISION FIVE, ONE, TEN, ZERO
243 parameter( zero = 0.0d+0, one = 1.0d+0,
244 $ ten = 10.0d+0, five = 5.0d+0 )
245 INTEGER IERREIN, IERRCLS, IERRSPC, IERREBZ, ITHVAL
246 parameter( ierrein = 1, ierrcls = 2, ierrspc = 4,
247 $ ierrebz = 8, ithval = 10 )
248
249
250 LOGICAL LOWER, WANTZ
251 INTEGER CONTEXTC, CSRC_A, I, IACOL, IAROW, ICOFFA,
252 $ IINFO, INDD, INDD2, INDE, INDE2, INDTAU,
253 $ INDWORK, INDWORK2, IROFFA, IROFFZ, ISCALE,
254 $ IZROW, J, K, LDC, LLWORK, LWMIN, MB_A, MB_Z,
255 $ MYCOL, MYPCOLC, MYPROWC, MYROW, NB, NB_A, NB_Z,
256 $ NP, NPCOL, NPCOLC, NPROCS, NPROW, NPROWC, NQ,
257 $ NRC, QRMEM, RSRC_A, RSRC_Z, SIZEMQRLEFT,
258 $ SIZESYTRD
259 DOUBLE PRECISION ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA,
260 $ SMLNUM
261
262
263 INTEGER DESCQR( 9 ), IDUM1( 3 ), IDUM2( 3 )
264
265
266 LOGICAL LSAME
267 INTEGER INDXG2P, NUMROC, SL_GRIDRESHAPE
268 DOUBLE PRECISION PDLAMCH, PDLANSY
271
272
273 EXTERNAL blacs_gridexit, blacs_gridinfo,
chk1mat, dcopy,
277
278
279 INTRINSIC abs, dble, ichar,
max,
min, mod, sqrt, int
280
281
282
283 IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
284 $ rsrc_.LT.0 )RETURN
285
286
287
288 IF( n.EQ.0 ) RETURN
289
290
291
292 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
293 info = 0
294
295 wantz =
lsame( jobz,
'V' )
296 IF( nprow.EQ.-1 ) THEN
297 info = -( 700+ctxt_ )
298 ELSE IF( wantz ) THEN
299 IF( desca( ctxt_ ).NE.descz( ctxt_ ) ) THEN
300 info = -( 1200+ctxt_ )
301 END IF
302 END IF
303 IF( info .EQ. 0 ) THEN
304 CALL chk1mat( n, 3, n, 3, ia, ja, desca, 7, info )
305 IF( wantz )
306 $
CALL chk1mat( n, 3, n, 3, iz, jz, descz, 12, info )
307
308 IF( info.EQ.0 ) THEN
309
310
311
312 safmin =
pdlamch( desca( ctxt_ ),
'Safe minimum' )
313 eps =
pdlamch( desca( ctxt_ ),
'Precision' )
314 smlnum = safmin / eps
315 bignum = one / smlnum
316 rmin = sqrt( smlnum )
317 rmax =
min( sqrt( bignum ), one / sqrt( sqrt( safmin ) ) )
318
319 nprocs = nprow*npcol
320 nb_a = desca( nb_ )
321 mb_a = desca( mb_ )
322 nb = nb_a
323 lower =
lsame( uplo,
'L' )
324
325 rsrc_a = desca( rsrc_ )
326 csrc_a = desca( csrc_ )
327 iroffa = mod( ia-1, mb_a )
328 icoffa = mod( ja-1, nb_a )
329 iarow =
indxg2p( 1, nb_a, myrow, rsrc_a, nprow )
330 iacol =
indxg2p( 1, mb_a, mycol, csrc_a, npcol )
331 np =
numroc( n+iroffa, nb, myrow, iarow, nprow )
332 nq =
numroc( n+icoffa, nb, mycol, iacol, npcol )
333
334 IF( wantz ) THEN
335 nb_z = descz( nb_ )
336 mb_z = descz( mb_ )
337 rsrc_z = descz( rsrc_ )
338 iroffz = mod( iz-1, mb_a )
339 izrow =
indxg2p( 1, nb_a, myrow, rsrc_z, nprow )
340 sizemqrleft =
max( ( nb_a*( nb_a-1 ) ) / 2, ( np+nq )*
341 $ nb_a ) + nb_a*nb_a
342 ELSE
343 sizemqrleft = 0
344 iroffz = 0
345 izrow = 0
346 END IF
347 sizesytrd =
max( nb * ( np +1 ), 3 * nb )
348
349
350
351
352
353
354
355 ldc = 0
356 IF( wantz ) THEN
358 $ nprocs, 1 )
359 CALL blacs_gridinfo( contextc, nprowc, npcolc, myprowc,
360 $ mypcolc )
361 nrc =
numroc( n, nb_a, myprowc, 0, nprocs)
363 CALL descinit( descqr, n, n, nb, nb, 0, 0, contextc,
364 $ ldc, info )
365 END IF
366
367
368
369
370 indtau = 1
371 inde = indtau + n
372 indd = inde + n
373 indd2 = indd + n
374 inde2 = indd2 + n
375 indwork = inde2 + n
376 indwork2 = indwork + n*ldc
377 llwork = lwork - indwork + 1
378
379
380
381 qrmem = 2*n-2
382 IF( wantz ) THEN
383 lwmin = 5*n + n*ldc +
max( sizemqrleft, qrmem ) + 1
384 ELSE
385 lwmin = 5*n + sizesytrd + 1
386 END IF
387
388 END IF
389 IF( info.EQ.0 ) THEN
390 IF( .NOT.( wantz .OR.
lsame( jobz,
'N' ) ) )
THEN
391 info = -1
392 ELSE IF( .NOT.( lower .OR.
lsame( uplo,
'U' ) ) )
THEN
393 info = -2
394 ELSE IF( lwork.LT.lwmin .AND. lwork.NE.-1 ) THEN
395 info = -14
396 ELSE IF( iroffa.NE.0 ) THEN
397 info = -5
398 ELSE IF( desca( mb_ ).NE.desca( nb_ ) ) THEN
399 info = -( 700+nb_ )
400 END IF
401 IF( wantz ) THEN
402 IF( iroffa.NE.iroffz ) THEN
403 info = -10
404 ELSE IF( iarow.NE.izrow ) THEN
405 info = -10
406 ELSE IF( desca( m_ ).NE.descz( m_ ) ) THEN
407 info = -( 1200+m_ )
408 ELSE IF( desca( n_ ).NE.descz( n_ ) ) THEN
409 info = -( 1200+n_ )
410 ELSE IF( desca( mb_ ).NE.descz( mb_ ) ) THEN
411 info = -( 1200+mb_ )
412 ELSE IF( desca( nb_ ).NE.descz( nb_ ) ) THEN
413 info = -( 1200+nb_ )
414 ELSE IF( desca( rsrc_ ).NE.descz( rsrc_ ) ) THEN
415 info = -( 1200+rsrc_ )
416 ELSE IF( desca( ctxt_ ).NE.descz( ctxt_ ) ) THEN
417 info = -( 1200+ctxt_ )
418 ENDIF
419 END IF
420 END IF
421 IF( wantz ) THEN
422 idum1( 1 ) = ichar( 'V' )
423 ELSE
424 idum1( 1 ) = ichar( 'N' )
425 END IF
426 idum2( 1 ) = 1
427 IF( lower ) THEN
428 idum1( 2 ) = ichar( 'L' )
429 ELSE
430 idum1( 2 ) = ichar( 'U' )
431 END IF
432 idum2( 2 ) = 2
433 IF( lwork.EQ.-1 ) THEN
434 idum1( 3 ) = -1
435 ELSE
436 idum1( 3 ) = 1
437 END IF
438 idum2( 3 ) = 3
439 IF(
lsame( jobz,
'V' ) )
THEN
440 CALL pchk2mat( n, 3, n, 3, ia, ja, desca, 7, n, 3, n, 3,
441 $ iz, jz, descz, 12, 3, idum1, idum2, info )
442 ELSE
443 CALL pchk1mat( n, 3, n, 3, ia, ja, desca, 7, 3, idum1,
444 $ idum2, info )
445 END IF
446
447
448
449 work( 1 ) = dble( lwmin )
450 END IF
451
452 IF( info.NE.0 ) THEN
453 CALL pxerbla( desca( ctxt_ ),
'PDSYEV', -info )
454 IF( wantz ) CALL blacs_gridexit( contextc )
455 RETURN
456 ELSE IF( lwork .EQ. -1 ) THEN
457 IF( wantz ) CALL blacs_gridexit( contextc )
458 RETURN
459 END IF
460
461
462
463 iscale = 0
464
465 anrm =
pdlansy(
'M', uplo, n, a, ia, ja, desca, work( indwork ) )
466
467
468 IF( anrm.GT.zero .AND. anrm.LT.rmin ) THEN
469 iscale = 1
470 sigma = rmin / anrm
471 ELSE IF( anrm.GT.rmax ) THEN
472 iscale = 1
473 sigma = rmax / anrm
474 END IF
475
476 IF( iscale.EQ.1 ) THEN
477 CALL pdlascl( uplo, one, sigma, n, n, a, ia, ja, desca, iinfo )
478 END IF
479
480
481
482 CALL pdsytrd( uplo, n, a, ia, ja, desca, work( indd ),
483 $ work( inde ), work( indtau ), work( indwork ),
484 $ llwork, iinfo )
485
486
487
488 DO 10 i=1,n
489 CALL pdelget(
'A',
' ', work(indd2+i-1), a,
490 $ i+ia-1, i+ja-1, desca )
491 10 CONTINUE
492 IF(
lsame( uplo,
'U') )
THEN
493 DO 20 i=1,n-1
494 CALL pdelget(
'A',
' ', work(inde2+i-1), a,
495 $ i+ia-1, i+ja, desca )
496 20 CONTINUE
497 ELSE
498 DO 30 i=1,n-1
499 CALL pdelget(
'A',
' ', work(inde2+i-1), a,
500 $ i+ia, i+ja-1, desca )
501 30 CONTINUE
502 ENDIF
503
504 IF( wantz ) THEN
505
506 CALL pdlaset(
'Full', n, n, zero, one, work( indwork ), 1, 1,
507 $ descqr )
508
509
510
511
512
513 CALL dsteqr2(
'I', n, work( indd2 ), work( inde2 ),
514 $ work( indwork ), ldc, nrc, work( indwork2 ),
515 $ info )
516
517 CALL pdgemr2d( n, n, work( indwork ), 1, 1, descqr, z, ia, ja,
518 $ descz, contextc )
519
520 CALL pdormtr(
'L', uplo,
'N', n, n, a, ia, ja, desca,
521 $ work( indtau ), z, iz, jz, descz,
522 $ work( indwork ), llwork, iinfo )
523
524 ELSE
525
526 CALL dsteqr2(
'N', n, work( indd2 ), work( inde2 ),
527 $ work( indwork ), 1, 1, work( indwork2 ),
528 $ info )
529 ENDIF
530
531
532
533 CALL dcopy( n, work( indd2 ), 1, w, 1 )
534
535
536
537 IF( iscale .EQ. 1 ) THEN
538 CALL dscal( n, one / sigma, w, 1 )
539 END IF
540
541
542
543 IF( wantz ) THEN
544 CALL blacs_gridexit( contextc )
545 END IF
546
547
548
549
550 IF( n.LE.ithval ) THEN
551 j = n
552 k = 1
553 ELSE
554 j = n/ithval
555 k = ithval
556 END IF
557
558 DO 40 i = 1, j
559 work( i+indtau ) = w( (i-1)*k+1 )
560 work( i+inde ) = w( (i-1)*k+1 )
561 40 CONTINUE
562
563 CALL dgamn2d( desca( ctxt_ ), 'a', ' ', j, 1, work( 1+indtau ),
564 $ j, 1, 1, -1, -1, 0 )
565 CALL dgamx2d( desca( ctxt_ ), 'a', ' ', j, 1, work( 1+inde ),
566 $ j, 1, 1, -1, -1, 0 )
567
568 DO 50 i = 1, j
569 IF( info.EQ.0 .AND. ( work( i+indtau )-work( i+inde )
570 $ .NE. zero ) )THEN
571 info = n+1
572 END IF
573 50 CONTINUE
574
575 RETURN
576
577
578
Int sl_gridreshape(Int *ctxt, Int *pstart, Int *row_major_in, Int *row_major_out, Int *P, Int *Q)
subroutine chk1mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, info)
subroutine descinit(desc, m, n, mb, nb, irsrc, icsrc, ictxt, lld, info)
subroutine dsteqr2(compz, n, d, e, z, ldz, nr, work, info)
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
integer function numroc(n, nb, iproc, isrcproc, nprocs)
subroutine pchk1mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, nextra, ex, expos, info)
subroutine pchk2mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, mb, mbpos0, nb, nbpos0, ib, jb, descb, descbpos0, nextra, ex, expos, info)
subroutine pdlaset(uplo, m, n, alpha, beta, a, ia, ja, desca)
double precision function pdlamch(ictxt, cmach)
subroutine pdelget(scope, top, alpha, a, ia, ja, desca)
double precision function pdlansy(norm, uplo, n, a, ia, ja, desca, work)
subroutine pdlascl(type, cfrom, cto, m, n, a, ia, ja, desca, info)
subroutine pdormtr(side, uplo, trans, m, n, a, ia, ja, desca, tau, c, ic, jc, descc, work, lwork, info)
subroutine pdsytrd(uplo, n, a, ia, ja, desca, d, e, tau, work, lwork, info)
subroutine pxerbla(ictxt, srname, info)