SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
All Classes Files Functions Variables Typedefs Macros
pchemm_.c
Go to the documentation of this file.
1/* ---------------------------------------------------------------------
2*
3* -- PBLAS routine (version 2.0) --
4* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5* and University of California, Berkeley.
6* April 1, 1998
7*
8* ---------------------------------------------------------------------
9*/
10/*
11* Include files
12*/
13#include "pblas.h"
14#include "PBpblas.h"
15#include "PBtools.h"
16#include "PBblacs.h"
17#include "PBblas.h"
18
19#ifdef __STDC__
20void pchemm_( F_CHAR_T SIDE, F_CHAR_T UPLO, Int * M, Int * N,
21 float * ALPHA,
22 float * A, Int * IA, Int * JA, Int * DESCA,
23 float * B, Int * IB, Int * JB, Int * DESCB,
24 float * BETA,
25 float * C, Int * IC, Int * JC, Int * DESCC )
26#else
27void pchemm_( SIDE, UPLO, M, N, ALPHA, A, IA, JA, DESCA,
28 B, IB, JB, DESCB, BETA, C, IC, JC, DESCC )
29/*
30* .. Scalar Arguments ..
31*/
32 F_CHAR_T SIDE, UPLO;
33 Int * IA, * IB, * IC, * JA, * JB, * JC, * M, * N;
34 float * ALPHA, * BETA;
35/*
36* .. Array Arguments ..
37*/
38 Int * DESCA, * DESCB, * DESCC;
39 float * A, * B, * C;
40#endif
41{
42/*
43* Purpose
44* =======
45*
46* PCHEMM performs one of the matrix-matrix operations
47*
48* sub( C ) := alpha*sub( A )*sub( B ) + beta*sub( C ),
49*
50* or
51*
52* sub( C ) := alpha*sub( B )*sub( A ) + beta*sub( C ),
53*
54* where
55*
56* sub( C ) denotes C(IC:IC+M-1,JC:JC+N-1),
57*
58* sub( A ) denotes A(IA:IA+M-1,JA:JA+M-1) if SIDE = 'L',
59* A(IA:IA+N-1,JA:JA+N-1) if SIDE = 'R', and,
60*
61* sub( B ) denotes B(IB:IB+M-1,JB:JB+N-1).
62*
63* Alpha and beta are scalars, sub( A ) is a Hermitian submatrix and
64* sub( B ) and sub( C ) are m by n submatrices.
65*
66* Notes
67* =====
68*
69* A description vector is associated with each 2D block-cyclicly dis-
70* tributed matrix. This vector stores the information required to
71* establish the mapping between a matrix entry and its corresponding
72* process and memory location.
73*
74* In the following comments, the character _ should be read as
75* "of the distributed matrix". Let A be a generic term for any 2D
76* block cyclicly distributed matrix. Its description vector is DESC_A:
77*
78* NOTATION STORED IN EXPLANATION
79* ---------------- --------------- ------------------------------------
80* DTYPE_A (global) DESCA[ DTYPE_ ] The descriptor type.
81* CTXT_A (global) DESCA[ CTXT_ ] The BLACS context handle, indicating
82* the NPROW x NPCOL BLACS process grid
83* A is distributed over. The context
84* itself is global, but the handle
85* (the integer value) may vary.
86* M_A (global) DESCA[ M_ ] The number of rows in the distribu-
87* ted matrix A, M_A >= 0.
88* N_A (global) DESCA[ N_ ] The number of columns in the distri-
89* buted matrix A, N_A >= 0.
90* IMB_A (global) DESCA[ IMB_ ] The number of rows of the upper left
91* block of the matrix A, IMB_A > 0.
92* INB_A (global) DESCA[ INB_ ] The number of columns of the upper
93* left block of the matrix A,
94* INB_A > 0.
95* MB_A (global) DESCA[ MB_ ] The blocking factor used to distri-
96* bute the last M_A-IMB_A rows of A,
97* MB_A > 0.
98* NB_A (global) DESCA[ NB_ ] The blocking factor used to distri-
99* bute the last N_A-INB_A columns of
100* A, NB_A > 0.
101* RSRC_A (global) DESCA[ RSRC_ ] The process row over which the first
102* row of the matrix A is distributed,
103* NPROW > RSRC_A >= 0.
104* CSRC_A (global) DESCA[ CSRC_ ] The process column over which the
105* first column of A is distributed.
106* NPCOL > CSRC_A >= 0.
107* LLD_A (local) DESCA[ LLD_ ] The leading dimension of the local
108* array storing the local blocks of
109* the distributed matrix A,
110* IF( Lc( 1, N_A ) > 0 )
111* LLD_A >= MAX( 1, Lr( 1, M_A ) )
112* ELSE
113* LLD_A >= 1.
114*
115* Let K be the number of rows of a matrix A starting at the global in-
116* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
117* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
118* receive if these K rows were distributed over NPROW processes. If K
119* is the number of columns of a matrix A starting at the global index
120* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
121* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
122* these K columns were distributed over NPCOL processes.
123*
124* The values of Lr() and Lc() may be determined via a call to the func-
125* tion PB_Cnumroc:
126* Lr( IA, K ) = PB_Cnumroc( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
127* Lc( JA, K ) = PB_Cnumroc( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
128*
129* Arguments
130* =========
131*
132* SIDE (global input) CHARACTER*1
133* On entry, SIDE specifies whether the Hermitian submatrix
134* sub( A ) appears on the left or right in the operation as
135* follows:
136*
137* SIDE = 'L' or 'l'
138* sub( C ) := alpha*sub( A )*sub( B ) + beta*sub( C ),
139*
140* SIDE = 'R' or 'r'
141* sub( C ) := alpha*sub( B )*sub( A ) + beta*sub( C ).
142*
143* UPLO (global input) CHARACTER*1
144* On entry, UPLO specifies whether the local pieces of
145* the array A containing the upper or lower triangular part
146* of the Hermitian submatrix sub( A ) are to be referenced as
147* follows:
148*
149* UPLO = 'U' or 'u' Only the local pieces corresponding to
150* the upper triangular part of the
151* Hermitian submatrix sub( A ) are to be
152* referenced,
153*
154* UPLO = 'L' or 'l' Only the local pieces corresponding to
155* the lower triangular part of the
156* Hermitian submatrix sub( A ) are to be
157* referenced.
158*
159* M (global input) INTEGER
160* On entry, M specifies the number of rows of the submatrix
161* sub( C ). M must be at least zero.
162*
163* N (global input) INTEGER
164* On entry, N specifies the number of columns of the submatrix
165* sub( C ). N must be at least zero.
166*
167* ALPHA (global input) COMPLEX
168* On entry, ALPHA specifies the scalar alpha. When ALPHA is
169* supplied as zero then the local entries of the arrays A and
170* B corresponding to the entries of the submatrices sub( A )
171* and sub( B ) respectively need not be set on input.
172*
173* A (local input) COMPLEX array
174* On entry, A is an array of dimension (LLD_A, Ka), where Ka is
175* at least Lc( 1, JA+M-1 ) when SIDE = 'L' or 'l' and is at
176* at least Lc( 1, JA+N-1 ) otherwise. Before entry, this array
177* contains the local entries of the matrix A.
178* Before entry with SIDE = 'L' or 'l', this array contains
179* the local entries corresponding to the entries of the m by m
180* Hermitian submatrix sub( A ), such that when UPLO = 'U' or
181* 'u', this array contains the local entries of the upper tri-
182* angular part of the Hermitian submatrix sub( A ), and the
183* local entries of the strictly lower triangular of sub( A )
184* are not referenced, and when UPLO = 'L' or 'l', this array
185* contains the local entries of the lower triangular part of
186* the Hermitian submatrix sub( A ), and the local entries of
187* the strictly upper triangular of sub( A ) are not referenced.
188* Before entry with SIDE = 'R' or 'r', this array contains
189* the local entries corresponding to the entries of the n by n
190* Hermitian submatrix sub( A ), such that when UPLO = 'U' or
191* 'u', this array contains the local entries of the upper tri-
192* angular part of the Hermitian submatrix sub( A ), and the
193* local entries of the strictly lower triangular of sub( A )
194* are not referenced, and when UPLO = 'L' or 'l', this array
195* contains the local entries of the lower triangular part of
196* the Hermitian submatrix sub( A ), and the local entries of
197* the strictly upper triangular of sub( A ) are not referenced.
198* Note that the imaginary parts of the local entries corres-
199* ponding to the diagonal elements of sub( A ) need not be
200* set and assumed to be zero.
201*
202* IA (global input) INTEGER
203* On entry, IA specifies A's global row index, which points to
204* the beginning of the submatrix sub( A ).
205*
206* JA (global input) INTEGER
207* On entry, JA specifies A's global column index, which points
208* to the beginning of the submatrix sub( A ).
209*
210* DESCA (global and local input) INTEGER array
211* On entry, DESCA is an integer array of dimension DLEN_. This
212* is the array descriptor for the matrix A.
213*
214* B (local input) COMPLEX array
215* On entry, B is an array of dimension (LLD_B, Kb), where Kb is
216* at least Lc( 1, JB+N-1 ). Before entry, this array contains
217* the local entries of the matrix B.
218*
219* IB (global input) INTEGER
220* On entry, IB specifies B's global row index, which points to
221* the beginning of the submatrix sub( B ).
222*
223* JB (global input) INTEGER
224* On entry, JB specifies B's global column index, which points
225* to the beginning of the submatrix sub( B ).
226*
227* DESCB (global and local input) INTEGER array
228* On entry, DESCB is an integer array of dimension DLEN_. This
229* is the array descriptor for the matrix B.
230*
231* BETA (global input) COMPLEX
232* On entry, BETA specifies the scalar beta. When BETA is
233* supplied as zero then the local entries of the array C
234* corresponding to the entries of the submatrix sub( C ) need
235* not be set on input.
236*
237* C (local input/local output) COMPLEX array
238* On entry, C is an array of dimension (LLD_C, Kc), where Kc is
239* at least Lc( 1, JC+N-1 ). Before entry, this array contains
240* the local entries of the matrix C.
241* On exit, the entries of this array corresponding to the local
242* entries of the submatrix sub( C ) are overwritten by the
243* local entries of the m by n updated submatrix.
244*
245* IC (global input) INTEGER
246* On entry, IC specifies C's global row index, which points to
247* the beginning of the submatrix sub( C ).
248*
249* JC (global input) INTEGER
250* On entry, JC specifies C's global column index, which points
251* to the beginning of the submatrix sub( C ).
252*
253* DESCC (global and local input) INTEGER array
254* On entry, DESCC is an integer array of dimension DLEN_. This
255* is the array descriptor for the matrix C.
256*
257* -- Written on April 1, 1998 by
258* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
259*
260* ---------------------------------------------------------------------
261*/
262/*
263* .. Local Scalars ..
264*/
265 char DirAB, SideOp, UploA, cbtop, cbtopsave, cctop, cctopsave,
266 rbtop, rbtopsave, rctop, rctopsave;
267 Int Ai, Aj, Bi, Bj, ChooseABC, Ci, Cj, ForceTop, ctxt, info,
268 lside, mycol, myrow, nb, npcol, nprow, upper;
269 double ABCest, BCest, tmp1, tmp2, tmp3, tmp4;
270 PBTYP_T * type;
271/*
272* .. Local Arrays ..
273*/
274 Int Ad[DLEN_], Bd[DLEN_], Cd[DLEN_];
275/* ..
276* .. Executable Statements ..
277*
278*/
279 lside = ( ( SideOp = Mupcase( F2C_CHAR( SIDE )[0] ) ) == CLEFT );
280 upper = ( ( UploA = Mupcase( F2C_CHAR( UPLO )[0] ) ) == CUPPER );
281 PB_CargFtoC( *IA, *JA, DESCA, &Ai, &Aj, Ad );
282 PB_CargFtoC( *IB, *JB, DESCB, &Bi, &Bj, Bd );
283 PB_CargFtoC( *IC, *JC, DESCC, &Ci, &Cj, Cd );
284#ifndef NO_ARGCHK
285/*
286* Test the input parameters
287*/
288 Cblacs_gridinfo( ( ctxt = Ad[CTXT_] ), &nprow, &npcol, &myrow, &mycol );
289 if( !( info = ( ( nprow == -1 ) ? -( 901 + CTXT_ ) : 0 ) ) )
290 {
291 if( ( !lside ) && ( SideOp != CRIGHT ) )
292 {
293 PB_Cwarn( ctxt, __LINE__, "PCHEMM", "Illegal SIDE = %c\n", SideOp );
294 info = -1;
295 }
296 else if( ( !upper ) && ( UploA != CLOWER ) )
297 {
298 PB_Cwarn( ctxt, __LINE__, "PCHEMM", "Illegal UPLO = %c\n", UploA );
299 info = -2;
300 }
301 if( lside )
302 {
303 PB_Cchkmat( ctxt, "PCHEMM", "A", *M, 3, *M, 3, Ai, Aj, Ad, 9,
304 &info );
305 PB_Cchkmat( ctxt, "PCHEMM", "B", *M, 3, *N, 4, Bi, Bj, Bd, 13,
306 &info );
307 }
308 else
309 {
310 PB_Cchkmat( ctxt, "PCHEMM", "A", *N, 4, *N, 4, Ai, Aj, Ad, 9,
311 &info );
312 PB_Cchkmat( ctxt, "PCHEMM", "B", *M, 3, *N, 4, Bi, Bj, Bd, 13,
313 &info );
314 }
315 PB_Cchkmat( ctxt, "PCHEMM", "C", *M, 3, *N, 4, Ci, Cj, Cd, 18,
316 &info );
317 }
318 if( info ) { PB_Cabort( ctxt, "PCHEMM", info ); return; }
319#endif
320/*
321* Quick return if possible
322*/
323 if( ( *M == 0 ) || ( *N == 0 ) ||
324 ( ( ( ALPHA[REAL_PART] == ZERO ) && ( ALPHA[IMAG_PART] == ZERO ) ) &&
325 ( ( BETA [REAL_PART] == ONE ) && ( BETA [IMAG_PART] == ZERO ) ) ) )
326 return;
327/*
328* Get type structure
329*/
330 type = PB_Cctypeset();
331/*
332* If alpha is zero, sub( C ) := beta * sub( C ).
333*/
334 if( ( ALPHA[REAL_PART] == ZERO ) && ( ALPHA[IMAG_PART] == ZERO ) )
335 {
336 if( ( BETA[REAL_PART] == ZERO ) && ( BETA[IMAG_PART] == ZERO ) )
337 {
338 PB_Cplapad( type, ALL, NOCONJG, *M, *N, type->zero, type->zero,
339 ((char *) C), Ci, Cj, Cd );
340 }
341 else if( !( ( BETA[REAL_PART] == ONE ) && ( BETA[IMAG_PART] == ZERO ) ) )
342 {
343 PB_Cplascal( type, ALL, NOCONJG, *M, *N, ((char *) BETA), ((char *) C),
344 Ci, Cj, Cd );
345 }
346 return;
347 }
348/*
349* Start the operations
350*/
351#ifdef NO_ARGCHK
352 Cblacs_gridinfo( ( ctxt = Ad[CTXT_] ), &nprow, &npcol, &myrow, &mycol );
353#endif
354/*
355* Algorithm selection is based on approximation of the communication volume
356* for distributed and aligned operands.
357*
358* ABCest: operands sub( A ), sub( B ) and sub( C ) are communicated (N >> M)
359* BCest : Both operands sub( B ) and sub( C ) are communicated (M >> N)
360*/
361 if( lside )
362 {
363 tmp1 = DNROC( *M, Ad[MB_], nprow ); tmp2 = DNROC( *N, Bd[NB_], npcol );
364 ABCest = (double)(*M) *
365 ( ( ( ( Ad[CSRC_] == -1 ) || ( npcol == 1 ) ) ? ZERO : tmp1 / TWO ) +
366 ( ( ( Bd[RSRC_] == -1 ) || ( nprow == 1 ) ) ? ZERO :
367 tmp2 + tmp2 * CBRATIO ) );
368 tmp1 = DNROC( *M, Ad[MB_], nprow ); tmp2 = DNROC( *M, Ad[NB_], npcol );
369 tmp3 = DNROC( *M, Bd[MB_], nprow ); tmp4 = DNROC( *M, Cd[MB_], nprow );
370 BCest = (double)(*N) *
371 ( CBRATIO * ( npcol == 1 ? ZERO : tmp1 ) +
372 ( nprow == 1 ? ZERO : tmp2 ) + MAX( tmp2, tmp3 ) +
373 ( ( ( Bd[CSRC_] == -1 ) || ( npcol == 1 ) ) ? ZERO : tmp1 ) +
374 CBRATIO * ( nprow == 1 ? ZERO : tmp2 ) + MAX( tmp2, tmp4 ) );
375 }
376 else
377 {
378 tmp1 = DNROC( *N, Ad[NB_], npcol ); tmp2 = DNROC( *M, Bd[MB_], nprow );
379 ABCest = (double)(*N) *
380 ( ( ( ( Ad[RSRC_] == -1 ) || ( nprow == 1 ) ) ? ZERO : tmp1 / TWO ) +
381 ( ( ( Bd[CSRC_] == -1 ) || ( npcol == 1 ) ) ? ZERO :
382 tmp2 + tmp2 * CBRATIO ) );
383 tmp1 = DNROC( *N, Ad[MB_], nprow ); tmp2 = DNROC( *N, Ad[NB_], npcol );
384 tmp3 = DNROC( *N, Bd[NB_], npcol ); tmp4 = DNROC( *N, Cd[NB_], npcol );
385 BCest = (double)(*M) *
386 ( ( npcol == 1 ? ZERO : tmp1 ) + MAX( tmp1, tmp3 ) +
387 CBRATIO * ( nprow == 1 ? ZERO : tmp2 ) +
388 ( ( ( Bd[RSRC_] == -1 ) || ( nprow == 1 ) ) ? ZERO : tmp2 ) +
389 CBRATIO * ( npcol == 1 ? ZERO : tmp1 ) + MAX( tmp1, tmp4 ) );
390 }
391/*
392* Shift a little the cross-over point between both algorithms.
393*/
394 ChooseABC = ( ( 1.5 * ABCest ) <= BCest );
395/*
396* BLACS topologies are enforced iff M and N are strictly greater than the
397* logical block size returned by pilaenv_. Otherwise, it is assumed that the
398* routine calling this routine has already selected an adequate topology.
399*/
400 nb = pilaenv_( &ctxt, C2F_CHAR( &type->type ) );
401 ForceTop = ( ( *M > nb ) && ( *N > nb ) );
402
403 rbtop = *PB_Ctop( &ctxt, BCAST, ROW, TOP_GET );
404 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_GET );
405 cbtop = *PB_Ctop( &ctxt, BCAST, COLUMN, TOP_GET );
406 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_GET );
407
408 if( ChooseABC )
409 {
410 if( ForceTop )
411 {
412 rbtopsave = rbtop; rctopsave = rctop;
413 cbtopsave = cbtop; cctopsave = cctop;
414
415 if( lside )
416 {
417/*
418* No clear winner for the ring topologies, so that if a ring topology is
419* already selected, keep it.
420*/
421 if( ( rbtop != CTOP_DRING ) && ( rbtop != CTOP_IRING ) &&
422 ( rbtop != CTOP_SRING ) )
423 rbtop = *PB_Ctop( &ctxt, BCAST, ROW, TOP_IRING );
424 if( ( ( cbtop != CTOP_DRING ) && ( cbtop != CTOP_IRING ) &&
425 ( cbtop != CTOP_SRING ) ) || ( cbtop != cctop ) )
426 {
427 cbtop = *PB_Ctop( &ctxt, BCAST, COLUMN, TOP_IRING );
428 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_IRING );
429/*
430* Remove the next 2 lines when the BLACS combine operations support ring
431* topologies
432*/
433 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_DEFAULT );
434 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_DEFAULT );
435 }
436 }
437 else
438 {
439/*
440* No clear winner for the ring topologies, so that if a ring topology is
441* already selected, keep it.
442*/
443 if( ( cbtop != CTOP_DRING ) && ( cbtop != CTOP_IRING ) &&
444 ( cbtop != CTOP_SRING ) )
445 cbtop = *PB_Ctop( &ctxt, BCAST, COLUMN, TOP_IRING );
446 if( ( ( rbtop != CTOP_DRING ) && ( rbtop != CTOP_IRING ) &&
447 ( rbtop != CTOP_SRING ) ) || ( rbtop != rctop ) )
448 {
449 rbtop = *PB_Ctop( &ctxt, BCAST, ROW, TOP_IRING );
450 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_IRING );
451/*
452* Remove the next 2 lines when the BLACS combine operations support ring
453* topologies
454*/
455 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_DEFAULT );
456 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_DEFAULT );
457 }
458 }
459 }
460 if( lside )
461 DirAB = ( rbtop == CTOP_DRING ? CBACKWARD : CFORWARD );
462 else
463 DirAB = ( cbtop == CTOP_DRING ? CBACKWARD : CFORWARD );
464
465 PB_CpsymmAB( type, &DirAB, CONJG, &SideOp, &UploA, *M, *N,
466 ((char *)ALPHA), ((char *)A), Ai, Aj, Ad, ((char *)B), Bi,
467 Bj, Bd, ((char *)BETA), ((char *)C), Ci, Cj, Cd );
468 }
469 else
470 {
471 if( ForceTop )
472 {
473 rbtopsave = rbtop; rctopsave = rctop;
474 cbtopsave = cbtop; cctopsave = cctop;
475
476 if( lside )
477 {
478/*
479* No clear winner for the ring topologies, so that if a ring topology is
480* already selected, keep it.
481*/
482 if( ( ( rbtop != CTOP_DRING ) && ( rbtop != CTOP_IRING ) &&
483 ( rbtop != CTOP_SRING ) ) || ( rbtop != rctop ) )
484 {
485 rbtop = *PB_Ctop( &ctxt, BCAST, ROW, TOP_IRING );
486 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_IRING );
487/*
488* Remove the next 2 lines when the BLACS combine operations support ring
489* topologies
490*/
491 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_DEFAULT );
492 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_DEFAULT );
493 }
494 cbtop = *PB_Ctop( &ctxt, BCAST, COLUMN, TOP_DEFAULT );
495 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_DEFAULT );
496 }
497 else
498 {
499/*
500* No clear winner for the ring topologies, so that if a ring topology is
501* already selected, keep it.
502*/
503 if( ( ( cbtop != CTOP_DRING ) && ( cbtop != CTOP_IRING ) &&
504 ( cbtop != CTOP_SRING ) ) || ( cbtop != cctop ) )
505 {
506 cbtop = *PB_Ctop( &ctxt, BCAST, COLUMN, TOP_IRING );
507 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_IRING );
508/*
509* Remove the next 2 lines when the BLACS combine operations support ring
510* topologies
511*/
512 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_DEFAULT );
513 cctop = *PB_Ctop( &ctxt, COMBINE, COLUMN, TOP_DEFAULT );
514 }
515 rbtop = *PB_Ctop( &ctxt, BCAST, ROW, TOP_DEFAULT );
516 rctop = *PB_Ctop( &ctxt, COMBINE, ROW, TOP_DEFAULT );
517 }
518 }
519 if( lside )
520 DirAB = ( ( rbtop == CTOP_DRING || rctop == CTOP_DRING ) ?
522 else
523 DirAB = ( ( cbtop == CTOP_DRING || cctop == CTOP_DRING ) ?
525
526 PB_CpsymmBC( type, &DirAB, CONJG, &SideOp, &UploA, *M, *N,
527 ((char *)ALPHA), ((char *)A), Ai, Aj, Ad, ((char *)B), Bi,
528 Bj, Bd, ((char *)BETA), ((char *)C), Ci, Cj, Cd );
529 }
530/*
531* Restore the BLACS topologies when necessary.
532*/
533 if( ForceTop )
534 {
535 rbtopsave = *PB_Ctop( &ctxt, BCAST, ROW, &rbtopsave );
536 rctopsave = *PB_Ctop( &ctxt, COMBINE, ROW, &rctopsave );
537 cbtopsave = *PB_Ctop( &ctxt, BCAST, COLUMN, &cbtopsave );
538 cctopsave = *PB_Ctop( &ctxt, COMBINE, COLUMN, &cctopsave );
539 }
540/*
541* End of PCHEMM
542*/
543}
#define Int
Definition Bconfig.h:22
#define REAL_PART
Definition pblas.h:139
#define F2C_CHAR(a)
Definition pblas.h:124
#define CBRATIO
Definition pblas.h:37
#define C2F_CHAR(a)
Definition pblas.h:125
#define IMAG_PART
Definition pblas.h:140
char * F_CHAR_T
Definition pblas.h:122
#define TOP_GET
Definition PBblacs.h:50
#define COLUMN
Definition PBblacs.h:45
#define COMBINE
Definition PBblacs.h:49
#define TOP_IRING
Definition PBblacs.h:52
#define CTOP_SRING
Definition PBblacs.h:29
#define TOP_DEFAULT
Definition PBblacs.h:51
#define ROW
Definition PBblacs.h:46
void Cblacs_gridinfo()
#define BCAST
Definition PBblacs.h:48
#define CTOP_IRING
Definition PBblacs.h:27
#define CTOP_DRING
Definition PBblacs.h:28
#define CONJG
Definition PBblas.h:47
#define ALL
Definition PBblas.h:50
#define CLEFT
Definition PBblas.h:29
#define CBACKWARD
Definition PBblas.h:39
#define NOCONJG
Definition PBblas.h:45
#define CUPPER
Definition PBblas.h:26
#define CRIGHT
Definition PBblas.h:30
#define CFORWARD
Definition PBblas.h:38
#define CLOWER
Definition PBblas.h:25
#define pilaenv_
Definition PBpblas.h:44
#define pchemm_
Definition PBpblas.h:159
#define CTXT_
Definition PBtools.h:38
#define MAX(a_, b_)
Definition PBtools.h:77
#define MB_
Definition PBtools.h:43
void PB_Cabort()
#define ONE
Definition PBtools.h:64
void PB_Cchkmat()
void PB_Cwarn()
char * PB_Ctop()
void PB_Cplapad()
void PB_Cplascal()
#define RSRC_
Definition PBtools.h:45
#define TWO
Definition PBtools.h:65
void PB_CpsymmBC()
void PB_CpsymmAB()
void PB_CargFtoC()
#define CSRC_
Definition PBtools.h:46
PBTYP_T * PB_Cctypeset()
#define ZERO
Definition PBtools.h:66
#define Mupcase(C)
Definition PBtools.h:83
#define DLEN_
Definition PBtools.h:48
#define NB_
Definition PBtools.h:44
#define DNROC(n_, nb_, p_)
Definition PBtools.h:111
char type
Definition pblas.h:331
char * zero
Definition pblas.h:335