1 SUBROUTINE psggqrf( N, M, P, A, IA, JA, DESCA, TAUA, B, IB, JB,
2 $ DESCB, TAUB, WORK, LWORK, INFO )
10 INTEGER IA, IB, INFO, JA, JB, LWORK, M, N, P
13 INTEGER DESCA( * ), DESCB( * )
14 REAL A( * ), B( * ), TAUA( * ), TAUB( * ), WORK( * )
257 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
258 $ lld_, mb_, m_, nb_, n_, rsrc_
259 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
260 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
261 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
265 INTEGER IACOL, IAROW, IBCOL, IBROW, ICOFFA, ICOFFB,
266 $ ictxt, iroffa, iroffb, lwmin, mqa0, mycol,
267 $ myrow, npa0, npb0, npcol, nprow, pqb0
274 INTEGER IDUM1( 1 ), IDUM2( 1 )
277 INTEGER INDXG2P, NUMROC
278 EXTERNAL indxg2p, numroc
281 INTRINSIC int,
max,
min, mod, real
287 ictxt = desca( ctxt_ )
288 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
293 IF( nprow.EQ.-1 )
THEN
296 CALL chk1mat( n, 1, m, 2, ia, ja, desca, 7, info )
297 CALL chk1mat( n, 1, p, 3, ib, jb, descb, 12, info )
299 iroffa = mod( ia-1, desca( mb_ ) )
300 icoffa = mod( ja-1, desca( nb_ ) )
301 iroffb = mod( ib-1, descb( mb_ ) )
302 icoffb = mod( jb-1, descb( nb_ ) )
303 iarow = indxg2p( ia, desca( mb_ ), myrow, desca( rsrc_ ),
305 iacol = indxg2p( ja, desca( nb_ ), mycol, desca( csrc_ ),
307 ibrow = indxg2p( ib, descb( mb_ ), myrow, descb( rsrc_ ),
309 ibcol = indxg2p( jb, descb( nb_ ), mycol, descb( csrc_ ),
311 npa0 = numroc( n+iroffa, desca( mb_ ), myrow, iarow, nprow )
312 mqa0 = numroc( m+icoffa, desca( nb_ ), mycol, iacol, npcol )
313 npb0 = numroc( n+iroffb, descb( mb_ ), myrow, ibrow, nprow )
314 pqb0 = numroc( p+icoffb, descb( nb_ ), mycol, ibcol, npcol )
315 lwmin =
max( desca( nb_ ) * ( npa0 + mqa0 + desca( nb_ ) ),
316 $
max(
max( ( desca( nb_ )*( desca( nb_ ) - 1 ) ) / 2,
317 $ ( pqb0 + npb0 ) * desca( nb_ ) ) +
318 $ desca( nb_ ) * desca( nb_ ),
319 $ descb( mb_ ) * ( npb0 + pqb0 + descb( mb_ ) ) ) )
321 work( 1 ) = real( lwmin )
322 lquery = ( lwork.EQ.-1 )
323 IF( iarow.NE.ibrow .OR. iroffa.NE.iroffb )
THEN
325 ELSE IF( desca( mb_ ).NE.descb( mb_ ) )
THEN
327 ELSE IF( ictxt.NE.descb( ctxt_ ) )
THEN
329 ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery )
THEN
339 CALL pchk2mat( n, 1, m, 2, ia, ja, desca, 7, n, 1, p, 3, ib,
340 $ jb, descb, 12, 1, idum1, idum2, info )
344 CALL pxerbla( ictxt,
'PSGGQRF', -info )
346 ELSE IF( lquery )
THEN
352 CALL psgeqrf( n, m, a, ia, ja, desca, taua, work, lwork, info )
353 lwmin = int( work( 1 ) )
357 CALL psormqr(
'Left',
'Transpose', n, p,
min( n, m ), a, ia, ja,
358 $ desca, taua, b, ib, jb, descb, work, lwork, info )
359 lwmin =
min( lwmin, int( work( 1 ) ) )
363 CALL psgerqf( n, p, b, ib, jb, descb, taub, work, lwork, info )
364 work( 1 ) = real(
max( lwmin, int( work( 1 ) ) ) )