1 SUBROUTINE pclarzb( SIDE, TRANS, DIRECT, STOREV, M, N, K, L, V,
2 $ IV, JV, DESCV, T, C, IC, JC, DESCC, WORK )
9 CHARACTER DIRECT, SIDE, STOREV, TRANS
10 INTEGER IC, IV, JC, JV, K, L, M, N
13 INTEGER DESCC( * ), DESCV( * )
14 COMPLEX C( * ), T( * ), V( * ), WORK( * )
221 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
222 $ lld_, mb_, m_, nb_, n_, rsrc_
223 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
224 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
225 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
227 parameter( one = ( 1.0e+0, 0.0e+0 ),
228 $ zero = ( 0.0e+0, 0.0e+0 ) )
232 CHARACTER COLBTOP, TRANST
233 INTEGER ICCOL1, ICCOL2, ICOFFC1, ICOFFC2, ICOFFV,
234 $ icrow1, icrow2, ictxt, iibeg, iic1, iic2,
235 $ iiend, iinxt, iiv, ileft, info, ioffc2, ioffv,
236 $ ipt, ipv, ipw, iroffc1, iroffc2, itop, ivcol,
237 $ ivrow, j, jjbeg, jjend, jjnxt, jjc1, jjc2, jjv,
238 $ ldc, ldv, lv, lw, mbc, mbv, mpc1, mpc2, mpc20,
239 $ mqv, mqv0, mycol, mydist, myrow, nbc, nbv,
240 $ npcol, nprow, nqc1, nqc2, nqcall, nqv
243 EXTERNAL blacs_abort, blacs_gridinfo, cgebr2d,
244 $ cgebs2d, cgemm, cgsum2d, clacgv,
245 $ clamov, claset, ctrbr2d, ctrbs2d,
254 INTEGER ICEIL, NUMROC
255 EXTERNAL iceil, lsame, numroc
261 IF( m.LE.0 .OR. n.LE.0 .OR. k.LE.0 )
266 ictxt = descc( ctxt_ )
267 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
272 IF( .NOT.lsame( direct,
'B' ) )
THEN
274 ELSE IF( .NOT.lsame( storev,
'R' ) )
THEN
278 CALL pxerbla( ictxt,
'PCLARZB', -info )
279 CALL blacs_abort( ictxt, 1 )
283 left = lsame( side,
'L' )
284 IF( lsame( trans,
'N' ) )
THEN
290 CALL infog2l( iv, jv, descv, nprow, npcol, myrow, mycol, iiv, jjv,
294 icoffv = mod( jv-1, nbv )
295 nqv = numroc( l+icoffv, nbv, mycol, ivcol, npcol )
299 iiv =
min( iiv, ldv )
300 jjv =
min( jjv,
max( 1, numroc( descv( n_ ), nbv, mycol,
301 $ descv( csrc_ ), npcol ) ) )
302 ioffv = iiv + ( jjv-1 ) * ldv
305 nqcall = numroc( descc( n_ ), nbc, mycol, descc( csrc_ ), npcol )
306 CALL infog2l( ic, jc, descc, nprow, npcol, myrow, mycol, iic1,
307 $ jjc1, icrow1, iccol1 )
309 iic1 =
min( iic1, ldc )
310 jjc1 =
min( jjc1,
max( 1, nqcall ) )
313 iroffc1 = mod( ic-1, mbc )
314 mpc1 = numroc( k+iroffc1, mbc, myrow, icrow1, nprow )
315 IF( myrow.EQ.icrow1 )
316 $ mpc1 = mpc1 - iroffc1
317 icoffc1 = mod( jc-1, nbc )
318 nqc1 = numroc( n+icoffc1, nbc, mycol, iccol1, npcol )
319 IF( mycol.EQ.iccol1 )
320 $ nqc1 = nqc1 - icoffc1
321 CALL infog2l( ic+m-l, jc, descc, nprow, npcol, myrow, mycol,
322 $ iic2, jjc2, icrow2, iccol2 )
323 iroffc2 = mod( ic+m-l-1, mbc )
324 mpc2 = numroc( l+iroffc2, mbc, myrow, icrow2, nprow )
325 IF( myrow.EQ.icrow2 )
326 $ mpc2 = mpc2 - iroffc2
330 iroffc1 = mod( ic-1, mbc )
331 mpc1 = numroc( m+iroffc1, mbc, myrow, icrow1, nprow )
332 IF( myrow.EQ.icrow1 )
333 $ mpc1 = mpc1 - iroffc1
334 icoffc1 = mod( jc-1, nbc )
335 nqc1 = numroc( k+icoffc1, nbc, mycol, iccol1, npcol )
336 IF( mycol.EQ.iccol1 )
337 $ nqc1 = nqc1 - icoffc1
338 CALL infog2l( ic, jc+n-l, descc, nprow, npcol, myrow, mycol,
339 $ iic2, jjc2, icrow2, iccol2 )
342 icoffc2 = mod( jc+n-l-1, nbc )
343 nqc2 = numroc( l+icoffc2, nbc, mycol, iccol2, npcol )
344 IF( mycol.EQ.iccol2 )
345 $ nqc2 = nqc2 - icoffc2
347 iic2 =
min( iic2, ldc )
348 jjc2 =
min( jjc2, nqcall )
349 ioffc2 = iic2 + ( jjc2-1 ) * ldc
351 IF( lsame( side,
'L' ) )
THEN
358 mqv0 = numroc( m+icoffv, nbv, mycol, ivcol, npcol )
359 IF( mycol.EQ.ivcol )
THEN
364 IF( myrow.EQ.icrow2 )
THEN
365 mpc20 = mpc2 + iroffc2
376 ipw = ipv + mpc20 * k
381 IF( myrow.EQ.ivrow )
THEN
382 IF( mycol.EQ.ivcol )
THEN
383 CALL clamov(
'All', k, mqv, v( ioffv ), ldv,
384 $ work( ipw+icoffv*lw ), lw )
386 CALL clamov(
'All', k, mqv, v( ioffv ), ldv,
393 CALL pbctran( ictxt,
'Rowwise',
'Conjugate transpose', k,
394 $ m+icoffv, descv( nb_ ), work( ipw ), lw, zero,
395 $ work( ipv ), lv, ivrow, ivcol, icrow2, -1,
400 IF( myrow.EQ.icrow2 )
401 $ ipv = ipv + iroffc2
409 CALL cgemm(
'Transpose',
'No transpose', nqc2, k, mpc2,
410 $ one, c( ioffc2 ), ldc, work( ipv ), lv, zero,
413 CALL claset(
'All', nqc2, k, zero, zero, work( ipw ), lw )
419 mydist = mod( myrow-icrow1+nprow, nprow )
420 itop =
max( 0, mydist * mbc - iroffc1 )
422 iiend = iic1 + mpc1 - 1
423 iinxt =
min( iceil( iibeg, mbc ) * mbc, iiend )
426 IF( iibeg.LE.iinxt )
THEN
427 CALL pbcmatadd( ictxt,
'Transpose', nqc2, iinxt-iibeg+1,
428 $ one, c( iibeg+(jjc1-1)*ldc ), ldc, one,
429 $ work( ipw+itop ), lw )
430 mydist = mydist + nprow
431 itop = mydist * mbc - iroffc1
433 iinxt =
min( iinxt+mbc, iiend )
438 CALL cgsum2d( ictxt,
'Columnwise',
' ', nqc2, k, work( ipw ),
443 IF( myrow.EQ.ivrow )
THEN
444 IF( mycol.EQ.ivcol )
THEN
448 CALL ctrbs2d( ictxt,
'Rowwise',
' ',
'Lower',
'Non unit',
451 CALL ctrbr2d( ictxt,
'Rowwise',
' ',
'Lower',
'Non unit',
452 $ k, k, t, mbv, myrow, ivcol )
454 CALL ctrmm(
'Right',
'Lower', transt,
'Non unit', nqc2, k,
455 $ one, t, mbv, work( ipw ), lw )
457 CALL cgebs2d( ictxt,
'Columnwise',
' ', nqc2, k,
460 CALL cgebr2d( ictxt,
'Columnwise',
' ', nqc2, k,
461 $ work( ipw ), lw, ivrow, mycol )
467 mydist = mod( myrow-icrow1+nprow, nprow )
468 itop =
max( 0, mydist * mbc - iroffc1 )
470 iiend = iic1 + mpc1 - 1
471 iinxt =
min( iceil( iibeg, mbc ) * mbc, iiend )
474 IF( iibeg.LE.iinxt )
THEN
475 CALL pbcmatadd( ictxt,
'Transpose', iinxt-iibeg+1, nqc2,
476 $ -one, work( ipw+itop ), lw, one,
477 $ c( iibeg+(jjc1-1)*ldc ), ldc )
478 mydist = mydist + nprow
479 itop = mydist * mbc - iroffc1
481 iinxt =
min( iinxt+mbc, iiend )
491 CALL clacgv( mpc2, work( ipv+(j-1)*lv ), 1 )
493 CALL cgemm(
'No transpose',
'Transpose', mpc2, nqc2, k, -one,
494 $ work( ipv ), lv, work( ipw ), lw, one,
512 CALL pb_topget( ictxt,
'Broadcast',
'Columnwise', colbtop )
513 IF( myrow.EQ.ivrow )
THEN
514 CALL cgebs2d( ictxt,
'Columnwise', colbtop, k, nqc2,
517 $
CALL ctrbs2d( ictxt,
'Columnwise', colbtop,
'Lower',
518 $
'Non unit', k, k, t, mbv )
519 CALL clamov(
'All', k, nqc2, v( ioffv ), ldv, work( ipv ),
522 CALL cgebr2d( ictxt,
'Columnwise', colbtop, k, nqc2,
523 $ work( ipv ), lv, ivrow, mycol )
525 $
CALL ctrbr2d( ictxt,
'Columnwise', colbtop,
'Lower',
526 $
'Non unit', k, k, t, mbv, ivrow, mycol )
533 CALL cgemm(
'No Transpose',
'Transpose', mpc2, k, nqc2,
534 $ one, c( ioffc2 ), ldc, work( ipv ), lv, zero,
537 CALL claset(
'All', mpc2, k, zero, zero, work( ipw ), lw )
543 mydist = mod( mycol-iccol1+npcol, npcol )
544 ileft =
max( 0, mydist * nbc - icoffc1 )
546 jjend = jjc1 + nqc1 - 1
547 jjnxt =
min( iceil( jjbeg, nbc ) * nbc, jjend )
550 IF( jjbeg.LE.jjnxt )
THEN
551 CALL pbcmatadd( ictxt,
'No transpose', mpc2,
552 $ jjnxt-jjbeg+1, one,
553 $ c( iic1+(jjbeg-1)*ldc ), ldc, one,
554 $ work( ipw+ileft*lw ), lw )
555 mydist = mydist + npcol
556 ileft = mydist * nbc - icoffc1
558 jjnxt =
min( jjnxt+nbc, jjend )
563 CALL cgsum2d( ictxt,
'Rowwise',
' ', mpc2, k, work( ipw ),
568 IF( mycol.EQ.ivcol )
THEN
570 CALL clacgv( k-j+1, t( j+(j-1)*mbv ), 1 )
572 CALL ctrmm(
'Right',
'Lower', trans,
'Non unit', mpc2, k,
573 $ one, t, mbv, work( ipw ), lw )
574 CALL cgebs2d( ictxt,
'Rowwise',
' ', mpc2, k, work( ipw ),
577 CALL clacgv( k-j+1, t( j+(j-1)*mbv ), 1 )
580 CALL cgebr2d( ictxt,
'Rowwise',
' ', mpc2, k, work( ipw ),
587 mydist = mod( mycol-iccol1+npcol, npcol )
588 ileft =
max( 0, mydist * nbc - icoffc1 )
590 jjend = jjc1 + nqc1 - 1
591 jjnxt =
min( iceil( jjbeg, nbc ) * nbc, jjend )
594 IF( jjbeg.LE.jjnxt )
THEN
595 CALL pbcmatadd( ictxt,
'No transpose', mpc2,
596 $ jjnxt-jjbeg+1, -one,
597 $ work( ipw+ileft*lw ), lw, one,
598 $ c( iic1+(jjbeg-1)*ldc ), ldc )
599 mydist = mydist + npcol
600 ileft = mydist * nbc - icoffc1
602 jjnxt =
min( jjnxt+nbc, jjend )
612 CALL clacgv( k, work( ipv+(j-1)*lv ), 1 )
615 $
CALL cgemm(
'No transpose',
'No transpose', mpc2, nqc2, k,
616 $ -one, work( ipw ), lw, work( ipv ), lv, one,