LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
stpsv.f
Go to the documentation of this file.
1 *> \brief \b STPSV
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE STPSV(UPLO,TRANS,DIAG,N,AP,X,INCX)
12 *
13 * .. Scalar Arguments ..
14 * INTEGER INCX,N
15 * CHARACTER DIAG,TRANS,UPLO
16 * ..
17 * .. Array Arguments ..
18 * REAL AP(*),X(*)
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> STPSV solves one of the systems of equations
28 *>
29 *> A*x = b, or A**T*x = b,
30 *>
31 *> where b and x are n element vectors and A is an n by n unit, or
32 *> non-unit, upper or lower triangular matrix, supplied in packed form.
33 *>
34 *> No test for singularity or near-singularity is included in this
35 *> routine. Such tests must be performed before calling this routine.
36 *> \endverbatim
37 *
38 * Arguments:
39 * ==========
40 *
41 *> \param[in] UPLO
42 *> \verbatim
43 *> UPLO is CHARACTER*1
44 *> On entry, UPLO specifies whether the matrix is an upper or
45 *> lower triangular matrix as follows:
46 *>
47 *> UPLO = 'U' or 'u' A is an upper triangular matrix.
48 *>
49 *> UPLO = 'L' or 'l' A is a lower triangular matrix.
50 *> \endverbatim
51 *>
52 *> \param[in] TRANS
53 *> \verbatim
54 *> TRANS is CHARACTER*1
55 *> On entry, TRANS specifies the equations to be solved as
56 *> follows:
57 *>
58 *> TRANS = 'N' or 'n' A*x = b.
59 *>
60 *> TRANS = 'T' or 't' A**T*x = b.
61 *>
62 *> TRANS = 'C' or 'c' A**T*x = b.
63 *> \endverbatim
64 *>
65 *> \param[in] DIAG
66 *> \verbatim
67 *> DIAG is CHARACTER*1
68 *> On entry, DIAG specifies whether or not A is unit
69 *> triangular as follows:
70 *>
71 *> DIAG = 'U' or 'u' A is assumed to be unit triangular.
72 *>
73 *> DIAG = 'N' or 'n' A is not assumed to be unit
74 *> triangular.
75 *> \endverbatim
76 *>
77 *> \param[in] N
78 *> \verbatim
79 *> N is INTEGER
80 *> On entry, N specifies the order of the matrix A.
81 *> N must be at least zero.
82 *> \endverbatim
83 *>
84 *> \param[in] AP
85 *> \verbatim
86 *> AP is REAL array of DIMENSION at least
87 *> ( ( n*( n + 1 ) )/2 ).
88 *> Before entry with UPLO = 'U' or 'u', the array AP must
89 *> contain the upper triangular matrix packed sequentially,
90 *> column by column, so that AP( 1 ) contains a( 1, 1 ),
91 *> AP( 2 ) and AP( 3 ) contain a( 1, 2 ) and a( 2, 2 )
92 *> respectively, and so on.
93 *> Before entry with UPLO = 'L' or 'l', the array AP must
94 *> contain the lower triangular matrix packed sequentially,
95 *> column by column, so that AP( 1 ) contains a( 1, 1 ),
96 *> AP( 2 ) and AP( 3 ) contain a( 2, 1 ) and a( 3, 1 )
97 *> respectively, and so on.
98 *> Note that when DIAG = 'U' or 'u', the diagonal elements of
99 *> A are not referenced, but are assumed to be unity.
100 *> \endverbatim
101 *>
102 *> \param[in,out] X
103 *> \verbatim
104 *> X is REAL array of dimension at least
105 *> ( 1 + ( n - 1 )*abs( INCX ) ).
106 *> Before entry, the incremented array X must contain the n
107 *> element right-hand side vector b. On exit, X is overwritten
108 *> with the solution vector x.
109 *> \endverbatim
110 *>
111 *> \param[in] INCX
112 *> \verbatim
113 *> INCX is INTEGER
114 *> On entry, INCX specifies the increment for the elements of
115 *> X. INCX must not be zero.
116 *> \endverbatim
117 *
118 * Authors:
119 * ========
120 *
121 *> \author Univ. of Tennessee
122 *> \author Univ. of California Berkeley
123 *> \author Univ. of Colorado Denver
124 *> \author NAG Ltd.
125 *
126 *> \date November 2011
127 *
128 *> \ingroup single_blas_level2
129 *
130 *> \par Further Details:
131 * =====================
132 *>
133 *> \verbatim
134 *>
135 *> Level 2 Blas routine.
136 *>
137 *> -- Written on 22-October-1986.
138 *> Jack Dongarra, Argonne National Lab.
139 *> Jeremy Du Croz, Nag Central Office.
140 *> Sven Hammarling, Nag Central Office.
141 *> Richard Hanson, Sandia National Labs.
142 *> \endverbatim
143 *>
144 * =====================================================================
145  SUBROUTINE stpsv(UPLO,TRANS,DIAG,N,AP,X,INCX)
146 *
147 * -- Reference BLAS level2 routine (version 3.4.0) --
148 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
149 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
150 * November 2011
151 *
152 * .. Scalar Arguments ..
153  INTEGER INCX,N
154  CHARACTER DIAG,TRANS,UPLO
155 * ..
156 * .. Array Arguments ..
157  REAL AP(*),X(*)
158 * ..
159 *
160 * =====================================================================
161 *
162 * .. Parameters ..
163  REAL ZERO
164  parameter(zero=0.0e+0)
165 * ..
166 * .. Local Scalars ..
167  REAL TEMP
168  INTEGER I,INFO,IX,J,JX,K,KK,KX
169  LOGICAL NOUNIT
170 * ..
171 * .. External Functions ..
172  LOGICAL LSAME
173  EXTERNAL lsame
174 * ..
175 * .. External Subroutines ..
176  EXTERNAL xerbla
177 * ..
178 *
179 * Test the input parameters.
180 *
181  info = 0
182  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
183  info = 1
184  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
185  + .NOT.lsame(trans,'C')) THEN
186  info = 2
187  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
188  info = 3
189  ELSE IF (n.LT.0) THEN
190  info = 4
191  ELSE IF (incx.EQ.0) THEN
192  info = 7
193  END IF
194  IF (info.NE.0) THEN
195  CALL xerbla('STPSV ',info)
196  RETURN
197  END IF
198 *
199 * Quick return if possible.
200 *
201  IF (n.EQ.0) RETURN
202 *
203  nounit = lsame(diag,'N')
204 *
205 * Set up the start point in X if the increment is not unity. This
206 * will be ( N - 1 )*INCX too small for descending loops.
207 *
208  IF (incx.LE.0) THEN
209  kx = 1 - (n-1)*incx
210  ELSE IF (incx.NE.1) THEN
211  kx = 1
212  END IF
213 *
214 * Start the operations. In this version the elements of AP are
215 * accessed sequentially with one pass through AP.
216 *
217  IF (lsame(trans,'N')) THEN
218 *
219 * Form x := inv( A )*x.
220 *
221  IF (lsame(uplo,'U')) THEN
222  kk = (n* (n+1))/2
223  IF (incx.EQ.1) THEN
224  DO 20 j = n,1,-1
225  IF (x(j).NE.zero) THEN
226  IF (nounit) x(j) = x(j)/ap(kk)
227  temp = x(j)
228  k = kk - 1
229  DO 10 i = j - 1,1,-1
230  x(i) = x(i) - temp*ap(k)
231  k = k - 1
232  10 CONTINUE
233  END IF
234  kk = kk - j
235  20 CONTINUE
236  ELSE
237  jx = kx + (n-1)*incx
238  DO 40 j = n,1,-1
239  IF (x(jx).NE.zero) THEN
240  IF (nounit) x(jx) = x(jx)/ap(kk)
241  temp = x(jx)
242  ix = jx
243  DO 30 k = kk - 1,kk - j + 1,-1
244  ix = ix - incx
245  x(ix) = x(ix) - temp*ap(k)
246  30 CONTINUE
247  END IF
248  jx = jx - incx
249  kk = kk - j
250  40 CONTINUE
251  END IF
252  ELSE
253  kk = 1
254  IF (incx.EQ.1) THEN
255  DO 60 j = 1,n
256  IF (x(j).NE.zero) THEN
257  IF (nounit) x(j) = x(j)/ap(kk)
258  temp = x(j)
259  k = kk + 1
260  DO 50 i = j + 1,n
261  x(i) = x(i) - temp*ap(k)
262  k = k + 1
263  50 CONTINUE
264  END IF
265  kk = kk + (n-j+1)
266  60 CONTINUE
267  ELSE
268  jx = kx
269  DO 80 j = 1,n
270  IF (x(jx).NE.zero) THEN
271  IF (nounit) x(jx) = x(jx)/ap(kk)
272  temp = x(jx)
273  ix = jx
274  DO 70 k = kk + 1,kk + n - j
275  ix = ix + incx
276  x(ix) = x(ix) - temp*ap(k)
277  70 CONTINUE
278  END IF
279  jx = jx + incx
280  kk = kk + (n-j+1)
281  80 CONTINUE
282  END IF
283  END IF
284  ELSE
285 *
286 * Form x := inv( A**T )*x.
287 *
288  IF (lsame(uplo,'U')) THEN
289  kk = 1
290  IF (incx.EQ.1) THEN
291  DO 100 j = 1,n
292  temp = x(j)
293  k = kk
294  DO 90 i = 1,j - 1
295  temp = temp - ap(k)*x(i)
296  k = k + 1
297  90 CONTINUE
298  IF (nounit) temp = temp/ap(kk+j-1)
299  x(j) = temp
300  kk = kk + j
301  100 CONTINUE
302  ELSE
303  jx = kx
304  DO 120 j = 1,n
305  temp = x(jx)
306  ix = kx
307  DO 110 k = kk,kk + j - 2
308  temp = temp - ap(k)*x(ix)
309  ix = ix + incx
310  110 CONTINUE
311  IF (nounit) temp = temp/ap(kk+j-1)
312  x(jx) = temp
313  jx = jx + incx
314  kk = kk + j
315  120 CONTINUE
316  END IF
317  ELSE
318  kk = (n* (n+1))/2
319  IF (incx.EQ.1) THEN
320  DO 140 j = n,1,-1
321  temp = x(j)
322  k = kk
323  DO 130 i = n,j + 1,-1
324  temp = temp - ap(k)*x(i)
325  k = k - 1
326  130 CONTINUE
327  IF (nounit) temp = temp/ap(kk-n+j)
328  x(j) = temp
329  kk = kk - (n-j+1)
330  140 CONTINUE
331  ELSE
332  kx = kx + (n-1)*incx
333  jx = kx
334  DO 160 j = n,1,-1
335  temp = x(jx)
336  ix = kx
337  DO 150 k = kk,kk - (n- (j+1)),-1
338  temp = temp - ap(k)*x(ix)
339  ix = ix - incx
340  150 CONTINUE
341  IF (nounit) temp = temp/ap(kk-n+j)
342  x(jx) = temp
343  jx = jx - incx
344  kk = kk - (n-j+1)
345  160 CONTINUE
346  END IF
347  END IF
348  END IF
349 *
350  RETURN
351 *
352 * End of STPSV .
353 *
354  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine stpsv(UPLO, TRANS, DIAG, N, AP, X, INCX)
STPSV
Definition: stpsv.f:146