HomeSort by relevance Sort by last modified time
    Searched defs:UPLO (Results 1 - 25 of 29) sorted by null

1 2

  /external/eigen/blas/
common.h 50 #define UPLO(X) ( ((X)=='U' || (X)=='u') ? UP \
69 inline bool check_uplo(const char* uplo)
71 return UPLO(*uplo)!=0xff;
  /external/eigen/blas/fortran/
chbmv.f 1 SUBROUTINE CHBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
52 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
70 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
160 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
chpmv.f 1 SUBROUTINE CHPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
48 * Before entry with UPLO = 'U' or 'u', the array AP must
53 * Before entry with UPLO = 'L' or 'l', the array AP must
126 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
dsbmv.f 1 SUBROUTINE DSBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
52 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
70 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
154 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
dspmv.f 1 SUBROUTINE DSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
48 * Before entry with UPLO = 'U' or 'u', the array AP must
53 * Before entry with UPLO = 'L' or 'l', the array AP must
119 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
dtbmv.f 1 SUBROUTINE DTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
4 CHARACTER DIAG,TRANS,UPLO
23 * UPLO - CHARACTER*1.
24 * On entry, UPLO specifies whether the matrix is an upper or
27 * UPLO = 'U' or 'u' A is an upper triangular matrix.
29 * UPLO = 'L' or 'l' A is a lower triangular matrix.
62 * On entry with UPLO = 'U' or 'u', K specifies the number of
64 * On entry with UPLO = 'L' or 'l', K specifies the number of
70 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
88 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1
    [all...]
ssbmv.f 1 SUBROUTINE SSBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
52 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
70 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
156 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
sspmv.f 1 SUBROUTINE SSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
48 * Before entry with UPLO = 'U' or 'u', the array AP must
53 * Before entry with UPLO = 'L' or 'l', the array AP must
119 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
stbmv.f 1 SUBROUTINE STBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
4 CHARACTER DIAG,TRANS,UPLO
23 * UPLO - CHARACTER*1.
24 * On entry, UPLO specifies whether the matrix is an upper or
27 * UPLO = 'U' or 'u' A is an upper triangular matrix.
29 * UPLO = 'L' or 'l' A is a lower triangular matrix.
62 * On entry with UPLO = 'U' or 'u', K specifies the number of
64 * On entry with UPLO = 'L' or 'l', K specifies the number of
70 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
88 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1
    [all...]
zhbmv.f 1 SUBROUTINE ZHBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
52 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
70 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
160 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
zhpmv.f 1 SUBROUTINE ZHPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
5 CHARACTER UPLO
24 * UPLO - CHARACTER*1.
25 * On entry, UPLO specifies whether the upper or lower
29 * UPLO = 'U' or 'u' The upper triangular part of A is
32 * UPLO = 'L' or 'l' The lower triangular part of A is
48 * Before entry with UPLO = 'U' or 'u', the array AP must
53 * Before entry with UPLO = 'L' or 'l', the array AP must
126 IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THE
    [all...]
ctbmv.f 1 SUBROUTINE CTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
4 CHARACTER DIAG,TRANS,UPLO
23 * UPLO - CHARACTER*1.
24 * On entry, UPLO specifies whether the matrix is an upper or
27 * UPLO = 'U' or 'u' A is an upper triangular matrix.
29 * UPLO = 'L' or 'l' A is a lower triangular matrix.
62 * On entry with UPLO = 'U' or 'u', K specifies the number of
64 * On entry with UPLO = 'L' or 'l', K specifies the number of
70 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
88 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1
    [all...]
ztbmv.f 1 SUBROUTINE ZTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
4 CHARACTER DIAG,TRANS,UPLO
23 * UPLO - CHARACTER*1.
24 * On entry, UPLO specifies whether the matrix is an upper or
27 * UPLO = 'U' or 'u' A is an upper triangular matrix.
29 * UPLO = 'L' or 'l' A is a lower triangular matrix.
62 * On entry with UPLO = 'U' or 'u', K specifies the number of
64 * On entry with UPLO = 'L' or 'l', K specifies the number of
70 * Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
88 * Before entry with UPLO = 'L' or 'l', the leading ( k + 1
    [all...]
  /external/cblas/testing/
c_cblat2.f     [all...]
c_cblat3.f 795 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS
868 UPLO = ICHU( ICU: ICU )
872 CALL CMAKE(SNAME( 8: 9 ), UPLO, ' ', NA, NA, A, NMAX,
892 UPLOS = UPLO
    [all...]
c_dblat2.f     [all...]
c_dblat3.f 776 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS
849 UPLO = ICHU( ICU: ICU )
853 CALL DMAKE( 'SY', UPLO, ' ', NA, NA, A, NMAX, AA, LDA,
873 UPLOS = UPLO
895 $ SIDE, UPLO, M, N, ALPHA, LDA, LDB,
899 CALL CDSYMM( IORDER, SIDE, UPLO, M, N, ALPHA,
    [all...]
c_sblat2.f     [all...]
c_sblat3.f 780 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS
853 UPLO = ICHU( ICU: ICU )
857 CALL SMAKE( 'SY', UPLO, ' ', NA, NA, A, NMAX, AA, LDA,
877 UPLOS = UPLO
899 $ SIDE, UPLO, M, N, ALPHA, LDA, LDB,
903 CALL CSSYMM( IORDER, SIDE, UPLO, M, N, ALPHA,
    [all...]
c_zblat2.f     [all...]
c_zblat3.f 796 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS
869 UPLO = ICHU( ICU: ICU )
873 CALL ZMAKE(SNAME( 8: 9 ), UPLO, ' ', NA, NA, A, NMAX,
893 UPLOS = UPLO
    [all...]
  /external/eigen/blas/testing/
cblat2.f 782 CHARACTER*1 UPLO, UPLOS
850 UPLO = ICH( IC: IC )
855 CALL CMAKE( SNAME( 2: 3 ), UPLO, ' ', N, N, A, NMAX, AA,
    [all...]
cblat3.f 690 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS
763 UPLO = ICHU( ICU: ICU )
767 CALL CMAKE( SNAME( 2: 3 ), UPLO, ' ', NA, NA, A, NMAX,
787 UPLOS = UPLO
809 $ UPLO, M, N, ALPHA, LDA, LDB, BETA, LDC
813 CALL CHEMM( SIDE, UPLO, M, N, ALPHA, AA, LDA,
816 CALL CSYMM( SIDE, UPLO, M, N, ALPHA, AA, LDA,
831 ISAME( 2 ) = UPLOS.EQ.UPLO
907 WRITE( NOUT, FMT = 9995 )NC, SNAME, SIDE, UPLO, M, N, ALPHA, LDA,
    [all...]
dblat2.f 768 CHARACTER*1 UPLO, UPLOS
836 UPLO = ICH( IC: IC )
841 CALL DMAKE( SNAME( 2: 3 ), UPLO, ' ', N, N, A, NMAX, AA,
880 UPLOS = UPLO
    [all...]
dblat3.f 672 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS
745 UPLO = ICHU( ICU: ICU )
749 CALL DMAKE( 'SY', UPLO, ' ', NA, NA, A, NMAX, AA, LDA,
769 UPLOS = UPLO
791 $ UPLO, M, N, ALPHA, LDA, LDB, BETA, LDC
794 CALL DSYMM( SIDE, UPLO, M, N, ALPHA, AA, LDA,
808 ISAME( 2 ) = UPLOS.EQ.UPLO
884 WRITE( NOUT, FMT = 9995 )NC, SNAME, SIDE, UPLO, M, N, ALPHA, LDA,
    [all...]

Completed in 194 milliseconds

1 2