SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ psblas2tstchk()

subroutine psblas2tstchk ( integer  ictxt,
integer  nout,
integer  nrout,
character*1  uplo,
character*1  trans,
character*1  diag,
integer  m,
integer  n,
real  alpha,
real, dimension( * )  a,
real, dimension( * )  pa,
integer  ia,
integer  ja,
integer, dimension( * )  desca,
real, dimension( * )  x,
real, dimension( * )  px,
integer  ix,
integer  jx,
integer, dimension( * )  descx,
integer  incx,
real  beta,
real, dimension( * )  y,
real, dimension( * )  py,
integer  iy,
integer  jy,
integer, dimension( * )  descy,
integer  incy,
real  thresh,
real  rogue,
real, dimension( * )  work,
integer  info 
)

Definition at line 2518 of file psblas2tst.f.

2523*
2524* -- PBLAS test routine (version 2.0) --
2525* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
2526* and University of California, Berkeley.
2527* April 1, 1998
2528*
2529* .. Scalar Arguments ..
2530 CHARACTER*1 DIAG, TRANS, UPLO
2531 INTEGER IA, ICTXT, INCX, INCY, INFO, IX, IY, JA, JX,
2532 $ JY, M, N, NOUT, NROUT
2533 REAL ALPHA, BETA, ROGUE, THRESH
2534* ..
2535* .. Array Arguments ..
2536 INTEGER DESCA( * ), DESCX( * ), DESCY( * )
2537 REAL A( * ), PA( * ), PX( * ), PY( * ), WORK( * ),
2538 $ X( * ), Y( * )
2539* ..
2540*
2541* Purpose
2542* =======
2543*
2544* PSBLAS2TSTCHK performs the computational tests of the Level 2 PBLAS.
2545*
2546* Notes
2547* =====
2548*
2549* A description vector is associated with each 2D block-cyclicly dis-
2550* tributed matrix. This vector stores the information required to
2551* establish the mapping between a matrix entry and its corresponding
2552* process and memory location.
2553*
2554* In the following comments, the character _ should be read as
2555* "of the distributed matrix". Let A be a generic term for any 2D
2556* block cyclicly distributed matrix. Its description vector is DESCA:
2557*
2558* NOTATION STORED IN EXPLANATION
2559* ---------------- --------------- ------------------------------------
2560* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
2561* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
2562* the NPROW x NPCOL BLACS process grid
2563* A is distributed over. The context
2564* itself is global, but the handle
2565* (the integer value) may vary.
2566* M_A (global) DESCA( M_ ) The number of rows in the distribu-
2567* ted matrix A, M_A >= 0.
2568* N_A (global) DESCA( N_ ) The number of columns in the distri-
2569* buted matrix A, N_A >= 0.
2570* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
2571* block of the matrix A, IMB_A > 0.
2572* INB_A (global) DESCA( INB_ ) The number of columns of the upper
2573* left block of the matrix A,
2574* INB_A > 0.
2575* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
2576* bute the last M_A-IMB_A rows of A,
2577* MB_A > 0.
2578* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
2579* bute the last N_A-INB_A columns of
2580* A, NB_A > 0.
2581* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
2582* row of the matrix A is distributed,
2583* NPROW > RSRC_A >= 0.
2584* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
2585* first column of A is distributed.
2586* NPCOL > CSRC_A >= 0.
2587* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
2588* array storing the local blocks of
2589* the distributed matrix A,
2590* IF( Lc( 1, N_A ) > 0 )
2591* LLD_A >= MAX( 1, Lr( 1, M_A ) )
2592* ELSE
2593* LLD_A >= 1.
2594*
2595* Let K be the number of rows of a matrix A starting at the global in-
2596* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
2597* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
2598* receive if these K rows were distributed over NPROW processes. If K
2599* is the number of columns of a matrix A starting at the global index
2600* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
2601* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
2602* these K columns were distributed over NPCOL processes.
2603*
2604* The values of Lr() and Lc() may be determined via a call to the func-
2605* tion PB_NUMROC:
2606* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
2607* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
2608*
2609* Arguments
2610* =========
2611*
2612* ICTXT (local input) INTEGER
2613* On entry, ICTXT specifies the BLACS context handle, indica-
2614* ting the global context of the operation. The context itself
2615* is global, but the value of ICTXT is local.
2616*
2617* NOUT (global input) INTEGER
2618* On entry, NOUT specifies the unit number for the output file.
2619* When NOUT is 6, output to screen, when NOUT is 0, output to
2620* stderr. NOUT is only defined for process 0.
2621*
2622* NROUT (global input) INTEGER
2623* On entry, NROUT specifies which routine will be tested as
2624* follows:
2625* If NROUT = 1, PSGEMV will be tested;
2626* else if NROUT = 2, PSSYMV will be tested;
2627* else if NROUT = 3, PSTRMV will be tested;
2628* else if NROUT = 4, PSTRSV will be tested;
2629* else if NROUT = 5, PSGER will be tested;
2630* else if NROUT = 6, PSSYR will be tested;
2631* else if NROUT = 7, PSSYR2 will be tested;
2632*
2633* UPLO (global input) CHARACTER*1
2634* On entry, UPLO specifies if the upper or lower part of the
2635* matrix operand is to be referenced.
2636*
2637* TRANS (global input) CHARACTER*1
2638* On entry, TRANS specifies if the matrix operand A is to be
2639* transposed.
2640*
2641* DIAG (global input) CHARACTER*1
2642* On entry, DIAG specifies if the triangular matrix operand is
2643* unit or non-unit.
2644*
2645* M (global input) INTEGER
2646* On entry, M specifies the number of rows of A.
2647*
2648* N (global input) INTEGER
2649* On entry, N specifies the number of columns of A.
2650*
2651* ALPHA (global input) REAL
2652* On entry, ALPHA specifies the scalar alpha.
2653*
2654* A (local input/local output) REAL array
2655* On entry, A is an array of dimension (DESCA( M_ ),*). This
2656* array contains a local copy of the initial entire matrix PA.
2657*
2658* PA (local input) REAL array
2659* On entry, PA is an array of dimension (DESCA( LLD_ ),*). This
2660* array contains the local entries of the matrix PA.
2661*
2662* IA (global input) INTEGER
2663* On entry, IA specifies A's global row index, which points to
2664* the beginning of the submatrix sub( A ).
2665*
2666* JA (global input) INTEGER
2667* On entry, JA specifies A's global column index, which points
2668* to the beginning of the submatrix sub( A ).
2669*
2670* DESCA (global and local input) INTEGER array
2671* On entry, DESCA is an integer array of dimension DLEN_. This
2672* is the array descriptor for the matrix A.
2673*
2674* X (local input/local output) REAL array
2675* On entry, X is an array of dimension (DESCX( M_ ),*). This
2676* array contains a local copy of the initial entire matrix PX.
2677*
2678* PX (local input) REAL array
2679* On entry, PX is an array of dimension (DESCX( LLD_ ),*). This
2680* array contains the local entries of the matrix PX.
2681*
2682* IX (global input) INTEGER
2683* On entry, IX specifies X's global row index, which points to
2684* the beginning of the submatrix sub( X ).
2685*
2686* JX (global input) INTEGER
2687* On entry, JX specifies X's global column index, which points
2688* to the beginning of the submatrix sub( X ).
2689*
2690* DESCX (global and local input) INTEGER array
2691* On entry, DESCX is an integer array of dimension DLEN_. This
2692* is the array descriptor for the matrix X.
2693*
2694* INCX (global input) INTEGER
2695* On entry, INCX specifies the global increment for the
2696* elements of X. Only two values of INCX are supported in
2697* this version, namely 1 and M_X. INCX must not be zero.
2698*
2699* BETA (global input) REAL
2700* On entry, BETA specifies the scalar beta.
2701*
2702* Y (local input/local output) REAL array
2703* On entry, Y is an array of dimension (DESCY( M_ ),*). This
2704* array contains a local copy of the initial entire matrix PY.
2705*
2706* PY (local input) REAL array
2707* On entry, PY is an array of dimension (DESCY( LLD_ ),*). This
2708* array contains the local entries of the matrix PY.
2709*
2710* IY (global input) INTEGER
2711* On entry, IY specifies Y's global row index, which points to
2712* the beginning of the submatrix sub( Y ).
2713*
2714* JY (global input) INTEGER
2715* On entry, JY specifies Y's global column index, which points
2716* to the beginning of the submatrix sub( Y ).
2717*
2718* DESCY (global and local input) INTEGER array
2719* On entry, DESCY is an integer array of dimension DLEN_. This
2720* is the array descriptor for the matrix Y.
2721*
2722* INCY (global input) INTEGER
2723* On entry, INCY specifies the global increment for the
2724* elements of Y. Only two values of INCY are supported in
2725* this version, namely 1 and M_Y. INCY must not be zero.
2726*
2727* THRESH (global input) REAL
2728* On entry, THRESH is the threshold value for the test ratio.
2729*
2730* ROGUE (global input) REAL
2731* On entry, ROGUE specifies the constant used to pad the
2732* non-referenced part of triangular or symmetric matrices.
2733*
2734* WORK (workspace) REAL array
2735* On entry, WORK is an array of dimension LWORK where LWORK is
2736* at least MAX( M, N ). This array is used to store the compu-
2737* ted gauges (see PSMVCH).
2738*
2739* INFO (global output) INTEGER
2740* On exit, if INFO = 0, no error has been found, otherwise
2741* if( MOD( INFO, 2 ) = 1 ) then an error on A has been found,
2742* if( MOD( INFO/2, 2 ) = 1 ) then an error on X has been found,
2743* if( MOD( INFO/4, 2 ) = 1 ) then an error on Y has been found.
2744*
2745* -- Written on April 1, 1998 by
2746* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
2747*
2748* =====================================================================
2749*
2750* .. Parameters ..
2751 REAL ONE, ZERO
2752 parameter( one = 1.0e+0, zero = 0.0e+0 )
2753 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
2754 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
2755 $ RSRC_
2756 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
2757 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
2758 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
2759 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
2760* ..
2761* .. Local Scalars ..
2762 INTEGER I, MYCOL, MYROW, NPCOL, NPROW
2763 REAL ERR
2764* ..
2765* .. Local Arrays ..
2766 INTEGER IERR( 3 )
2767* ..
2768* .. External Subroutines ..
2769 EXTERNAL blacs_gridinfo, pb_slaset, pschkmin, pschkvin,
2770 $ psmvch, pstrmv, psvmch, psvmch2, strsv
2771* ..
2772* .. External Functions ..
2773 LOGICAL LSAME
2774 EXTERNAL lsame
2775* ..
2776* .. Executable Statements ..
2777*
2778 info = 0
2779*
2780* Quick return if possible
2781*
2782 IF( ( m.LE.0 ).OR.( n.LE.0 ) )
2783 $ RETURN
2784*
2785* Start the operations
2786*
2787 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
2788*
2789 DO 10 i = 1, 3
2790 ierr( i ) = 0
2791 10 CONTINUE
2792*
2793 IF( nrout.EQ.1 ) THEN
2794*
2795* Test PSGEMV
2796*
2797* Check the resulting vector Y
2798*
2799 CALL psmvch( ictxt, trans, m, n, alpha, a, ia, ja, desca, x,
2800 $ ix, jx, descx, incx, beta, y, py, iy, jy, descy,
2801 $ incy, work, err, ierr( 3 ) )
2802*
2803 IF( ierr( 3 ).NE.0 ) THEN
2804 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2805 $ WRITE( nout, fmt = 9997 )
2806 ELSE IF( err.GT.thresh ) THEN
2807 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2808 $ WRITE( nout, fmt = 9996 ) err
2809 END IF
2810*
2811* Check the input-only arguments
2812*
2813 CALL pschkmin( err, m, n, a, pa, ia, ja, desca, ierr( 1 ) )
2814 IF( lsame( trans, 'N' ) ) THEN
2815 CALL pschkvin( err, n, x, px, ix, jx, descx, incx,
2816 $ ierr( 2 ) )
2817 ELSE
2818 CALL pschkvin( err, m, x, px, ix, jx, descx, incx,
2819 $ ierr( 2 ) )
2820 END IF
2821*
2822 ELSE IF( nrout.EQ.2 ) THEN
2823*
2824* Test PSSYMV
2825*
2826* Check the resulting vector Y
2827*
2828 CALL psmvch( ictxt, 'No transpose', n, n, alpha, a, ia, ja,
2829 $ desca, x, ix, jx, descx, incx, beta, y, py, iy,
2830 $ jy, descy, incy, work, err, ierr( 3 ) )
2831*
2832 IF( ierr( 3 ).NE.0 ) THEN
2833 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2834 $ WRITE( nout, fmt = 9997 )
2835 ELSE IF( err.GT.thresh ) THEN
2836 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2837 $ WRITE( nout, fmt = 9996 ) err
2838 END IF
2839*
2840* Check the input-only arguments
2841*
2842 IF( lsame( uplo, 'L' ) ) THEN
2843 CALL pb_slaset( 'Upper', n-1, n-1, 0, rogue, rogue,
2844 $ a( ia+ja*desca( m_ ) ), desca( m_ ) )
2845 ELSE
2846 CALL pb_slaset( 'Lower', n-1, n-1, 0, rogue, rogue,
2847 $ a( ia+1+(ja-1)*desca( m_ ) ), desca( m_ ) )
2848 END IF
2849 CALL pschkmin( err, n, n, a, pa, ia, ja, desca, ierr( 1 ) )
2850 CALL pschkvin( err, n, x, px, ix, jx, descx, incx, ierr( 2 ) )
2851*
2852 ELSE IF( nrout.EQ.3 ) THEN
2853*
2854* Test PSTRMV
2855*
2856* Check the resulting vector X
2857*
2858 CALL psmvch( ictxt, trans, n, n, one, a, ia, ja, desca, y, ix,
2859 $ jx, descx, incx, zero, x, px, ix, jx, descx, incx,
2860 $ work, err, ierr( 2 ) )
2861*
2862 IF( ierr( 2 ).NE.0 ) THEN
2863 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2864 $ WRITE( nout, fmt = 9997 )
2865 ELSE IF( err.GT.thresh ) THEN
2866 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2867 $ WRITE( nout, fmt = 9996 ) err
2868 END IF
2869*
2870* Check the input-only arguments
2871*
2872 IF( lsame( uplo, 'L' ) ) THEN
2873 IF( lsame( diag, 'N' ) ) THEN
2874 CALL pb_slaset( 'Upper', n-1, n-1, 0, rogue, rogue,
2875 $ a( ia+ja*desca( m_ ) ), desca( m_ ) )
2876 ELSE
2877 CALL pb_slaset( 'Upper', n, n, 0, rogue, one,
2878 $ a( ia+(ja-1)*desca( m_ ) ), desca( m_ ) )
2879 END IF
2880 ELSE
2881 IF( lsame( diag, 'N' ) ) THEN
2882 CALL pb_slaset( 'Lower', n-1, n-1, 0, rogue, rogue,
2883 $ a( ia+1+(ja-1)*desca( m_ ) ),
2884 $ desca( m_ ) )
2885 ELSE
2886 CALL pb_slaset( 'Lower', n, n, 0, rogue, one,
2887 $ a( ia+(ja-1)*desca( m_ ) ), desca( m_ ) )
2888 END IF
2889 END IF
2890 CALL pschkmin( err, n, n, a, pa, ia, ja, desca, ierr( 1 ) )
2891*
2892 ELSE IF( nrout.EQ.4 ) THEN
2893*
2894* Test PSTRSV
2895*
2896* Check the resulting vector X
2897*
2898 CALL strsv( uplo, trans, diag, n, a( ia+(ja-1)*desca( m_ ) ),
2899 $ desca( m_ ), x( ix+(jx-1)*descx( m_ ) ), incx )
2900 CALL pstrmv( uplo, trans, diag, n, pa, ia, ja, desca, px, ix,
2901 $ jx, descx, incx )
2902 CALL psmvch( ictxt, trans, n, n, one, a, ia, ja, desca, x, ix,
2903 $ jx, descx, incx, zero, y, px, ix, jx, descx, incx,
2904 $ work, err, ierr( 2 ) )
2905*
2906 IF( ierr( 2 ).NE.0 ) THEN
2907 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2908 $ WRITE( nout, fmt = 9997 )
2909 ELSE IF( err.GT.thresh ) THEN
2910 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2911 $ WRITE( nout, fmt = 9996 ) err
2912 END IF
2913*
2914* Check the input-only arguments
2915*
2916 IF( lsame( uplo, 'L' ) ) THEN
2917 IF( lsame( diag, 'N' ) ) THEN
2918 CALL pb_slaset( 'Upper', n-1, n-1, 0, rogue, rogue,
2919 $ a( ia+ja*desca( m_ ) ), desca( m_ ) )
2920 ELSE
2921 CALL pb_slaset( 'Upper', n, n, 0, rogue, one,
2922 $ a( ia+(ja-1)*desca( m_ ) ), desca( m_ ) )
2923 END IF
2924 ELSE
2925 IF( lsame( diag, 'N' ) ) THEN
2926 CALL pb_slaset( 'Lower', n-1, n-1, 0, rogue, rogue,
2927 $ a( ia+1+(ja-1)*desca( m_ ) ),
2928 $ desca( m_ ) )
2929 ELSE
2930 CALL pb_slaset( 'Lower', n, n, 0, rogue, one,
2931 $ a( ia+(ja-1)*desca( m_ ) ), desca( m_ ) )
2932 END IF
2933 END IF
2934 CALL pschkmin( err, n, n, a, pa, ia, ja, desca, ierr( 1 ) )
2935*
2936 ELSE IF( nrout.EQ.5 ) THEN
2937*
2938* Test PSGER
2939*
2940* Check the resulting matrix A
2941*
2942 CALL psvmch( ictxt, 'Ge', m, n, alpha, x, ix, jx, descx,
2943 $ incx, y, iy, jy, descy, incy, a, pa, ia, ja,
2944 $ desca, work, err, ierr( 1 ) )
2945 IF( ierr( 1 ).NE.0 ) THEN
2946 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2947 $ WRITE( nout, fmt = 9997 )
2948 ELSE IF( err.GT.thresh ) THEN
2949 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2950 $ WRITE( nout, fmt = 9996 ) err
2951 END IF
2952*
2953* Check the input-only arguments
2954*
2955 CALL pschkvin( err, m, x, px, ix, jx, descx, incx, ierr( 2 ) )
2956 CALL pschkvin( err, n, y, py, iy, jy, descy, incy, ierr( 3 ) )
2957*
2958 ELSE IF( nrout.EQ.6 ) THEN
2959*
2960* Test PSSYR
2961*
2962* Check the resulting matrix A
2963*
2964 CALL psvmch( ictxt, uplo, n, n, alpha, x, ix, jx, descx,
2965 $ incx, x, ix, jx, descx, incx, a, pa, ia, ja,
2966 $ desca, work, err, ierr( 1 ) )
2967 IF( ierr( 1 ).NE.0 ) THEN
2968 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2969 $ WRITE( nout, fmt = 9997 )
2970 ELSE IF( err.GT.thresh ) THEN
2971 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2972 $ WRITE( nout, fmt = 9996 ) err
2973 END IF
2974*
2975* Check the input-only arguments
2976*
2977 CALL pschkvin( err, n, x, px, ix, jx, descx, incx, ierr( 2 ) )
2978*
2979 ELSE IF( nrout.EQ.7 ) THEN
2980*
2981* Test PSSYR2
2982*
2983* Check the resulting matrix A
2984*
2985 CALL psvmch2( ictxt, uplo, n, n, alpha, x, ix, jx, descx, incx,
2986 $ y, iy, jy, descy, incy, a, pa, ia, ja, desca,
2987 $ work, err, ierr( 1 ) )
2988 IF( ierr( 1 ).NE.0 ) THEN
2989 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2990 $ WRITE( nout, fmt = 9997 )
2991 ELSE IF( err.GT.thresh ) THEN
2992 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
2993 $ WRITE( nout, fmt = 9996 ) err
2994 END IF
2995*
2996* Check the input-only arguments
2997*
2998 CALL pschkvin( err, n, x, px, ix, jx, descx, incx, ierr( 2 ) )
2999 CALL pschkvin( err, n, y, py, iy, jy, descy, incy, ierr( 3 ) )
3000*
3001 END IF
3002*
3003 IF( ierr( 1 ).NE.0 ) THEN
3004 info = info + 1
3005 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
3006 $ WRITE( nout, fmt = 9999 ) 'A'
3007 END IF
3008*
3009 IF( ierr( 2 ).NE.0 ) THEN
3010 info = info + 2
3011 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
3012 $ WRITE( nout, fmt = 9998 ) 'X'
3013 END IF
3014*
3015 IF( ierr( 3 ).NE.0 ) THEN
3016 info = info + 4
3017 IF( myrow.EQ.0 .AND. mycol.EQ.0 )
3018 $ WRITE( nout, fmt = 9998 ) 'Y'
3019 END IF
3020*
3021 9999 FORMAT( 2x, ' ***** ERROR: Matrix operand ', a,
3022 $ ' is incorrect.' )
3023 9998 FORMAT( 2x, ' ***** ERROR: Vector operand ', a,
3024 $ ' is incorrect.' )
3025 9997 FORMAT( 2x, ' ***** FATAL ERROR - Computed result is less ',
3026 $ 'than half accurate *****' )
3027 9996 FORMAT( 2x, ' ***** Test completed with maximum test ratio: ',
3028 $ f11.5, ' SUSPECT *****' )
3029*
3030 RETURN
3031*
3032* End of PSBLAS2TSTCHK
3033*
subroutine pschkmin(errmax, m, n, a, pa, ia, ja, desca, info)
Definition psblastst.f:3326
subroutine pschkvin(errmax, n, x, px, ix, jx, descx, incx, info)
Definition psblastst.f:2576
subroutine pb_slaset(uplo, m, n, ioffd, alpha, beta, a, lda)
Definition psblastst.f:9361
subroutine psvmch(ictxt, uplo, m, n, alpha, x, ix, jx, descx, incx, y, iy, jy, descy, incy, a, pa, ia, ja, desca, g, err, info)
Definition psblastst.f:4570
subroutine psmvch(ictxt, trans, m, n, alpha, a, ia, ja, desca, x, ix, jx, descx, incx, beta, y, py, iy, jy, descy, incy, g, err, info)
Definition psblastst.f:4157
subroutine psvmch2(ictxt, uplo, m, n, alpha, x, ix, jx, descx, incx, y, iy, jy, descy, incy, a, pa, ia, ja, desca, g, err, info)
Definition psblastst.f:4919
logical function lsame(ca, cb)
Definition tools.f:1724
Here is the call graph for this function:
Here is the caller graph for this function: