root / src / refsor.f90 @ 4
Historique | Voir | Annoter | Télécharger (13,71 ko)
1 |
!!! Downloaded from http://www.fortran-2000.com/rank/index.html |
---|---|
2 |
!!! on October 13th, 2010 |
3 |
|
4 |
!PFL 2010 Oct 13-> |
5 |
! I deleted the 'module' part to keep only |
6 |
! the Double subroutine. |
7 |
|
8 |
! Module m_refsor |
9 |
! ! PFL 2010 Oct 13 -> |
10 |
! !Integer, Parameter :: kdp = selected_real_kind(15) |
11 |
! Integer, Parameter :: kdp = KIND(1.0D0) |
12 |
! ! <- PFL 2010 Oct 13 |
13 |
! public :: refsor |
14 |
! private :: kdp |
15 |
! private :: R_refsor, I_refsor, D_refsor |
16 |
! private :: R_inssor, I_inssor, D_inssor |
17 |
! private :: R_subsor, I_subsor, D_subsor |
18 |
! interface refsor |
19 |
! module procedure d_refsor, r_refsor, i_refsor |
20 |
! end interface refsor |
21 |
! contains |
22 |
|
23 |
! Subroutine D_refsor (XDONT) |
24 |
Subroutine Drefsor (XDONT) |
25 |
! Sorts XDONT into ascending order - Quicksort |
26 |
! __________________________________________________________ |
27 |
! Quicksort chooses a "pivot" in the set, and explores the |
28 |
! array from both ends, looking for a value > pivot with the |
29 |
! increasing index, for a value <= pivot with the decreasing |
30 |
! index, and swapping them when it has found one of each. |
31 |
! The array is then subdivided in 2 ([3]) subsets: |
32 |
! { values <= pivot} {pivot} {values > pivot} |
33 |
! One then call recursively the program to sort each subset. |
34 |
! When the size of the subarray is small enough, one uses an |
35 |
! insertion sort that is faster for very small sets. |
36 |
! Michel Olagnon - Apr. 2000 |
37 |
! __________________________________________________________ |
38 |
! __________________________________________________________ |
39 |
|
40 |
use VarTypes |
41 |
|
42 |
Real (KREAL), Dimension (:), Intent (InOut) :: XDONT |
43 |
! __________________________________________________________ |
44 |
! |
45 |
! |
46 |
Call D_subsor (XDONT, 1, Size (XDONT)) |
47 |
Call D_inssor (XDONT) |
48 |
Return |
49 |
End Subroutine Drefsor |
50 |
|
51 |
Recursive Subroutine D_subsor (XDONT, IDEB1, IFIN1) |
52 |
! Sorts XDONT from IDEB1 to IFIN1 |
53 |
! __________________________________________________________ |
54 |
|
55 |
use VarTypes |
56 |
|
57 |
IMPLICIT NONE |
58 |
|
59 |
Real(KREAL), dimension (:), Intent (InOut) :: XDONT |
60 |
Integer(KINT), Intent (In) :: IDEB1, IFIN1 |
61 |
! __________________________________________________________ |
62 |
Integer(KINT), Parameter :: NINS = 16 ! Max for insertion sort |
63 |
Integer(KINT) :: ICRS, IDEB, IDCR, IFIN, IMIL |
64 |
Real(KREAL) :: XPIV, XWRK |
65 |
! |
66 |
IDEB = IDEB1 |
67 |
IFIN = IFIN1 |
68 |
! |
69 |
! If we don't have enough values to make it worth while, we leave |
70 |
! them unsorted, and the final insertion sort will take care of them |
71 |
! |
72 |
If ((IFIN - IDEB) > NINS) Then |
73 |
IMIL = (IDEB+IFIN) / 2 |
74 |
! |
75 |
! One chooses a pivot, median of 1st, last, and middle values |
76 |
! |
77 |
If (XDONT(IMIL) < XDONT(IDEB)) Then |
78 |
XWRK = XDONT (IDEB) |
79 |
XDONT (IDEB) = XDONT (IMIL) |
80 |
XDONT (IMIL) = XWRK |
81 |
End If |
82 |
If (XDONT(IMIL) > XDONT(IFIN)) Then |
83 |
XWRK = XDONT (IFIN) |
84 |
XDONT (IFIN) = XDONT (IMIL) |
85 |
XDONT (IMIL) = XWRK |
86 |
If (XDONT(IMIL) < XDONT(IDEB)) Then |
87 |
XWRK = XDONT (IDEB) |
88 |
XDONT (IDEB) = XDONT (IMIL) |
89 |
XDONT (IMIL) = XWRK |
90 |
End If |
91 |
End If |
92 |
XPIV = XDONT (IMIL) |
93 |
! |
94 |
! One exchanges values to put those > pivot in the end and |
95 |
! those <= pivot at the beginning |
96 |
! |
97 |
ICRS = IDEB |
98 |
IDCR = IFIN |
99 |
ECH2: Do |
100 |
Do |
101 |
ICRS = ICRS + 1 |
102 |
If (ICRS >= IDCR) Then |
103 |
! |
104 |
! the first > pivot is IDCR |
105 |
! the last <= pivot is ICRS-1 |
106 |
! Note: If one arrives here on the first iteration, then |
107 |
! the pivot is the maximum of the set, the last value is equal |
108 |
! to it, and one can reduce by one the size of the set to process, |
109 |
! as if XDONT (IFIN) > XPIV |
110 |
! |
111 |
Exit ECH2 |
112 |
! |
113 |
End If |
114 |
If (XDONT(ICRS) > XPIV) Exit |
115 |
End Do |
116 |
Do |
117 |
If (XDONT(IDCR) <= XPIV) Exit |
118 |
IDCR = IDCR - 1 |
119 |
If (ICRS >= IDCR) Then |
120 |
! |
121 |
! The last value < pivot is always ICRS-1 |
122 |
! |
123 |
Exit ECH2 |
124 |
End If |
125 |
End Do |
126 |
! |
127 |
XWRK = XDONT (IDCR) |
128 |
XDONT (IDCR) = XDONT (ICRS) |
129 |
XDONT (ICRS) = XWRK |
130 |
End Do ECH2 |
131 |
! |
132 |
! One now sorts each of the two sub-intervals |
133 |
! |
134 |
Call D_subsor (XDONT, IDEB1, ICRS-1) |
135 |
Call D_subsor (XDONT, IDCR, IFIN1) |
136 |
End If |
137 |
Return |
138 |
End Subroutine D_subsor |
139 |
|
140 |
Subroutine D_inssor (XDONT) |
141 |
! Sorts XDONT into increasing order (Insertion sort) |
142 |
! __________________________________________________________ |
143 |
|
144 |
use VarTypes |
145 |
|
146 |
IMPLICIT NONE |
147 |
Real(KREAL), dimension (:), Intent (InOut) :: XDONT |
148 |
! __________________________________________________________ |
149 |
Integer(KINT) :: ICRS, IDCR |
150 |
Real(KREAL) :: XWRK |
151 |
! |
152 |
Do ICRS = 2, Size (XDONT) |
153 |
XWRK = XDONT (ICRS) |
154 |
If (XWRK >= XDONT(ICRS-1)) Cycle |
155 |
XDONT (ICRS) = XDONT (ICRS-1) |
156 |
Do IDCR = ICRS - 2, 1, - 1 |
157 |
If (XWRK >= XDONT(IDCR)) Exit |
158 |
XDONT (IDCR+1) = XDONT (IDCR) |
159 |
End Do |
160 |
XDONT (IDCR+1) = XWRK |
161 |
End Do |
162 |
! |
163 |
Return |
164 |
! |
165 |
End Subroutine D_inssor |
166 |
|
167 |
|
168 |
! ! |
169 |
! Subroutine R_refsor (XDONT) |
170 |
! ! Sorts XDONT into ascending order - Quicksort |
171 |
! ! __________________________________________________________ |
172 |
! ! Quicksort chooses a "pivot" in the set, and explores the |
173 |
! ! array from both ends, looking for a value > pivot with the |
174 |
! ! increasing index, for a value <= pivot with the decreasing |
175 |
! ! index, and swapping them when it has found one of each. |
176 |
! ! The array is then subdivided in 2 ([3]) subsets: |
177 |
! ! { values <= pivot} {pivot} {values > pivot} |
178 |
! ! One then call recursively the program to sort each subset. |
179 |
! ! When the size of the subarray is small enough, one uses an |
180 |
! ! insertion sort that is faster for very small sets. |
181 |
! ! Michel Olagnon - Apr. 2000 |
182 |
! ! __________________________________________________________ |
183 |
! ! _________________________________________________________ |
184 |
! Real, Dimension (:), Intent (InOut) :: XDONT |
185 |
! ! __________________________________________________________ |
186 |
! ! |
187 |
! ! |
188 |
! Call R_subsor (XDONT, 1, Size (XDONT)) |
189 |
! Call R_inssor (XDONT) |
190 |
! Return |
191 |
! End Subroutine R_refsor |
192 |
|
193 |
! Recursive Subroutine R_subsor (XDONT, IDEB1, IFIN1) |
194 |
! ! Sorts XDONT from IDEB1 to IFIN1 |
195 |
! ! __________________________________________________________ |
196 |
! Real, dimension (:), Intent (InOut) :: XDONT |
197 |
! Integer, Intent (In) :: IDEB1, IFIN1 |
198 |
! ! __________________________________________________________ |
199 |
! Integer, Parameter :: NINS = 16 ! Max for insertion sort |
200 |
! Integer :: ICRS, IDEB, IDCR, IFIN, IMIL |
201 |
! Real :: XPIV, XWRK |
202 |
! ! |
203 |
! IDEB = IDEB1 |
204 |
! IFIN = IFIN1 |
205 |
! ! |
206 |
! ! If we don't have enough values to make it worth while, we leave |
207 |
! ! them unsorted, and the final insertion sort will take care of them |
208 |
! ! |
209 |
! If ((IFIN - IDEB) > NINS) Then |
210 |
! IMIL = (IDEB+IFIN) / 2 |
211 |
! ! |
212 |
! ! One chooses a pivot, median of 1st, last, and middle values |
213 |
! ! |
214 |
! If (XDONT(IMIL) < XDONT(IDEB)) Then |
215 |
! XWRK = XDONT (IDEB) |
216 |
! XDONT (IDEB) = XDONT (IMIL) |
217 |
! XDONT (IMIL) = XWRK |
218 |
! End If |
219 |
! If (XDONT(IMIL) > XDONT(IFIN)) Then |
220 |
! XWRK = XDONT (IFIN) |
221 |
! XDONT (IFIN) = XDONT (IMIL) |
222 |
! XDONT (IMIL) = XWRK |
223 |
! If (XDONT(IMIL) < XDONT(IDEB)) Then |
224 |
! XWRK = XDONT (IDEB) |
225 |
! XDONT (IDEB) = XDONT (IMIL) |
226 |
! XDONT (IMIL) = XWRK |
227 |
! End If |
228 |
! End If |
229 |
! XPIV = XDONT (IMIL) |
230 |
! ! |
231 |
! ! One exchanges values to put those > pivot in the end and |
232 |
! ! those <= pivot at the beginning |
233 |
! ! |
234 |
! ICRS = IDEB |
235 |
! IDCR = IFIN |
236 |
! ECH2: Do |
237 |
! Do |
238 |
! ICRS = ICRS + 1 |
239 |
! If (ICRS >= IDCR) Then |
240 |
! ! |
241 |
! ! the first > pivot is IDCR |
242 |
! ! the last <= pivot is ICRS-1 |
243 |
! ! Note: If one arrives here on the first iteration, then |
244 |
! ! the pivot is the maximum of the set, the last value is equal |
245 |
! ! to it, and one can reduce by one the size of the set to process, |
246 |
! ! as if XDONT (IFIN) > XPIV |
247 |
! ! |
248 |
! Exit ECH2 |
249 |
! ! |
250 |
! End If |
251 |
! If (XDONT(ICRS) > XPIV) Exit |
252 |
! End Do |
253 |
! Do |
254 |
! If (XDONT(IDCR) <= XPIV) Exit |
255 |
! IDCR = IDCR - 1 |
256 |
! If (ICRS >= IDCR) Then |
257 |
! ! |
258 |
! ! The last value < pivot is always ICRS-1 |
259 |
! ! |
260 |
! Exit ECH2 |
261 |
! End If |
262 |
! End Do |
263 |
! ! |
264 |
! XWRK = XDONT (IDCR) |
265 |
! XDONT (IDCR) = XDONT (ICRS) |
266 |
! XDONT (ICRS) = XWRK |
267 |
! End Do ECH2 |
268 |
! ! |
269 |
! ! One now sorts each of the two sub-intervals |
270 |
! ! |
271 |
! Call R_subsor (XDONT, IDEB1, ICRS-1) |
272 |
! Call R_subsor (XDONT, IDCR, IFIN1) |
273 |
! End If |
274 |
! Return |
275 |
! End Subroutine R_subsor |
276 |
! Subroutine R_inssor (XDONT) |
277 |
! ! Sorts XDONT into increasing order (Insertion sort) |
278 |
! ! __________________________________________________________ |
279 |
! Real, dimension (:), Intent (InOut) :: XDONT |
280 |
! ! __________________________________________________________ |
281 |
! Integer :: ICRS, IDCR |
282 |
! Real :: XWRK |
283 |
! ! |
284 |
! Do ICRS = 2, Size (XDONT) |
285 |
! XWRK = XDONT (ICRS) |
286 |
! If (XWRK >= XDONT(ICRS-1)) Cycle |
287 |
! XDONT (ICRS) = XDONT (ICRS-1) |
288 |
! Do IDCR = ICRS - 2, 1, - 1 |
289 |
! If (XWRK >= XDONT(IDCR)) Exit |
290 |
! XDONT (IDCR+1) = XDONT (IDCR) |
291 |
! End Do |
292 |
! XDONT (IDCR+1) = XWRK |
293 |
! End Do |
294 |
! ! |
295 |
! Return |
296 |
! ! |
297 |
! End Subroutine R_inssor |
298 |
! ! |
299 |
! Subroutine I_refsor (XDONT) |
300 |
! ! Sorts XDONT into ascending order - Quicksort |
301 |
! ! __________________________________________________________ |
302 |
! ! Quicksort chooses a "pivot" in the set, and explores the |
303 |
! ! array from both ends, looking for a value > pivot with the |
304 |
! ! increasing index, for a value <= pivot with the decreasing |
305 |
! ! index, and swapping them when it has found one of each. |
306 |
! ! The array is then subdivided in 2 ([3]) subsets: |
307 |
! ! { values <= pivot} {pivot} {values > pivot} |
308 |
! ! One then call recursively the program to sort each subset. |
309 |
! ! When the size of the subarray is small enough, one uses an |
310 |
! ! insertion sort that is faster for very small sets. |
311 |
! ! Michel Olagnon - Apr. 2000 |
312 |
! ! __________________________________________________________ |
313 |
! ! __________________________________________________________ |
314 |
! Integer, Dimension (:), Intent (InOut) :: XDONT |
315 |
! ! __________________________________________________________ |
316 |
! ! |
317 |
! ! |
318 |
! Call I_subsor (XDONT, 1, Size (XDONT)) |
319 |
! Call I_inssor (XDONT) |
320 |
! Return |
321 |
! End Subroutine I_refsor |
322 |
! Recursive Subroutine I_subsor (XDONT, IDEB1, IFIN1) |
323 |
! ! Sorts XDONT from IDEB1 to IFIN1 |
324 |
! ! __________________________________________________________ |
325 |
! Integer, dimension (:), Intent (InOut) :: XDONT |
326 |
! Integer, Intent (In) :: IDEB1, IFIN1 |
327 |
! ! __________________________________________________________ |
328 |
! Integer, Parameter :: NINS = 16 ! Max for insertion sort |
329 |
! Integer :: ICRS, IDEB, IDCR, IFIN, IMIL |
330 |
! Integer :: XPIV, XWRK |
331 |
! ! |
332 |
! IDEB = IDEB1 |
333 |
! IFIN = IFIN1 |
334 |
! ! |
335 |
! ! If we don't have enough values to make it worth while, we leave |
336 |
! ! them unsorted, and the final insertion sort will take care of them |
337 |
! ! |
338 |
! If ((IFIN - IDEB) > NINS) Then |
339 |
! IMIL = (IDEB+IFIN) / 2 |
340 |
! ! |
341 |
! ! One chooses a pivot, median of 1st, last, and middle values |
342 |
! ! |
343 |
! If (XDONT(IMIL) < XDONT(IDEB)) Then |
344 |
! XWRK = XDONT (IDEB) |
345 |
! XDONT (IDEB) = XDONT (IMIL) |
346 |
! XDONT (IMIL) = XWRK |
347 |
! End If |
348 |
! If (XDONT(IMIL) > XDONT(IFIN)) Then |
349 |
! XWRK = XDONT (IFIN) |
350 |
! XDONT (IFIN) = XDONT (IMIL) |
351 |
! XDONT (IMIL) = XWRK |
352 |
! If (XDONT(IMIL) < XDONT(IDEB)) Then |
353 |
! XWRK = XDONT (IDEB) |
354 |
! XDONT (IDEB) = XDONT (IMIL) |
355 |
! XDONT (IMIL) = XWRK |
356 |
! End If |
357 |
! End If |
358 |
! XPIV = XDONT (IMIL) |
359 |
! ! |
360 |
! ! One exchanges values to put those > pivot in the end and |
361 |
! ! those <= pivot at the beginning |
362 |
! ! |
363 |
! ICRS = IDEB |
364 |
! IDCR = IFIN |
365 |
! ECH2: Do |
366 |
! Do |
367 |
! ICRS = ICRS + 1 |
368 |
! If (ICRS >= IDCR) Then |
369 |
! ! |
370 |
! ! the first > pivot is IDCR |
371 |
! ! the last <= pivot is ICRS-1 |
372 |
! ! Note: If one arrives here on the first iteration, then |
373 |
! ! the pivot is the maximum of the set, the last value is equal |
374 |
! ! to it, and one can reduce by one the size of the set to process, |
375 |
! ! as if XDONT (IFIN) > XPIV |
376 |
! ! |
377 |
! Exit ECH2 |
378 |
! ! |
379 |
! End If |
380 |
! If (XDONT(ICRS) > XPIV) Exit |
381 |
! End Do |
382 |
! Do |
383 |
! If (XDONT(IDCR) <= XPIV) Exit |
384 |
! IDCR = IDCR - 1 |
385 |
! If (ICRS >= IDCR) Then |
386 |
! ! |
387 |
! ! The last value < pivot is always ICRS-1 |
388 |
! ! |
389 |
! Exit ECH2 |
390 |
! End If |
391 |
! End Do |
392 |
! ! |
393 |
! XWRK = XDONT (IDCR) |
394 |
! XDONT (IDCR) = XDONT (ICRS) |
395 |
! XDONT (ICRS) = XWRK |
396 |
! End Do ECH2 |
397 |
! ! |
398 |
! ! One now sorts each of the two sub-intervals |
399 |
! ! |
400 |
! Call I_subsor (XDONT, IDEB1, ICRS-1) |
401 |
! Call I_subsor (XDONT, IDCR, IFIN1) |
402 |
! End If |
403 |
! Return |
404 |
! End Subroutine I_subsor |
405 |
! Subroutine I_inssor (XDONT) |
406 |
! ! Sorts XDONT into increasing order (Insertion sort) |
407 |
! ! __________________________________________________________ |
408 |
! Integer, dimension (:), Intent (InOut) :: XDONT |
409 |
! ! __________________________________________________________ |
410 |
! Integer :: ICRS, IDCR |
411 |
! Integer :: XWRK |
412 |
! ! |
413 |
! Do ICRS = 2, Size (XDONT) |
414 |
! XWRK = XDONT (ICRS) |
415 |
! If (XWRK >= XDONT(ICRS-1)) Cycle |
416 |
! XDONT (ICRS) = XDONT (ICRS-1) |
417 |
! Do IDCR = ICRS - 2, 1, - 1 |
418 |
! If (XWRK >= XDONT(IDCR)) Exit |
419 |
! XDONT (IDCR+1) = XDONT (IDCR) |
420 |
! End Do |
421 |
! XDONT (IDCR+1) = XWRK |
422 |
! End Do |
423 |
! ! |
424 |
! Return |
425 |
! ! |
426 |
! End Subroutine I_inssor |
427 |
! ! |
428 |
! end module m_refsor |