root / src / lapack / double / dlasrt.f @ 11
Historique | Voir | Annoter | Télécharger (6,28 ko)
1 | 1 | pfleura2 | SUBROUTINE DLASRT( ID, N, D, INFO ) |
---|---|---|---|
2 | 1 | pfleura2 | * |
3 | 1 | pfleura2 | * -- LAPACK 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 | CHARACTER ID |
10 | 1 | pfleura2 | INTEGER INFO, N |
11 | 1 | pfleura2 | * .. |
12 | 1 | pfleura2 | * .. Array Arguments .. |
13 | 1 | pfleura2 | DOUBLE PRECISION D( * ) |
14 | 1 | pfleura2 | * .. |
15 | 1 | pfleura2 | * |
16 | 1 | pfleura2 | * Purpose |
17 | 1 | pfleura2 | * ======= |
18 | 1 | pfleura2 | * |
19 | 1 | pfleura2 | * Sort the numbers in D in increasing order (if ID = 'I') or |
20 | 1 | pfleura2 | * in decreasing order (if ID = 'D' ). |
21 | 1 | pfleura2 | * |
22 | 1 | pfleura2 | * Use Quick Sort, reverting to Insertion sort on arrays of |
23 | 1 | pfleura2 | * size <= 20. Dimension of STACK limits N to about 2**32. |
24 | 1 | pfleura2 | * |
25 | 1 | pfleura2 | * Arguments |
26 | 1 | pfleura2 | * ========= |
27 | 1 | pfleura2 | * |
28 | 1 | pfleura2 | * ID (input) CHARACTER*1 |
29 | 1 | pfleura2 | * = 'I': sort D in increasing order; |
30 | 1 | pfleura2 | * = 'D': sort D in decreasing order. |
31 | 1 | pfleura2 | * |
32 | 1 | pfleura2 | * N (input) INTEGER |
33 | 1 | pfleura2 | * The length of the array D. |
34 | 1 | pfleura2 | * |
35 | 1 | pfleura2 | * D (input/output) DOUBLE PRECISION array, dimension (N) |
36 | 1 | pfleura2 | * On entry, the array to be sorted. |
37 | 1 | pfleura2 | * On exit, D has been sorted into increasing order |
38 | 1 | pfleura2 | * (D(1) <= ... <= D(N) ) or into decreasing order |
39 | 1 | pfleura2 | * (D(1) >= ... >= D(N) ), depending on ID. |
40 | 1 | pfleura2 | * |
41 | 1 | pfleura2 | * INFO (output) INTEGER |
42 | 1 | pfleura2 | * = 0: successful exit |
43 | 1 | pfleura2 | * < 0: if INFO = -i, the i-th argument had an illegal value |
44 | 1 | pfleura2 | * |
45 | 1 | pfleura2 | * ===================================================================== |
46 | 1 | pfleura2 | * |
47 | 1 | pfleura2 | * .. Parameters .. |
48 | 1 | pfleura2 | INTEGER SELECT |
49 | 1 | pfleura2 | PARAMETER ( SELECT = 20 ) |
50 | 1 | pfleura2 | * .. |
51 | 1 | pfleura2 | * .. Local Scalars .. |
52 | 1 | pfleura2 | INTEGER DIR, ENDD, I, J, START, STKPNT |
53 | 1 | pfleura2 | DOUBLE PRECISION D1, D2, D3, DMNMX, TMP |
54 | 1 | pfleura2 | * .. |
55 | 1 | pfleura2 | * .. Local Arrays .. |
56 | 1 | pfleura2 | INTEGER STACK( 2, 32 ) |
57 | 1 | pfleura2 | * .. |
58 | 1 | pfleura2 | * .. External Functions .. |
59 | 1 | pfleura2 | LOGICAL LSAME |
60 | 1 | pfleura2 | EXTERNAL LSAME |
61 | 1 | pfleura2 | * .. |
62 | 1 | pfleura2 | * .. External Subroutines .. |
63 | 1 | pfleura2 | EXTERNAL XERBLA |
64 | 1 | pfleura2 | * .. |
65 | 1 | pfleura2 | * .. Executable Statements .. |
66 | 1 | pfleura2 | * |
67 | 1 | pfleura2 | * Test the input paramters. |
68 | 1 | pfleura2 | * |
69 | 1 | pfleura2 | INFO = 0 |
70 | 1 | pfleura2 | DIR = -1 |
71 | 1 | pfleura2 | IF( LSAME( ID, 'D' ) ) THEN |
72 | 1 | pfleura2 | DIR = 0 |
73 | 1 | pfleura2 | ELSE IF( LSAME( ID, 'I' ) ) THEN |
74 | 1 | pfleura2 | DIR = 1 |
75 | 1 | pfleura2 | END IF |
76 | 1 | pfleura2 | IF( DIR.EQ.-1 ) THEN |
77 | 1 | pfleura2 | INFO = -1 |
78 | 1 | pfleura2 | ELSE IF( N.LT.0 ) THEN |
79 | 1 | pfleura2 | INFO = -2 |
80 | 1 | pfleura2 | END IF |
81 | 1 | pfleura2 | IF( INFO.NE.0 ) THEN |
82 | 1 | pfleura2 | CALL XERBLA( 'DLASRT', -INFO ) |
83 | 1 | pfleura2 | RETURN |
84 | 1 | pfleura2 | END IF |
85 | 1 | pfleura2 | * |
86 | 1 | pfleura2 | * Quick return if possible |
87 | 1 | pfleura2 | * |
88 | 1 | pfleura2 | IF( N.LE.1 ) |
89 | 1 | pfleura2 | $ RETURN |
90 | 1 | pfleura2 | * |
91 | 1 | pfleura2 | STKPNT = 1 |
92 | 1 | pfleura2 | STACK( 1, 1 ) = 1 |
93 | 1 | pfleura2 | STACK( 2, 1 ) = N |
94 | 1 | pfleura2 | 10 CONTINUE |
95 | 1 | pfleura2 | START = STACK( 1, STKPNT ) |
96 | 1 | pfleura2 | ENDD = STACK( 2, STKPNT ) |
97 | 1 | pfleura2 | STKPNT = STKPNT - 1 |
98 | 1 | pfleura2 | IF( ENDD-START.LE.SELECT .AND. ENDD-START.GT.0 ) THEN |
99 | 1 | pfleura2 | * |
100 | 1 | pfleura2 | * Do Insertion sort on D( START:ENDD ) |
101 | 1 | pfleura2 | * |
102 | 1 | pfleura2 | IF( DIR.EQ.0 ) THEN |
103 | 1 | pfleura2 | * |
104 | 1 | pfleura2 | * Sort into decreasing order |
105 | 1 | pfleura2 | * |
106 | 1 | pfleura2 | DO 30 I = START + 1, ENDD |
107 | 1 | pfleura2 | DO 20 J = I, START + 1, -1 |
108 | 1 | pfleura2 | IF( D( J ).GT.D( J-1 ) ) THEN |
109 | 1 | pfleura2 | DMNMX = D( J ) |
110 | 1 | pfleura2 | D( J ) = D( J-1 ) |
111 | 1 | pfleura2 | D( J-1 ) = DMNMX |
112 | 1 | pfleura2 | ELSE |
113 | 1 | pfleura2 | GO TO 30 |
114 | 1 | pfleura2 | END IF |
115 | 1 | pfleura2 | 20 CONTINUE |
116 | 1 | pfleura2 | 30 CONTINUE |
117 | 1 | pfleura2 | * |
118 | 1 | pfleura2 | ELSE |
119 | 1 | pfleura2 | * |
120 | 1 | pfleura2 | * Sort into increasing order |
121 | 1 | pfleura2 | * |
122 | 1 | pfleura2 | DO 50 I = START + 1, ENDD |
123 | 1 | pfleura2 | DO 40 J = I, START + 1, -1 |
124 | 1 | pfleura2 | IF( D( J ).LT.D( J-1 ) ) THEN |
125 | 1 | pfleura2 | DMNMX = D( J ) |
126 | 1 | pfleura2 | D( J ) = D( J-1 ) |
127 | 1 | pfleura2 | D( J-1 ) = DMNMX |
128 | 1 | pfleura2 | ELSE |
129 | 1 | pfleura2 | GO TO 50 |
130 | 1 | pfleura2 | END IF |
131 | 1 | pfleura2 | 40 CONTINUE |
132 | 1 | pfleura2 | 50 CONTINUE |
133 | 1 | pfleura2 | * |
134 | 1 | pfleura2 | END IF |
135 | 1 | pfleura2 | * |
136 | 1 | pfleura2 | ELSE IF( ENDD-START.GT.SELECT ) THEN |
137 | 1 | pfleura2 | * |
138 | 1 | pfleura2 | * Partition D( START:ENDD ) and stack parts, largest one first |
139 | 1 | pfleura2 | * |
140 | 1 | pfleura2 | * Choose partition entry as median of 3 |
141 | 1 | pfleura2 | * |
142 | 1 | pfleura2 | D1 = D( START ) |
143 | 1 | pfleura2 | D2 = D( ENDD ) |
144 | 1 | pfleura2 | I = ( START+ENDD ) / 2 |
145 | 1 | pfleura2 | D3 = D( I ) |
146 | 1 | pfleura2 | IF( D1.LT.D2 ) THEN |
147 | 1 | pfleura2 | IF( D3.LT.D1 ) THEN |
148 | 1 | pfleura2 | DMNMX = D1 |
149 | 1 | pfleura2 | ELSE IF( D3.LT.D2 ) THEN |
150 | 1 | pfleura2 | DMNMX = D3 |
151 | 1 | pfleura2 | ELSE |
152 | 1 | pfleura2 | DMNMX = D2 |
153 | 1 | pfleura2 | END IF |
154 | 1 | pfleura2 | ELSE |
155 | 1 | pfleura2 | IF( D3.LT.D2 ) THEN |
156 | 1 | pfleura2 | DMNMX = D2 |
157 | 1 | pfleura2 | ELSE IF( D3.LT.D1 ) THEN |
158 | 1 | pfleura2 | DMNMX = D3 |
159 | 1 | pfleura2 | ELSE |
160 | 1 | pfleura2 | DMNMX = D1 |
161 | 1 | pfleura2 | END IF |
162 | 1 | pfleura2 | END IF |
163 | 1 | pfleura2 | * |
164 | 1 | pfleura2 | IF( DIR.EQ.0 ) THEN |
165 | 1 | pfleura2 | * |
166 | 1 | pfleura2 | * Sort into decreasing order |
167 | 1 | pfleura2 | * |
168 | 1 | pfleura2 | I = START - 1 |
169 | 1 | pfleura2 | J = ENDD + 1 |
170 | 1 | pfleura2 | 60 CONTINUE |
171 | 1 | pfleura2 | 70 CONTINUE |
172 | 1 | pfleura2 | J = J - 1 |
173 | 1 | pfleura2 | IF( D( J ).LT.DMNMX ) |
174 | 1 | pfleura2 | $ GO TO 70 |
175 | 1 | pfleura2 | 80 CONTINUE |
176 | 1 | pfleura2 | I = I + 1 |
177 | 1 | pfleura2 | IF( D( I ).GT.DMNMX ) |
178 | 1 | pfleura2 | $ GO TO 80 |
179 | 1 | pfleura2 | IF( I.LT.J ) THEN |
180 | 1 | pfleura2 | TMP = D( I ) |
181 | 1 | pfleura2 | D( I ) = D( J ) |
182 | 1 | pfleura2 | D( J ) = TMP |
183 | 1 | pfleura2 | GO TO 60 |
184 | 1 | pfleura2 | END IF |
185 | 1 | pfleura2 | IF( J-START.GT.ENDD-J-1 ) THEN |
186 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
187 | 1 | pfleura2 | STACK( 1, STKPNT ) = START |
188 | 1 | pfleura2 | STACK( 2, STKPNT ) = J |
189 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
190 | 1 | pfleura2 | STACK( 1, STKPNT ) = J + 1 |
191 | 1 | pfleura2 | STACK( 2, STKPNT ) = ENDD |
192 | 1 | pfleura2 | ELSE |
193 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
194 | 1 | pfleura2 | STACK( 1, STKPNT ) = J + 1 |
195 | 1 | pfleura2 | STACK( 2, STKPNT ) = ENDD |
196 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
197 | 1 | pfleura2 | STACK( 1, STKPNT ) = START |
198 | 1 | pfleura2 | STACK( 2, STKPNT ) = J |
199 | 1 | pfleura2 | END IF |
200 | 1 | pfleura2 | ELSE |
201 | 1 | pfleura2 | * |
202 | 1 | pfleura2 | * Sort into increasing order |
203 | 1 | pfleura2 | * |
204 | 1 | pfleura2 | I = START - 1 |
205 | 1 | pfleura2 | J = ENDD + 1 |
206 | 1 | pfleura2 | 90 CONTINUE |
207 | 1 | pfleura2 | 100 CONTINUE |
208 | 1 | pfleura2 | J = J - 1 |
209 | 1 | pfleura2 | IF( D( J ).GT.DMNMX ) |
210 | 1 | pfleura2 | $ GO TO 100 |
211 | 1 | pfleura2 | 110 CONTINUE |
212 | 1 | pfleura2 | I = I + 1 |
213 | 1 | pfleura2 | IF( D( I ).LT.DMNMX ) |
214 | 1 | pfleura2 | $ GO TO 110 |
215 | 1 | pfleura2 | IF( I.LT.J ) THEN |
216 | 1 | pfleura2 | TMP = D( I ) |
217 | 1 | pfleura2 | D( I ) = D( J ) |
218 | 1 | pfleura2 | D( J ) = TMP |
219 | 1 | pfleura2 | GO TO 90 |
220 | 1 | pfleura2 | END IF |
221 | 1 | pfleura2 | IF( J-START.GT.ENDD-J-1 ) THEN |
222 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
223 | 1 | pfleura2 | STACK( 1, STKPNT ) = START |
224 | 1 | pfleura2 | STACK( 2, STKPNT ) = J |
225 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
226 | 1 | pfleura2 | STACK( 1, STKPNT ) = J + 1 |
227 | 1 | pfleura2 | STACK( 2, STKPNT ) = ENDD |
228 | 1 | pfleura2 | ELSE |
229 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
230 | 1 | pfleura2 | STACK( 1, STKPNT ) = J + 1 |
231 | 1 | pfleura2 | STACK( 2, STKPNT ) = ENDD |
232 | 1 | pfleura2 | STKPNT = STKPNT + 1 |
233 | 1 | pfleura2 | STACK( 1, STKPNT ) = START |
234 | 1 | pfleura2 | STACK( 2, STKPNT ) = J |
235 | 1 | pfleura2 | END IF |
236 | 1 | pfleura2 | END IF |
237 | 1 | pfleura2 | END IF |
238 | 1 | pfleura2 | IF( STKPNT.GT.0 ) |
239 | 1 | pfleura2 | $ GO TO 10 |
240 | 1 | pfleura2 | RETURN |
241 | 1 | pfleura2 | * |
242 | 1 | pfleura2 | * End of DLASRT |
243 | 1 | pfleura2 | * |
244 | 1 | pfleura2 | END |