root / src / blas / cgerc.f @ 10
Historique | Voir | Annoter | Télécharger (4,17 ko)
1 | 1 | pfleura2 | SUBROUTINE CGERC(M,N,ALPHA,X,INCX,Y,INCY,A,LDA) |
---|---|---|---|
2 | 1 | pfleura2 | * .. Scalar Arguments .. |
3 | 1 | pfleura2 | COMPLEX ALPHA |
4 | 1 | pfleura2 | INTEGER INCX,INCY,LDA,M,N |
5 | 1 | pfleura2 | * .. |
6 | 1 | pfleura2 | * .. Array Arguments .. |
7 | 1 | pfleura2 | COMPLEX A(LDA,*),X(*),Y(*) |
8 | 1 | pfleura2 | * .. |
9 | 1 | pfleura2 | * |
10 | 1 | pfleura2 | * Purpose |
11 | 1 | pfleura2 | * ======= |
12 | 1 | pfleura2 | * |
13 | 1 | pfleura2 | * CGERC performs the rank 1 operation |
14 | 1 | pfleura2 | * |
15 | 1 | pfleura2 | * A := alpha*x*conjg( y' ) + A, |
16 | 1 | pfleura2 | * |
17 | 1 | pfleura2 | * where alpha is a scalar, x is an m element vector, y is an n element |
18 | 1 | pfleura2 | * vector and A is an m by n matrix. |
19 | 1 | pfleura2 | * |
20 | 1 | pfleura2 | * Arguments |
21 | 1 | pfleura2 | * ========== |
22 | 1 | pfleura2 | * |
23 | 1 | pfleura2 | * M - INTEGER. |
24 | 1 | pfleura2 | * On entry, M specifies the number of rows of the matrix A. |
25 | 1 | pfleura2 | * M must be at least zero. |
26 | 1 | pfleura2 | * Unchanged on exit. |
27 | 1 | pfleura2 | * |
28 | 1 | pfleura2 | * N - INTEGER. |
29 | 1 | pfleura2 | * On entry, N specifies the number of columns of the matrix A. |
30 | 1 | pfleura2 | * N must be at least zero. |
31 | 1 | pfleura2 | * Unchanged on exit. |
32 | 1 | pfleura2 | * |
33 | 1 | pfleura2 | * ALPHA - COMPLEX . |
34 | 1 | pfleura2 | * On entry, ALPHA specifies the scalar alpha. |
35 | 1 | pfleura2 | * Unchanged on exit. |
36 | 1 | pfleura2 | * |
37 | 1 | pfleura2 | * X - COMPLEX array of dimension at least |
38 | 1 | pfleura2 | * ( 1 + ( m - 1 )*abs( INCX ) ). |
39 | 1 | pfleura2 | * Before entry, the incremented array X must contain the m |
40 | 1 | pfleura2 | * element vector x. |
41 | 1 | pfleura2 | * Unchanged on exit. |
42 | 1 | pfleura2 | * |
43 | 1 | pfleura2 | * INCX - INTEGER. |
44 | 1 | pfleura2 | * On entry, INCX specifies the increment for the elements of |
45 | 1 | pfleura2 | * X. INCX must not be zero. |
46 | 1 | pfleura2 | * Unchanged on exit. |
47 | 1 | pfleura2 | * |
48 | 1 | pfleura2 | * Y - COMPLEX array of dimension at least |
49 | 1 | pfleura2 | * ( 1 + ( n - 1 )*abs( INCY ) ). |
50 | 1 | pfleura2 | * Before entry, the incremented array Y must contain the n |
51 | 1 | pfleura2 | * element vector y. |
52 | 1 | pfleura2 | * Unchanged on exit. |
53 | 1 | pfleura2 | * |
54 | 1 | pfleura2 | * INCY - INTEGER. |
55 | 1 | pfleura2 | * On entry, INCY specifies the increment for the elements of |
56 | 1 | pfleura2 | * Y. INCY must not be zero. |
57 | 1 | pfleura2 | * Unchanged on exit. |
58 | 1 | pfleura2 | * |
59 | 1 | pfleura2 | * A - COMPLEX array of DIMENSION ( LDA, n ). |
60 | 1 | pfleura2 | * Before entry, the leading m by n part of the array A must |
61 | 1 | pfleura2 | * contain the matrix of coefficients. On exit, A is |
62 | 1 | pfleura2 | * overwritten by the updated matrix. |
63 | 1 | pfleura2 | * |
64 | 1 | pfleura2 | * LDA - INTEGER. |
65 | 1 | pfleura2 | * On entry, LDA specifies the first dimension of A as declared |
66 | 1 | pfleura2 | * in the calling (sub) program. LDA must be at least |
67 | 1 | pfleura2 | * max( 1, m ). |
68 | 1 | pfleura2 | * Unchanged on exit. |
69 | 1 | pfleura2 | * |
70 | 1 | pfleura2 | * |
71 | 1 | pfleura2 | * Level 2 Blas routine. |
72 | 1 | pfleura2 | * |
73 | 1 | pfleura2 | * -- Written on 22-October-1986. |
74 | 1 | pfleura2 | * Jack Dongarra, Argonne National Lab. |
75 | 1 | pfleura2 | * Jeremy Du Croz, Nag Central Office. |
76 | 1 | pfleura2 | * Sven Hammarling, Nag Central Office. |
77 | 1 | pfleura2 | * Richard Hanson, Sandia National Labs. |
78 | 1 | pfleura2 | * |
79 | 1 | pfleura2 | * |
80 | 1 | pfleura2 | * .. Parameters .. |
81 | 1 | pfleura2 | COMPLEX ZERO |
82 | 1 | pfleura2 | PARAMETER (ZERO= (0.0E+0,0.0E+0)) |
83 | 1 | pfleura2 | * .. |
84 | 1 | pfleura2 | * .. Local Scalars .. |
85 | 1 | pfleura2 | COMPLEX TEMP |
86 | 1 | pfleura2 | INTEGER I,INFO,IX,J,JY,KX |
87 | 1 | pfleura2 | * .. |
88 | 1 | pfleura2 | * .. External Subroutines .. |
89 | 1 | pfleura2 | EXTERNAL XERBLA |
90 | 1 | pfleura2 | * .. |
91 | 1 | pfleura2 | * .. Intrinsic Functions .. |
92 | 1 | pfleura2 | INTRINSIC CONJG,MAX |
93 | 1 | pfleura2 | * .. |
94 | 1 | pfleura2 | * |
95 | 1 | pfleura2 | * Test the input parameters. |
96 | 1 | pfleura2 | * |
97 | 1 | pfleura2 | INFO = 0 |
98 | 1 | pfleura2 | IF (M.LT.0) THEN |
99 | 1 | pfleura2 | INFO = 1 |
100 | 1 | pfleura2 | ELSE IF (N.LT.0) THEN |
101 | 1 | pfleura2 | INFO = 2 |
102 | 1 | pfleura2 | ELSE IF (INCX.EQ.0) THEN |
103 | 1 | pfleura2 | INFO = 5 |
104 | 1 | pfleura2 | ELSE IF (INCY.EQ.0) THEN |
105 | 1 | pfleura2 | INFO = 7 |
106 | 1 | pfleura2 | ELSE IF (LDA.LT.MAX(1,M)) THEN |
107 | 1 | pfleura2 | INFO = 9 |
108 | 1 | pfleura2 | END IF |
109 | 1 | pfleura2 | IF (INFO.NE.0) THEN |
110 | 1 | pfleura2 | CALL XERBLA('CGERC ',INFO) |
111 | 1 | pfleura2 | RETURN |
112 | 1 | pfleura2 | END IF |
113 | 1 | pfleura2 | * |
114 | 1 | pfleura2 | * Quick return if possible. |
115 | 1 | pfleura2 | * |
116 | 1 | pfleura2 | IF ((M.EQ.0) .OR. (N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN |
117 | 1 | pfleura2 | * |
118 | 1 | pfleura2 | * Start the operations. In this version the elements of A are |
119 | 1 | pfleura2 | * accessed sequentially with one pass through A. |
120 | 1 | pfleura2 | * |
121 | 1 | pfleura2 | IF (INCY.GT.0) THEN |
122 | 1 | pfleura2 | JY = 1 |
123 | 1 | pfleura2 | ELSE |
124 | 1 | pfleura2 | JY = 1 - (N-1)*INCY |
125 | 1 | pfleura2 | END IF |
126 | 1 | pfleura2 | IF (INCX.EQ.1) THEN |
127 | 1 | pfleura2 | DO 20 J = 1,N |
128 | 1 | pfleura2 | IF (Y(JY).NE.ZERO) THEN |
129 | 1 | pfleura2 | TEMP = ALPHA*CONJG(Y(JY)) |
130 | 1 | pfleura2 | DO 10 I = 1,M |
131 | 1 | pfleura2 | A(I,J) = A(I,J) + X(I)*TEMP |
132 | 1 | pfleura2 | 10 CONTINUE |
133 | 1 | pfleura2 | END IF |
134 | 1 | pfleura2 | JY = JY + INCY |
135 | 1 | pfleura2 | 20 CONTINUE |
136 | 1 | pfleura2 | ELSE |
137 | 1 | pfleura2 | IF (INCX.GT.0) THEN |
138 | 1 | pfleura2 | KX = 1 |
139 | 1 | pfleura2 | ELSE |
140 | 1 | pfleura2 | KX = 1 - (M-1)*INCX |
141 | 1 | pfleura2 | END IF |
142 | 1 | pfleura2 | DO 40 J = 1,N |
143 | 1 | pfleura2 | IF (Y(JY).NE.ZERO) THEN |
144 | 1 | pfleura2 | TEMP = ALPHA*CONJG(Y(JY)) |
145 | 1 | pfleura2 | IX = KX |
146 | 1 | pfleura2 | DO 30 I = 1,M |
147 | 1 | pfleura2 | A(I,J) = A(I,J) + X(IX)*TEMP |
148 | 1 | pfleura2 | IX = IX + INCX |
149 | 1 | pfleura2 | 30 CONTINUE |
150 | 1 | pfleura2 | END IF |
151 | 1 | pfleura2 | JY = JY + INCY |
152 | 1 | pfleura2 | 40 CONTINUE |
153 | 1 | pfleura2 | END IF |
154 | 1 | pfleura2 | * |
155 | 1 | pfleura2 | RETURN |
156 | 1 | pfleura2 | * |
157 | 1 | pfleura2 | * End of CGERC . |
158 | 1 | pfleura2 | * |
159 | 1 | pfleura2 | END |