/external/eigen/lapack/ |
H A D | cholesky.cpp | 17 if(UPLO(*uplo)==INVALID) *info = -1; 29 if(UPLO(*uplo)==UP) ret = int(internal::llt_inplace<Scalar, Upper>::blocked(A)); 44 if(UPLO(*uplo)==INVALID) *info = -1; 60 if(UPLO(*uplo)==UP)
|
H A D | eigenvalues.cpp | 21 else if(UPLO(*uplo)==INVALID) *info = -2; 28 // int nb = ILAENV( 1, 'SSYTRD', UPLO, N, -1, -1, -1 ) 59 if(UPLO(*uplo)==UP) mat = matrix(a,*n,*n,*lda).adjoint();
|
/external/eigen/blas/ |
H A D | dspmv.f | 1 SUBROUTINE DSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:DSPMV 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,' [all...] |
H A D | sspmv.f | 1 SUBROUTINE SSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:SSPMV 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,' [all...] |
H A D | level2_real_impl.h | 38 if(UPLO(*uplo)==INVALID) info = 1; 58 int code = UPLO(*uplo); 108 if(UPLO(*uplo)==INVALID) info = 1; 120 int code = UPLO(*uplo); 169 if(UPLO(*uplo)==INVALID) info = 1; 183 int code = UPLO(*uplo); 192 // int code = UPLO(*uplo); 256 if(UPLO(*uplo)==INVALID) info = 1; 267 int code = UPLO(*uplo); 308 if(UPLO(*upl [all...] |
H A D | ctbmv.f | 1 SUBROUTINE CTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) 4 CHARACTER DIAG,TRANS,UPLO local in subroutine:CTBMV 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 [all...] |
H A D | dtbmv.f | 1 SUBROUTINE DTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) 4 CHARACTER DIAG,TRANS,UPLO local in subroutine:DTBMV 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 [all...] |
H A D | stbmv.f | 1 SUBROUTINE STBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) 4 CHARACTER DIAG,TRANS,UPLO local in subroutine:STBMV 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 [all...] |
H A D | ztbmv.f | 1 SUBROUTINE ZTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX) 4 CHARACTER DIAG,TRANS,UPLO local in subroutine:ZTBMV 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 [all...] |
H A D | level2_cplx_impl.h | 44 if(UPLO(*uplo)==INVALID) info = 1; 66 int code = UPLO(*uplo); 133 if(UPLO(*uplo)==INVALID) info = 1; 144 int code = UPLO(*uplo); 185 if(UPLO(*uplo)==INVALID) info = 1; 198 int code = UPLO(*uplo); 239 if(UPLO(*uplo)==INVALID) info = 1; 251 int code = UPLO(*uplo); 294 if(UPLO(*uplo)==INVALID) info = 1; 308 int code = UPLO(*upl [all...] |
H A D | chbmv.f | 1 SUBROUTINE CHBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:CHBMV 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,' [all...] |
H A D | chpmv.f | 1 SUBROUTINE CHPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:CHPMV 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,' [all...] |
H A D | dsbmv.f | 1 SUBROUTINE DSBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:DSBMV 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,' [all...] |
H A D | ssbmv.f | 1 SUBROUTINE SSBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:SSBMV 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,' [all...] |
H A D | zhbmv.f | 1 SUBROUTINE ZHBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:ZHBMV 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,' [all...] |
H A D | zhpmv.f | 1 SUBROUTINE ZHPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY) 5 CHARACTER UPLO local in subroutine:ZHPMV 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,' [all...] |
H A D | level3_impl.h | 120 else if(UPLO(*uplo)==INVALID) info = 2; 130 int code = OP(*opa) | (SIDE(*side) << 2) | (UPLO(*uplo) << 3) | (DIAG(*diag) << 4); 204 else if(UPLO(*uplo)==INVALID) info = 2; 214 int code = OP(*opa) | (SIDE(*side) << 2) | (UPLO(*uplo) << 3) | (DIAG(*diag) << 4); 249 else if(UPLO(*uplo)==INVALID) info = 2; 273 if(UPLO(*uplo)==UP) 278 else if(UPLO(*uplo)==LO) 289 if(UPLO(*uplo)==UP) internal::product_selfadjoint_matrix<Scalar, DenseIndex, RowMajor,true,false, ColMajor,false,false, ColMajor>::run(*m, *n, a, *lda, b, *ldb, c, *ldc, alpha); 290 else if(UPLO(*uplo)==LO) internal::product_selfadjoint_matrix<Scalar, DenseIndex, ColMajor,true,false, ColMajor,false,false, ColMajor>::run(*m, *n, a, *lda, b, *ldb, c, *ldc, alpha); 293 if(UPLO(*upl [all...] |
H A D | level2_impl.h | 110 if(UPLO(*uplo)==INVALID) info = 1; 121 int code = OP(*opa) | (UPLO(*uplo) << 2) | (DIAG(*diag) << 3); 165 if(UPLO(*uplo)==INVALID) info = 1; 181 int code = OP(*opa) | (UPLO(*uplo) << 2) | (DIAG(*diag) << 3); 277 if(UPLO(*uplo)==INVALID) info = 1; 296 int ku = UPLO(*uplo)==UPPER ? *k : 0; 297 int kl = UPLO(*uplo)==LOWER ? *k : 0; 367 if(UPLO(*uplo)==INVALID) info = 1; 384 int code = OP(*op) | (UPLO(*uplo) << 2) | (DIAG(*diag) << 3); 436 if(UPLO(*upl [all...] |
H A D | common.h | 50 #define UPLO(X) ( ((X)=='U' || (X)=='u') ? UP \ macro 71 return UPLO(*uplo)!=0xff;
|
/external/eigen/blas/testing/ |
H A D | cblat2.f | 782 CHARACTER*1 UPLO, UPLOS local in subroutine:CCHK2 850 UPLO = ICH( IC: IC ) 855 CALL CMAKE( SNAME( 2: 3 ), UPLO, ' ', N, N, A, NMAX, AA, 894 UPLOS = UPLO 917 $ UPLO, N, ALPHA, LDA, INCX, BETA, INCY 920 CALL CHEMV( UPLO, N, ALPHA, AA, LDA, XX, 925 $ UPLO, N, K, ALPHA, LDA, INCX, BETA, 929 CALL CHBMV( UPLO, N, K, ALPHA, AA, LDA, 934 $ UPLO, N, ALPHA, INCX, BETA, INCY 937 CALL CHPMV( UPLO, 1126 CHARACTER*1 DIAG, DIAGS, TRANS, TRANSS, UPLO local in subroutine:CCHK3 1767 CHARACTER*1 UPLO local in subroutine:CCHK5 2052 CHARACTER*1 UPLO local in subroutine:CCHK6 2707 CHARACTER*1 DIAG, UPLO local in subroutine:CMAKE 3046 CHARACTER*1 UPLO local in function:LCERES [all...] |
H A D | dblat2.f | 768 CHARACTER*1 UPLO, UPLOS local in subroutine:DCHK2 836 UPLO = ICH( IC: IC ) 841 CALL DMAKE( SNAME( 2: 3 ), UPLO, ' ', N, N, A, NMAX, AA, 880 UPLOS = UPLO 903 $ UPLO, N, ALPHA, LDA, INCX, BETA, INCY 906 CALL DSYMV( UPLO, N, ALPHA, AA, LDA, XX, 911 $ UPLO, N, K, ALPHA, LDA, INCX, BETA, 915 CALL DSBMV( UPLO, N, K, ALPHA, AA, LDA, 920 $ UPLO, N, ALPHA, INCX, BETA, INCY 923 CALL DSPMV( UPLO, 1106 CHARACTER*1 DIAG, DIAGS, TRANS, TRANSS, UPLO local in subroutine:DCHK3 1726 CHARACTER*1 UPLO local in subroutine:DCHK5 2005 CHARACTER*1 UPLO local in subroutine:DCHK6 2637 CHARACTER*1 DIAG, UPLO local in subroutine:DMAKE 2949 CHARACTER*1 UPLO local in function:LDERES [all...] |
H A D | sblat2.f | 768 CHARACTER*1 UPLO, UPLOS local in subroutine:SCHK2 836 UPLO = ICH( IC: IC ) 841 CALL SMAKE( SNAME( 2: 3 ), UPLO, ' ', N, N, A, NMAX, AA, 880 UPLOS = UPLO 903 $ UPLO, N, ALPHA, LDA, INCX, BETA, INCY 906 CALL SSYMV( UPLO, N, ALPHA, AA, LDA, XX, 911 $ UPLO, N, K, ALPHA, LDA, INCX, BETA, 915 CALL SSBMV( UPLO, N, K, ALPHA, AA, LDA, 920 $ UPLO, N, ALPHA, INCX, BETA, INCY 923 CALL SSPMV( UPLO, 1106 CHARACTER*1 DIAG, DIAGS, TRANS, TRANSS, UPLO local in subroutine:SCHK3 1726 CHARACTER*1 UPLO local in subroutine:SCHK5 2005 CHARACTER*1 UPLO local in subroutine:SCHK6 2637 CHARACTER*1 DIAG, UPLO local in subroutine:SMAKE 2949 CHARACTER*1 UPLO local in function:LSERES [all...] |
H A D | zblat2.f | 785 CHARACTER*1 UPLO, UPLOS local in subroutine:ZCHK2 853 UPLO = ICH( IC: IC ) 858 CALL ZMAKE( SNAME( 2: 3 ), UPLO, ' ', N, N, A, NMAX, AA, 897 UPLOS = UPLO 920 $ UPLO, N, ALPHA, LDA, INCX, BETA, INCY 923 CALL ZHEMV( UPLO, N, ALPHA, AA, LDA, XX, 928 $ UPLO, N, K, ALPHA, LDA, INCX, BETA, 932 CALL ZHBMV( UPLO, N, K, ALPHA, AA, LDA, 937 $ UPLO, N, ALPHA, INCX, BETA, INCY 940 CALL ZHPMV( UPLO, 1130 CHARACTER*1 DIAG, DIAGS, TRANS, TRANSS, UPLO local in subroutine:ZCHK3 1773 CHARACTER*1 UPLO local in subroutine:ZCHK5 2059 CHARACTER*1 UPLO local in subroutine:ZCHK6 2715 CHARACTER*1 DIAG, UPLO local in subroutine:ZMAKE 3054 CHARACTER*1 UPLO local in function:LZERES [all...] |
H A D | cblat3.f | 690 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS local in subroutine:CCHK2 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, 968 CHARACTER*1 DIAG, DIAGS, SIDE, SIDES, TRANAS, TRANSA, UPLO, local in subroutine:CCHK3 1279 CHARACTER*1 TRANS, TRANSS, TRANST, UPLO local in subroutine:CCHK4 1611 CHARACTER*1 TRANS, TRANSS, TRANST, UPLO local in subroutine:CCHK5 2901 CHARACTER*1 DIAG, UPLO local in subroutine:CMAKE 3235 CHARACTER*1 UPLO local in function:LCERES [all...] |
H A D | zblat3.f | 691 CHARACTER*1 SIDE, SIDES, UPLO, UPLOS local in subroutine:ZCHK2 764 UPLO = ICHU( ICU: ICU ) 768 CALL ZMAKE( SNAME( 2: 3 ), UPLO, ' ', NA, NA, A, NMAX, 788 UPLOS = UPLO 810 $ UPLO, M, N, ALPHA, LDA, LDB, BETA, LDC 814 CALL ZHEMM( SIDE, UPLO, M, N, ALPHA, AA, LDA, 817 CALL ZSYMM( SIDE, UPLO, M, N, ALPHA, AA, LDA, 832 ISAME( 2 ) = UPLOS.EQ.UPLO 908 WRITE( NOUT, FMT = 9995 )NC, SNAME, SIDE, UPLO, M, N, ALPHA, LDA, 970 CHARACTER*1 DIAG, DIAGS, SIDE, SIDES, TRANAS, TRANSA, UPLO, local in subroutine:ZCHK3 1281 CHARACTER*1 TRANS, TRANSS, TRANST, UPLO local in subroutine:ZCHK4 1614 CHARACTER*1 TRANS, TRANSS, TRANST, UPLO local in subroutine:ZCHK5 2905 CHARACTER*1 DIAG, UPLO local in subroutine:ZMAKE 3241 CHARACTER*1 UPLO local in function:LZERES [all...] |