GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dhels.f
Go to the documentation of this file.
1C Work performed under the auspices of the U.S. Department of Energy
2C by Lawrence Livermore National Laboratory under contract number
3C W-7405-Eng-48.
4C
5 SUBROUTINE dhels (A, LDA, N, Q, B)
6C
7C***BEGIN PROLOGUE DHELS
8C***DATE WRITTEN 890101 (YYMMDD)
9C***REVISION DATE 900926 (YYMMDD)
10C
11C
12C-----------------------------------------------------------------------
13C***DESCRIPTION
14C
15C This is similar to the LINPACK routine DGESL except that
16C A is an upper Hessenberg matrix.
17C
18C DHELS solves the least squares problem
19C
20C MIN (B-A*X,B-A*X)
21C
22C using the factors computed by DHEQR.
23C
24C On entry
25C
26C A DOUBLE PRECISION (LDA, N)
27C The output from DHEQR which contains the upper
28C triangular factor R in the QR decomposition of A.
29C
30C LDA INTEGER
31C The leading dimension of the array A .
32C
33C N INTEGER
34C A is originally an (N+1) by N matrix.
35C
36C Q DOUBLE PRECISION(2*N)
37C The coefficients of the N givens rotations
38C used in the QR factorization of A.
39C
40C B DOUBLE PRECISION(N+1)
41C The right hand side vector.
42C
43C
44C On return
45C
46C B The solution vector X.
47C
48C
49C Modification of LINPACK.
50C Peter Brown, Lawrence Livermore Natl. Lab.
51C
52C-----------------------------------------------------------------------
53C***ROUTINES CALLED
54C DAXPY
55C
56C***END PROLOGUE DHELS
57C
58 INTEGER LDA, N
59 DOUBLE PRECISION A(LDA,*), B(*), Q(*)
60 INTEGER IQ, K, KB, KP1
61 DOUBLE PRECISION C, S, T, T1, T2
62C
63C Minimize (B-A*X,B-A*X).
64C First form Q*B.
65C
66 DO 20 k = 1, n
67 kp1 = k + 1
68 iq = 2*(k-1) + 1
69 c = q(iq)
70 s = q(iq+1)
71 t1 = b(k)
72 t2 = b(kp1)
73 b(k) = c*t1 - s*t2
74 b(kp1) = s*t1 + c*t2
75 20 CONTINUE
76C
77C Now solve R*X = Q*B.
78C
79 DO 40 kb = 1, n
80 k = n + 1 - kb
81 b(k) = b(k)/a(k,k)
82 t = -b(k)
83 CALL daxpy (k-1, t, a(1,k), 1, b(1), 1)
84 40 CONTINUE
85 RETURN
86C
87C------END OF SUBROUTINE DHELS------------------------------------------
88 END
subroutine dhels(a, lda, n, q, b)
Definition dhels.f:6