Searched refs:INCX (Results 1 - 25 of 39) sorted by relevance

12

/external/eigen/blas/
H A Dcomplexdots.f1 COMPLEX FUNCTION CDOTC(N,CX,INCX,CY,INCY)
2 INTEGER INCX,INCY,N local in function:CDOTC
7 CALL CDOTCW(N,CX,INCX,CY,INCY,RES)
12 COMPLEX FUNCTION CDOTU(N,CX,INCX,CY,INCY)
13 INTEGER INCX,INCY,N local in function:CDOTU
18 CALL CDOTUW(N,CX,INCX,CY,INCY,RES)
23 DOUBLE COMPLEX FUNCTION ZDOTC(N,CX,INCX,CY,INCY)
24 INTEGER INCX,INCY,N local in function:ZDOTC
29 CALL ZDOTCW(N,CX,INCX,CY,INCY,RES)
34 DOUBLE COMPLEX FUNCTION ZDOTU(N,CX,INCX,C
35 INTEGER INCX local in function:ZDOTU
[all...]
H A Ddspr.f1 SUBROUTINE DSPR(UPLO,N,ALPHA,X,INCX,AP)
4 INTEGER INCX,N local in subroutine:DSPR
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
110 ELSE IF (INCX.EQ.0) THEN
124 IF (INCX.LE.0) THEN
125 KX = 1 - (N-1)*INCX
126 ELSE IF (INCX
[all...]
H A Dsspr.f1 SUBROUTINE SSPR(UPLO,N,ALPHA,X,INCX,AP)
4 INTEGER INCX,N local in subroutine:SSPR
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
110 ELSE IF (INCX.EQ.0) THEN
124 IF (INCX.LE.0) THEN
125 KX = 1 - (N-1)*INCX
126 ELSE IF (INCX
[all...]
H A Dctbmv.f1 SUBROUTINE CTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
3 INTEGER INCX,K,LDA,N local in subroutine:CTBMV
118 * ( 1 + ( n - 1 )*abs( INCX ) ).
123 * INCX - INTEGER.
124 * On entry, INCX specifies the increment for the elements of
125 * X. INCX must not be zero.
177 ELSE IF (INCX.EQ.0) THEN
193 * will be ( N - 1 )*INCX too small for descending loops.
195 IF (INCX.LE.0) THEN
196 KX = 1 - (N-1)*INCX
[all...]
H A Dztbmv.f1 SUBROUTINE ZTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
3 INTEGER INCX,K,LDA,N local in subroutine:ZTBMV
118 * ( 1 + ( n - 1 )*abs( INCX ) ).
123 * INCX - INTEGER.
124 * On entry, INCX specifies the increment for the elements of
125 * X. INCX must not be zero.
177 ELSE IF (INCX.EQ.0) THEN
193 * will be ( N - 1 )*INCX too small for descending loops.
195 IF (INCX.LE.0) THEN
196 KX = 1 - (N-1)*INCX
[all...]
H A Ddtbmv.f1 SUBROUTINE DTBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
3 INTEGER INCX,K,LDA,N local in subroutine:DTBMV
118 * ( 1 + ( n - 1 )*abs( INCX ) ).
123 * INCX - INTEGER.
124 * On entry, INCX specifies the increment for the elements of
125 * X. INCX must not be zero.
177 ELSE IF (INCX.EQ.0) THEN
192 * will be ( N - 1 )*INCX too small for descending loops.
194 IF (INCX.LE.0) THEN
195 KX = 1 - (N-1)*INCX
[all...]
H A Dstbmv.f1 SUBROUTINE STBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
3 INTEGER INCX,K,LDA,N local in subroutine:STBMV
118 * ( 1 + ( n - 1 )*abs( INCX ) ).
123 * INCX - INTEGER.
124 * On entry, INCX specifies the increment for the elements of
125 * X. INCX must not be zero.
177 ELSE IF (INCX.EQ.0) THEN
192 * will be ( N - 1 )*INCX too small for descending loops.
194 IF (INCX.LE.0) THEN
195 KX = 1 - (N-1)*INCX
[all...]
H A Dctpmv.f1 SUBROUTINE CTPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:CTPMV
78 * ( 1 + ( n - 1 )*abs( INCX ) ).
83 * INCX - INTEGER.
84 * On entry, INCX specifies the increment for the elements of
85 * X. INCX must not be zero.
133 ELSE IF (INCX.EQ.0) THEN
149 * will be ( N - 1 )*INCX too small for descending loops.
151 IF (INCX.LE.0) THEN
152 KX = 1 - (N-1)*INCX
[all...]
H A Dctpsv.f1 SUBROUTINE CTPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:CTPSV
81 * ( 1 + ( n - 1 )*abs( INCX ) ).
86 * INCX - INTEGER.
87 * On entry, INCX specifies the increment for the elements of
88 * X. INCX must not be zero.
136 ELSE IF (INCX.EQ.0) THEN
152 * will be ( N - 1 )*INCX too small for descending loops.
154 IF (INCX.LE.0) THEN
155 KX = 1 - (N-1)*INCX
[all...]
H A Dztpmv.f1 SUBROUTINE ZTPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:ZTPMV
78 * ( 1 + ( n - 1 )*abs( INCX ) ).
83 * INCX - INTEGER.
84 * On entry, INCX specifies the increment for the elements of
85 * X. INCX must not be zero.
133 ELSE IF (INCX.EQ.0) THEN
149 * will be ( N - 1 )*INCX too small for descending loops.
151 IF (INCX.LE.0) THEN
152 KX = 1 - (N-1)*INCX
[all...]
H A Dztpsv.f1 SUBROUTINE ZTPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:ZTPSV
81 * ( 1 + ( n - 1 )*abs( INCX ) ).
86 * INCX - INTEGER.
87 * On entry, INCX specifies the increment for the elements of
88 * X. INCX must not be zero.
136 ELSE IF (INCX.EQ.0) THEN
152 * will be ( N - 1 )*INCX too small for descending loops.
154 IF (INCX.LE.0) THEN
155 KX = 1 - (N-1)*INCX
[all...]
H A Ddrotm.f1 SUBROUTINE DROTM(N,DX,INCX,DY,INCY,DPARAM)
3 INTEGER INCX,INCY,N local in subroutine:DROTM
17 * DX(LX+I*INCX), I = 0 TO N-1, WHERE LX = 1 IF INCX .GE. 0, ELSE
18 * LX = (-INCX)*N, AND SIMILARLY FOR SY USING LY AND INCY.
37 * INCX (input) INTEGER
65 IF (.NOT. (INCX.EQ.INCY.AND.INCX.GT.0)) GO TO 70
67 NSTEPS = N*INCX
72 DO 20 I = 1,NSTEPS,INCX
[all...]
H A Dsrotm.f1 SUBROUTINE SROTM(N,SX,INCX,SY,INCY,SPARAM)
3 INTEGER INCX,INCY,N local in subroutine:SROTM
17 * SX(LX+I*INCX), I = 0 TO N-1, WHERE LX = 1 IF INCX .GE. 0, ELSE
18 * LX = (-INCX)*N, AND SIMILARLY FOR SY USING USING LY AND INCY.
38 * INCX (input) INTEGER
66 IF (.NOT. (INCX.EQ.INCY.AND.INCX.GT.0)) GO TO 70
68 NSTEPS = N*INCX
73 DO 20 I = 1,NSTEPS,INCX
[all...]
H A Ddtpmv.f1 SUBROUTINE DTPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:DTPMV
78 * ( 1 + ( n - 1 )*abs( INCX ) ).
83 * INCX - INTEGER.
84 * On entry, INCX specifies the increment for the elements of
85 * X. INCX must not be zero.
130 ELSE IF (INCX.EQ.0) THEN
145 * will be ( N - 1 )*INCX too small for descending loops.
147 IF (INCX.LE.0) THEN
148 KX = 1 - (N-1)*INCX
[all...]
H A Ddtpsv.f1 SUBROUTINE DTPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:DTPSV
81 * ( 1 + ( n - 1 )*abs( INCX ) ).
86 * INCX - INTEGER.
87 * On entry, INCX specifies the increment for the elements of
88 * X. INCX must not be zero.
133 ELSE IF (INCX.EQ.0) THEN
148 * will be ( N - 1 )*INCX too small for descending loops.
150 IF (INCX.LE.0) THEN
151 KX = 1 - (N-1)*INCX
[all...]
H A Dstpmv.f1 SUBROUTINE STPMV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:STPMV
78 * ( 1 + ( n - 1 )*abs( INCX ) ).
83 * INCX - INTEGER.
84 * On entry, INCX specifies the increment for the elements of
85 * X. INCX must not be zero.
130 ELSE IF (INCX.EQ.0) THEN
145 * will be ( N - 1 )*INCX too small for descending loops.
147 IF (INCX.LE.0) THEN
148 KX = 1 - (N-1)*INCX
[all...]
H A Dstpsv.f1 SUBROUTINE STPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
3 INTEGER INCX,N local in subroutine:STPSV
81 * ( 1 + ( n - 1 )*abs( INCX ) ).
86 * INCX - INTEGER.
87 * On entry, INCX specifies the increment for the elements of
88 * X. INCX must not be zero.
133 ELSE IF (INCX.EQ.0) THEN
148 * will be ( N - 1 )*INCX too small for descending loops.
150 IF (INCX.LE.0) THEN
151 KX = 1 - (N-1)*INCX
[all...]
H A Dchpr.f1 SUBROUTINE CHPR(UPLO,N,ALPHA,X,INCX,AP)
4 INTEGER INCX,N local in subroutine:CHPR
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
116 ELSE IF (INCX.EQ.0) THEN
130 IF (INCX.LE.0) THEN
131 KX = 1 - (N-1)*INCX
132 ELSE IF (INCX
[all...]
H A Dchpr2.f1 SUBROUTINE CHPR2(UPLO,N,ALPHA,X,INCX,Y,INCY,AP)
4 INTEGER INCX,INCY,N local in subroutine:CHPR2
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
127 ELSE IF (INCX.EQ.0) THEN
144 IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN
145 IF (INCX.GT.0) THEN
148 KX = 1 - (N-1)*INCX
[all...]
H A Ddspr2.f1 SUBROUTINE DSPR2(UPLO,N,ALPHA,X,INCX,Y,INCY,AP)
4 INTEGER INCX,INCY,N local in subroutine:DSPR2
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
121 ELSE IF (INCX.EQ.0) THEN
138 IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN
139 IF (INCX.GT.0) THEN
142 KX = 1 - (N-1)*INCX
[all...]
H A Dsspr2.f1 SUBROUTINE SSPR2(UPLO,N,ALPHA,X,INCX,Y,INCY,AP)
4 INTEGER INCX,INCY,N local in subroutine:SSPR2
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
121 ELSE IF (INCX.EQ.0) THEN
138 IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN
139 IF (INCX.GT.0) THEN
142 KX = 1 - (N-1)*INCX
[all...]
H A Dzhpr.f1 SUBROUTINE ZHPR(UPLO,N,ALPHA,X,INCX,AP)
4 INTEGER INCX,N local in subroutine:ZHPR
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
116 ELSE IF (INCX.EQ.0) THEN
130 IF (INCX.LE.0) THEN
131 KX = 1 - (N-1)*INCX
132 ELSE IF (INCX
[all...]
H A Dzhpr2.f1 SUBROUTINE ZHPR2(UPLO,N,ALPHA,X,INCX,Y,INCY,AP)
4 INTEGER INCX,INCY,N local in subroutine:ZHPR2
47 * ( 1 + ( n - 1 )*abs( INCX ) ).
52 * INCX - INTEGER.
53 * On entry, INCX specifies the increment for the elements of
54 * X. INCX must not be zero.
127 ELSE IF (INCX.EQ.0) THEN
144 IF ((INCX.NE.1) .OR. (INCY.NE.1)) THEN
145 IF (INCX.GT.0) THEN
148 KX = 1 - (N-1)*INCX
[all...]
H A Ddspmv.f1 SUBROUTINE DSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
4 INTEGER INCX,INCY,N local in subroutine:DSPMV
61 * ( 1 + ( n - 1 )*abs( INCX ) ).
66 * INCX - INTEGER.
67 * On entry, INCX specifies the increment for the elements of
68 * X. INCX must not be zero.
123 ELSE IF (INCX.EQ.0) THEN
139 IF (INCX.GT.0) THEN
142 KX = 1 - (N-1)*INCX
187 IF ((INCX
[all...]
H A Dsspmv.f1 SUBROUTINE SSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
4 INTEGER INCX,INCY,N local in subroutine:SSPMV
61 * ( 1 + ( n - 1 )*abs( INCX ) ).
66 * INCX - INTEGER.
67 * On entry, INCX specifies the increment for the elements of
68 * X. INCX must not be zero.
123 ELSE IF (INCX.EQ.0) THEN
139 IF (INCX.GT.0) THEN
142 KX = 1 - (N-1)*INCX
187 IF ((INCX
[all...]

Completed in 327 milliseconds

12