root / src / lapack / double / dlartg.f @ 10
Historique | Voir | Annoter | Télécharger (4,02 ko)
1 | 1 | pfleura2 | SUBROUTINE DLARTG( F, G, CS, SN, R ) |
---|---|---|---|
2 | 1 | pfleura2 | * |
3 | 1 | pfleura2 | * -- LAPACK auxiliary routine (version 3.2) -- |
4 | 1 | pfleura2 | * -- LAPACK is a software package provided by Univ. of Tennessee, -- |
5 | 1 | pfleura2 | * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- |
6 | 1 | pfleura2 | * November 2006 |
7 | 1 | pfleura2 | * |
8 | 1 | pfleura2 | * .. Scalar Arguments .. |
9 | 1 | pfleura2 | DOUBLE PRECISION CS, F, G, R, SN |
10 | 1 | pfleura2 | * .. |
11 | 1 | pfleura2 | * |
12 | 1 | pfleura2 | * Purpose |
13 | 1 | pfleura2 | * ======= |
14 | 1 | pfleura2 | * |
15 | 1 | pfleura2 | * DLARTG generate a plane rotation so that |
16 | 1 | pfleura2 | * |
17 | 1 | pfleura2 | * [ CS SN ] . [ F ] = [ R ] where CS**2 + SN**2 = 1. |
18 | 1 | pfleura2 | * [ -SN CS ] [ G ] [ 0 ] |
19 | 1 | pfleura2 | * |
20 | 1 | pfleura2 | * This is a slower, more accurate version of the BLAS1 routine DROTG, |
21 | 1 | pfleura2 | * with the following other differences: |
22 | 1 | pfleura2 | * F and G are unchanged on return. |
23 | 1 | pfleura2 | * If G=0, then CS=1 and SN=0. |
24 | 1 | pfleura2 | * If F=0 and (G .ne. 0), then CS=0 and SN=1 without doing any |
25 | 1 | pfleura2 | * floating point operations (saves work in DBDSQR when |
26 | 1 | pfleura2 | * there are zeros on the diagonal). |
27 | 1 | pfleura2 | * |
28 | 1 | pfleura2 | * If F exceeds G in magnitude, CS will be positive. |
29 | 1 | pfleura2 | * |
30 | 1 | pfleura2 | * Arguments |
31 | 1 | pfleura2 | * ========= |
32 | 1 | pfleura2 | * |
33 | 1 | pfleura2 | * F (input) DOUBLE PRECISION |
34 | 1 | pfleura2 | * The first component of vector to be rotated. |
35 | 1 | pfleura2 | * |
36 | 1 | pfleura2 | * G (input) DOUBLE PRECISION |
37 | 1 | pfleura2 | * The second component of vector to be rotated. |
38 | 1 | pfleura2 | * |
39 | 1 | pfleura2 | * CS (output) DOUBLE PRECISION |
40 | 1 | pfleura2 | * The cosine of the rotation. |
41 | 1 | pfleura2 | * |
42 | 1 | pfleura2 | * SN (output) DOUBLE PRECISION |
43 | 1 | pfleura2 | * The sine of the rotation. |
44 | 1 | pfleura2 | * |
45 | 1 | pfleura2 | * R (output) DOUBLE PRECISION |
46 | 1 | pfleura2 | * The nonzero component of the rotated vector. |
47 | 1 | pfleura2 | * |
48 | 1 | pfleura2 | * This version has a few statements commented out for thread safety |
49 | 1 | pfleura2 | * (machine parameters are computed on each entry). 10 feb 03, SJH. |
50 | 1 | pfleura2 | * |
51 | 1 | pfleura2 | * ===================================================================== |
52 | 1 | pfleura2 | * |
53 | 1 | pfleura2 | * .. Parameters .. |
54 | 1 | pfleura2 | DOUBLE PRECISION ZERO |
55 | 1 | pfleura2 | PARAMETER ( ZERO = 0.0D0 ) |
56 | 1 | pfleura2 | DOUBLE PRECISION ONE |
57 | 1 | pfleura2 | PARAMETER ( ONE = 1.0D0 ) |
58 | 1 | pfleura2 | DOUBLE PRECISION TWO |
59 | 1 | pfleura2 | PARAMETER ( TWO = 2.0D0 ) |
60 | 1 | pfleura2 | * .. |
61 | 1 | pfleura2 | * .. Local Scalars .. |
62 | 1 | pfleura2 | * LOGICAL FIRST |
63 | 1 | pfleura2 | INTEGER COUNT, I |
64 | 1 | pfleura2 | DOUBLE PRECISION EPS, F1, G1, SAFMIN, SAFMN2, SAFMX2, SCALE |
65 | 1 | pfleura2 | * .. |
66 | 1 | pfleura2 | * .. External Functions .. |
67 | 1 | pfleura2 | DOUBLE PRECISION DLAMCH |
68 | 1 | pfleura2 | EXTERNAL DLAMCH |
69 | 1 | pfleura2 | * .. |
70 | 1 | pfleura2 | * .. Intrinsic Functions .. |
71 | 1 | pfleura2 | INTRINSIC ABS, INT, LOG, MAX, SQRT |
72 | 1 | pfleura2 | * .. |
73 | 1 | pfleura2 | * .. Save statement .. |
74 | 1 | pfleura2 | * SAVE FIRST, SAFMX2, SAFMIN, SAFMN2 |
75 | 1 | pfleura2 | * .. |
76 | 1 | pfleura2 | * .. Data statements .. |
77 | 1 | pfleura2 | * DATA FIRST / .TRUE. / |
78 | 1 | pfleura2 | * .. |
79 | 1 | pfleura2 | * .. Executable Statements .. |
80 | 1 | pfleura2 | * |
81 | 1 | pfleura2 | * IF( FIRST ) THEN |
82 | 1 | pfleura2 | SAFMIN = DLAMCH( 'S' ) |
83 | 1 | pfleura2 | EPS = DLAMCH( 'E' ) |
84 | 1 | pfleura2 | SAFMN2 = DLAMCH( 'B' )**INT( LOG( SAFMIN / EPS ) / |
85 | 1 | pfleura2 | $ LOG( DLAMCH( 'B' ) ) / TWO ) |
86 | 1 | pfleura2 | SAFMX2 = ONE / SAFMN2 |
87 | 1 | pfleura2 | * FIRST = .FALSE. |
88 | 1 | pfleura2 | * END IF |
89 | 1 | pfleura2 | IF( G.EQ.ZERO ) THEN |
90 | 1 | pfleura2 | CS = ONE |
91 | 1 | pfleura2 | SN = ZERO |
92 | 1 | pfleura2 | R = F |
93 | 1 | pfleura2 | ELSE IF( F.EQ.ZERO ) THEN |
94 | 1 | pfleura2 | CS = ZERO |
95 | 1 | pfleura2 | SN = ONE |
96 | 1 | pfleura2 | R = G |
97 | 1 | pfleura2 | ELSE |
98 | 1 | pfleura2 | F1 = F |
99 | 1 | pfleura2 | G1 = G |
100 | 1 | pfleura2 | SCALE = MAX( ABS( F1 ), ABS( G1 ) ) |
101 | 1 | pfleura2 | IF( SCALE.GE.SAFMX2 ) THEN |
102 | 1 | pfleura2 | COUNT = 0 |
103 | 1 | pfleura2 | 10 CONTINUE |
104 | 1 | pfleura2 | COUNT = COUNT + 1 |
105 | 1 | pfleura2 | F1 = F1*SAFMN2 |
106 | 1 | pfleura2 | G1 = G1*SAFMN2 |
107 | 1 | pfleura2 | SCALE = MAX( ABS( F1 ), ABS( G1 ) ) |
108 | 1 | pfleura2 | IF( SCALE.GE.SAFMX2 ) |
109 | 1 | pfleura2 | $ GO TO 10 |
110 | 1 | pfleura2 | R = SQRT( F1**2+G1**2 ) |
111 | 1 | pfleura2 | CS = F1 / R |
112 | 1 | pfleura2 | SN = G1 / R |
113 | 1 | pfleura2 | DO 20 I = 1, COUNT |
114 | 1 | pfleura2 | R = R*SAFMX2 |
115 | 1 | pfleura2 | 20 CONTINUE |
116 | 1 | pfleura2 | ELSE IF( SCALE.LE.SAFMN2 ) THEN |
117 | 1 | pfleura2 | COUNT = 0 |
118 | 1 | pfleura2 | 30 CONTINUE |
119 | 1 | pfleura2 | COUNT = COUNT + 1 |
120 | 1 | pfleura2 | F1 = F1*SAFMX2 |
121 | 1 | pfleura2 | G1 = G1*SAFMX2 |
122 | 1 | pfleura2 | SCALE = MAX( ABS( F1 ), ABS( G1 ) ) |
123 | 1 | pfleura2 | IF( SCALE.LE.SAFMN2 ) |
124 | 1 | pfleura2 | $ GO TO 30 |
125 | 1 | pfleura2 | R = SQRT( F1**2+G1**2 ) |
126 | 1 | pfleura2 | CS = F1 / R |
127 | 1 | pfleura2 | SN = G1 / R |
128 | 1 | pfleura2 | DO 40 I = 1, COUNT |
129 | 1 | pfleura2 | R = R*SAFMN2 |
130 | 1 | pfleura2 | 40 CONTINUE |
131 | 1 | pfleura2 | ELSE |
132 | 1 | pfleura2 | R = SQRT( F1**2+G1**2 ) |
133 | 1 | pfleura2 | CS = F1 / R |
134 | 1 | pfleura2 | SN = G1 / R |
135 | 1 | pfleura2 | END IF |
136 | 1 | pfleura2 | IF( ABS( F ).GT.ABS( G ) .AND. CS.LT.ZERO ) THEN |
137 | 1 | pfleura2 | CS = -CS |
138 | 1 | pfleura2 | SN = -SN |
139 | 1 | pfleura2 | R = -R |
140 | 1 | pfleura2 | END IF |
141 | 1 | pfleura2 | END IF |
142 | 1 | pfleura2 | RETURN |
143 | 1 | pfleura2 | * |
144 | 1 | pfleura2 | * End of DLARTG |
145 | 1 | pfleura2 | * |
146 | 1 | pfleura2 | END |