3
4
5
6
7
8
9
10
11
12 IMPLICIT NONE
13
14
15 INTEGER N, IX, JX, INCX, IY, JY, INCY, LWORK, INFO
16 DOUBLE PRECISION CS, SN
17
18
19 INTEGER DESCX( * ), DESCY( * )
20 DOUBLE PRECISION X( * ), Y( * ), WORK( * )
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 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
177 $ LLD_, MB_, M_, NB_, N_, RSRC_
178 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
179 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
180 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
181
182
183 LOGICAL LQUERY, LEFT, RIGHT
184 INTEGER ICTXT, NPROW, NPCOL, MYROW, MYCOL, NPROCS,
185 $ MB, NB, XYROWS, XYCOLS, RSRC1, RSRC2, CSRC1,
186 $ CSRC2, ICOFFXY, IROFFXY, MNWRK, LLDX, LLDY,
187 $ INDX, JXX, XLOC1, XLOC2, RSRC, CSRC, YLOC1,
188 $ YLOC2, JYY, IXX, IYY
189
190
191 INTEGER NUMROC, INDXG2P, INDXG2L
193
194
195 EXTERNAL drot
196
197
199
200
201 INTEGER ICEIL
202
203
204
205
206
207 ictxt = descx( ctxt_ )
208 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
209 nprocs = nprow*npcol
210
211
212
213 lquery = lwork.EQ.-1
214 info = 0
215 IF( n.LT.0 ) THEN
216 info = -1
217 ELSEIF( ix.LT.1 .OR. ix.GT.descx(m_) ) THEN
218 info = -3
219 ELSEIF( jx.LT.1 .OR. jx.GT.descx(n_) ) THEN
220 info = -4
221 ELSEIF( incx.NE.1 .AND. incx.NE.descx(m_) ) THEN
222 info = -6
223 ELSEIF( iy.LT.1 .OR. iy.GT.descy(m_) ) THEN
224 info = -8
225 ELSEIF( jy.LT.1 .OR. jy.GT.descy(n_) ) THEN
226 info = -9
227 ELSEIF( incy.NE.1 .AND. incy.NE.descy(m_) ) THEN
228 info = -11
229 ELSEIF( (incx.EQ.descx(m_) .AND. incy.NE.descy(m_)) .OR.
230 $ (incx.EQ.1 .AND. incy.NE.1 ) ) THEN
231 info = -11
232 ELSEIF( (incx.EQ.1 .AND. incy.EQ.1) .AND.
233 $ ix.NE.iy ) THEN
234 info = -8
235 ELSEIF( (incx.EQ.descx(m_) .AND. incy.EQ.descy(m_)) .AND.
236 $ jx.NE.jy ) THEN
237 info = -9
238 END IF
239
240
241
242 left = incx.EQ.descx(m_) .AND. incy.EQ.descy(m_)
243 right = incx.EQ.1 .AND. incy.EQ.1
244
245
246
247 IF( info.EQ.0 ) THEN
248 IF( left .AND. descx(nb_).NE.descy(nb_) ) THEN
249 info = -(100*5 + nb_)
250 END IF
251 IF( right .AND. descx(mb_).NE.descy(nb_) ) THEN
252 info = -(100*10 + mb_)
253 END IF
254 END IF
255 IF( info.EQ.0 ) THEN
256 IF( left .AND. descx(csrc_).NE.descy(csrc_) ) THEN
257 info = -(100*5 + csrc_)
258 END IF
259 IF( right .AND. descx(rsrc_).NE.descy(rsrc_) ) THEN
260 info = -(100*10 + rsrc_)
261 END IF
262 END IF
263
264
265
266 mb = descx( mb_ )
267 nb = descx( nb_ )
268 IF( left ) THEN
269 rsrc1 =
indxg2p( ix, mb, myrow, descx(rsrc_), nprow )
270 rsrc2 =
indxg2p( iy, mb, myrow, descy(rsrc_), nprow )
271 csrc =
indxg2p( jx, nb, mycol, descx(csrc_), npcol )
272 icoffxy = mod( jx - 1, nb )
273 xycols =
numroc( n+icoffxy, nb, mycol, csrc, npcol )
274 IF( ( myrow.EQ.rsrc1 .OR. myrow.EQ.rsrc2 ) .AND.
275 $ mycol.EQ.csrc ) xycols = xycols - icoffxy
276 IF( rsrc1.NE.rsrc2 ) THEN
277 mnwrk = xycols
278 ELSE
279 mnwrk = 0
280 END IF
281 ELSEIF( right ) THEN
282 csrc1 =
indxg2p( jx, nb, mycol, descx(csrc_), npcol )
283 csrc2 =
indxg2p( jy, nb, mycol, descy(csrc_), npcol )
284 rsrc =
indxg2p( ix, mb, myrow, descx(rsrc_), nprow )
285 iroffxy = mod( ix - 1, mb )
286 xyrows =
numroc( n+iroffxy, mb, myrow, rsrc, nprow )
287 IF( ( mycol.EQ.csrc1 .OR. mycol.EQ.csrc2 ) .AND.
288 $ myrow.EQ.rsrc ) xyrows = xyrows - iroffxy
289 IF( csrc1.NE.csrc2 ) THEN
290 mnwrk = xyrows
291 ELSE
292 mnwrk = 0
293 END IF
294 END IF
295 IF( info.EQ.0 ) THEN
296 IF( .NOT.lquery . and. lwork.LT.mnwrk ) info = -15
297 END IF
298
299
300
301 IF( info.NE.0 ) THEN
302 CALL pxerbla( ictxt,
'PDROT', -info )
303 RETURN
304 ELSEIF( lquery ) THEN
305 work( 1 ) = dble(mnwrk)
306 RETURN
307 END IF
308
309
310
311 IF( n.EQ.0 ) THEN
312 RETURN
313 END IF
314
315
316
317 lldx = descx( lld_ )
318 lldy = descy( lld_ )
319
320
321
322
323 IF( nprocs.EQ.1 ) THEN
324 IF( left ) THEN
325 CALL drot( n, x((jx-1)*lldx+ix), lldx, y((jy-1)*lldy+iy),
326 $ lldy, cs, sn )
327 ELSEIF( right ) THEN
328 CALL drot( n, x((jx-1)*lldx+ix), 1, y((jy-1)*lldy+iy),
329 $ 1, cs, sn )
330 END IF
331 RETURN
332 END IF
333
334
335
336
337 IF( left ) THEN
338 DO 10 indx = 1, npcol
339 IF( myrow.EQ.rsrc1 .AND. xycols.GT.0 ) THEN
340 IF( indx.EQ.1 ) THEN
341 jxx = jx
342 ELSE
343 jxx = jx-icoffxy + (indx-1)*nb
344 END IF
345 CALL infog2l( ix, jxx, descx, nprow, npcol, myrow,
346 $ mycol, xloc1, xloc2, rsrc, csrc )
347 IF( myrow.EQ.rsrc .AND. mycol.EQ.csrc ) THEN
348 IF( rsrc1.NE.rsrc2 ) THEN
349 CALL dgesd2d( ictxt, 1, xycols,
350 $ x((xloc2-1)*lldx+xloc1), lldx,
351 $ rsrc2, csrc )
352 CALL dgerv2d( ictxt, 1, xycols, work, 1,
353 $ rsrc2, csrc )
354 CALL drot( xycols, x((xloc2-1)*lldx+xloc1),
355 $ lldx, work, 1, cs, sn )
356 ELSE
357 CALL infog2l( iy, jxx, descy, nprow, npcol,
358 $ myrow, mycol, yloc1, yloc2, rsrc,
359 $ csrc )
360 CALL drot( xycols, x((xloc2-1)*lldx+xloc1),
361 $ lldx, y((yloc2-1)*lldy+yloc1), lldy, cs,
362 $ sn )
363 END IF
364 END IF
365 END IF
366 IF( myrow.EQ.rsrc2 .AND. rsrc1.NE.rsrc2 ) THEN
367 IF( indx.EQ.1 ) THEN
368 jyy = jy
369 ELSE
370 jyy = jy-icoffxy + (indx-1)*nb
371 END IF
372 CALL infog2l( iy, jyy, descy, nprow, npcol, myrow,
373 $ mycol, yloc1, yloc2, rsrc, csrc )
374 IF( myrow.EQ.rsrc .AND. mycol.EQ.csrc ) THEN
375 CALL dgesd2d( ictxt, 1, xycols,
376 $ y((yloc2-1)*lldy+yloc1), lldy,
377 $ rsrc1, csrc )
378 CALL dgerv2d( ictxt, 1, xycols, work, 1,
379 $ rsrc1, csrc )
380 CALL drot( xycols, work, 1, y((yloc2-1)*lldy+yloc1),
381 $ lldy, cs, sn )
382 END IF
383 END IF
384 10 CONTINUE
385 ELSEIF( right ) THEN
386 DO 20 indx = 1, nprow
387 IF( mycol.EQ.csrc1 .AND. xyrows.GT.0 ) THEN
388 IF( indx.EQ.1 ) THEN
389 ixx = ix
390 ELSE
391 ixx = ix-iroffxy + (indx-1)*mb
392 END IF
393 CALL infog2l( ixx, jx, descx, nprow, npcol, myrow,
394 $ mycol, xloc1, xloc2, rsrc, csrc )
395 IF( myrow.EQ.rsrc .AND. mycol.EQ.csrc ) THEN
396 IF( csrc1.NE.csrc2 ) THEN
397 CALL dgesd2d( ictxt, xyrows, 1,
398 $ x((xloc2-1)*lldx+xloc1), lldx,
399 $ rsrc, csrc2 )
400 CALL dgerv2d( ictxt, xyrows, 1, work, xyrows,
401 $ rsrc, csrc2 )
402 CALL drot( xyrows, x((xloc2-1)*lldx+xloc1),
403 $ 1, work, 1, cs, sn )
404 ELSE
405 CALL infog2l( ixx, jy, descy, nprow, npcol,
406 $ myrow, mycol, yloc1, yloc2, rsrc,
407 $ csrc )
408 CALL drot( xyrows, x((xloc2-1)*lldx+xloc1),
409 $ 1, y((yloc2-1)*lldy+yloc1), 1, cs,
410 $ sn )
411 END IF
412 END IF
413 END IF
414 IF( mycol.EQ.csrc2 .AND. csrc1.NE.csrc2 ) THEN
415 IF( indx.EQ.1 ) THEN
416 iyy = iy
417 ELSE
418 iyy = iy-iroffxy + (indx-1)*mb
419 END IF
420 CALL infog2l( iyy, jy, descy, nprow, npcol, myrow,
421 $ mycol, yloc1, yloc2, rsrc, csrc )
422 IF( myrow.EQ.rsrc .AND. mycol.EQ.csrc ) THEN
423 CALL dgesd2d( ictxt, xyrows, 1,
424 $ y((yloc2-1)*lldy+yloc1), lldy,
425 $ rsrc, csrc1 )
426 CALL dgerv2d( ictxt, xyrows, 1, work, xyrows,
427 $ rsrc, csrc1 )
428 CALL drot( xyrows, work, 1, y((yloc2-1)*lldy+yloc1),
429 $ 1, cs, sn )
430 END IF
431 END IF
432 20 CONTINUE
433 END IF
434
435
436
437 work( 1 ) = dble(mnwrk)
438 RETURN
439
440
441
integer function indxg2l(indxglob, nb, iproc, isrcproc, nprocs)
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
subroutine infog2l(grindx, gcindx, desc, nprow, npcol, myrow, mycol, lrindx, lcindx, rsrc, csrc)
integer function numroc(n, nb, iproc, isrcproc, nprocs)
subroutine pxerbla(ictxt, srname, info)