]> git.saurik.com Git - apple/libc.git/blob - stdlib/radixsort.c
Libc-262.3.2.tar.gz
[apple/libc.git] / stdlib / radixsort.c
1 /*
2 * Copyright (c) 1999 Apple Computer, Inc. All rights reserved.
3 *
4 * @APPLE_LICENSE_HEADER_START@
5 *
6 * Copyright (c) 1999-2003 Apple Computer, Inc. All Rights Reserved.
7 *
8 * This file contains Original Code and/or Modifications of Original Code
9 * as defined in and that are subject to the Apple Public Source License
10 * Version 2.0 (the 'License'). You may not use this file except in
11 * compliance with the License. Please obtain a copy of the License at
12 * http://www.opensource.apple.com/apsl/ and read it before using this
13 * file.
14 *
15 * The Original Code and all software distributed under the License are
16 * distributed on an 'AS IS' basis, WITHOUT WARRANTY OF ANY KIND, EITHER
17 * EXPRESS OR IMPLIED, AND APPLE HEREBY DISCLAIMS ALL SUCH WARRANTIES,
18 * INCLUDING WITHOUT LIMITATION, ANY WARRANTIES OF MERCHANTABILITY,
19 * FITNESS FOR A PARTICULAR PURPOSE, QUIET ENJOYMENT OR NON-INFRINGEMENT.
20 * Please see the License for the specific language governing rights and
21 * limitations under the License.
22 *
23 * @APPLE_LICENSE_HEADER_END@
24 */
25 /*
26 * Copyright (c) 1990, 1993
27 * The Regents of the University of California. All rights reserved.
28 *
29 * This code is derived from software contributed to Berkeley by
30 * Peter McIlroy and by Dan Bernstein at New York University,
31 *
32 * Redistribution and use in source and binary forms, with or without
33 * modification, are permitted provided that the following conditions
34 * are met:
35 * 1. Redistributions of source code must retain the above copyright
36 * notice, this list of conditions and the following disclaimer.
37 * 2. Redistributions in binary form must reproduce the above copyright
38 * notice, this list of conditions and the following disclaimer in the
39 * documentation and/or other materials provided with the distribution.
40 * 3. All advertising materials mentioning features or use of this software
41 * must display the following acknowledgement:
42 * This product includes software developed by the University of
43 * California, Berkeley and its contributors.
44 * 4. Neither the name of the University nor the names of its contributors
45 * may be used to endorse or promote products derived from this software
46 * without specific prior written permission.
47 *
48 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
49 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
50 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
51 * ARE DISCLAIMED. IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
52 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
53 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
54 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
55 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
56 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
57 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
58 * SUCH DAMAGE.
59 */
60
61
62 /*
63 * Radixsort routines.
64 *
65 * Program r_sort_a() is unstable but uses O(logN) extra memory for a stack.
66 * Use radixsort(a, n, trace, endchar) for this case.
67 *
68 * For stable sorting (using N extra pointers) use sradixsort(), which calls
69 * r_sort_b().
70 *
71 * For a description of this code, see D. McIlroy, P. McIlroy, K. Bostic,
72 * "Engineering Radix Sort".
73 */
74
75 #include <sys/types.h>
76 #include <stdlib.h>
77 #include <stddef.h>
78 #include <errno.h>
79
80 typedef struct {
81 const u_char **sa;
82 int sn, si;
83 } stack;
84
85 static inline void simplesort
86 __P((const u_char **, int, int, const u_char *, u_int));
87 static void r_sort_a __P((const u_char **, int, int, const u_char *, u_int));
88 static void r_sort_b __P((const u_char **,
89 const u_char **, int, int, const u_char *, u_int));
90
91 #define THRESHOLD 20 /* Divert to simplesort(). */
92 #define SIZE 512 /* Default stack size. */
93
94 #define SETUP { \
95 if (tab == NULL) { \
96 tr = tr0; \
97 for (c = 0; c < endch; c++) \
98 tr0[c] = c + 1; \
99 tr0[c] = 0; \
100 for (c++; c < 256; c++) \
101 tr0[c] = c; \
102 endch = 0; \
103 } else { \
104 endch = tab[endch]; \
105 tr = tab; \
106 if (endch != 0 && endch != 255) { \
107 errno = EINVAL; \
108 return (-1); \
109 } \
110 } \
111 }
112
113 int
114 radixsort(a, n, tab, endch)
115 const u_char **a, *tab;
116 int n;
117 u_int endch;
118 {
119 const u_char *tr;
120 int c;
121 u_char tr0[256];
122
123 SETUP;
124 r_sort_a(a, n, 0, tr, endch);
125 return (0);
126 }
127
128 int
129 sradixsort(a, n, tab, endch)
130 const u_char **a, *tab;
131 int n;
132 u_int endch;
133 {
134 const u_char *tr, **ta;
135 int c;
136 u_char tr0[256];
137
138 SETUP;
139 if (n < THRESHOLD)
140 simplesort(a, n, 0, tr, endch);
141 else {
142 if ((ta = malloc(n * sizeof(a))) == NULL)
143 return (-1);
144 r_sort_b(a, ta, n, 0, tr, endch);
145 free(ta);
146 }
147 return (0);
148 }
149
150 #define empty(s) (s >= sp)
151 #define pop(a, n, i) a = (--sp)->sa, n = sp->sn, i = sp->si
152 #define push(a, n, i) sp->sa = a, sp->sn = n, (sp++)->si = i
153 #define swap(a, b, t) t = a, a = b, b = t
154
155 /* Unstable, in-place sort. */
156 static void
157 r_sort_a(a, n, i, tr, endch)
158 const u_char **a;
159 int n, i;
160 const u_char *tr;
161 u_int endch;
162 {
163 static int *count = NULL, nc, bmin;
164 register int c;
165 register const u_char **ak, *r;
166 stack s[SIZE], *sp, *sp0, *sp1, temp;
167 int *cp, bigc;
168 const u_char **an, *t, **aj, **top[256];
169
170 if( count == NULL ) {
171 count = malloc(256*sizeof(int));
172 if( count == NULL )
173 return;
174 }
175
176 /* Set up stack. */
177 sp = s;
178 push(a, n, i);
179 while (!empty(s)) {
180 pop(a, n, i);
181 if (n < THRESHOLD) {
182 simplesort(a, n, i, tr, endch);
183 continue;
184 }
185 an = a + n;
186
187 /* Make character histogram. */
188 if (nc == 0) {
189 bmin = 255; /* First occupied bin, excluding eos. */
190 for (ak = a; ak < an;) {
191 c = tr[(*ak++)[i]];
192 if (++count[c] == 1 && c != endch) {
193 if (c < bmin)
194 bmin = c;
195 nc++;
196 }
197 }
198 if (sp + nc > s + SIZE) { /* Get more stack. */
199 r_sort_a(a, n, i, tr, endch);
200 continue;
201 }
202 }
203
204 /*
205 * Set top[]; push incompletely sorted bins onto stack.
206 * top[] = pointers to last out-of-place element in bins.
207 * count[] = counts of elements in bins.
208 * Before permuting: top[c-1] + count[c] = top[c];
209 * during deal: top[c] counts down to top[c-1].
210 */
211 sp0 = sp1 = sp; /* Stack position of biggest bin. */
212 bigc = 2; /* Size of biggest bin. */
213 if (endch == 0) /* Special case: set top[eos]. */
214 top[0] = ak = a + count[0];
215 else {
216 ak = a;
217 top[255] = an;
218 }
219 for (cp = count + bmin; nc > 0; cp++) {
220 while (*cp == 0) /* Find next non-empty pile. */
221 cp++;
222 if (*cp > 1) {
223 if (*cp > bigc) {
224 bigc = *cp;
225 sp1 = sp;
226 }
227 push(ak, *cp, i+1);
228 }
229 top[cp-count] = ak += *cp;
230 nc--;
231 }
232 swap(*sp0, *sp1, temp); /* Play it safe -- biggest bin last. */
233
234 /*
235 * Permute misplacements home. Already home: everything
236 * before aj, and in bin[c], items from top[c] on.
237 * Inner loop:
238 * r = next element to put in place;
239 * ak = top[r[i]] = location to put the next element.
240 * aj = bottom of 1st disordered bin.
241 * Outer loop:
242 * Once the 1st disordered bin is done, ie. aj >= ak,
243 * aj<-aj + count[c] connects the bins in a linked list;
244 * reset count[c].
245 */
246 for (aj = a; aj < an; *aj = r, aj += count[c], count[c] = 0)
247 for (r = *aj; aj < (ak = --top[c = tr[r[i]]]);)
248 swap(*ak, r, t);
249 }
250 }
251
252 /* Stable sort, requiring additional memory. */
253 static void
254 r_sort_b(a, ta, n, i, tr, endch)
255 const u_char **a, **ta;
256 int n, i;
257 const u_char *tr;
258 u_int endch;
259 {
260 static int *count = NULL, nc, bmin;
261 register int c;
262 register const u_char **ak, **ai;
263 stack s[512], *sp, *sp0, *sp1, temp;
264 const u_char **top[256];
265 int *cp, bigc;
266
267 if( count == NULL ) {
268 count = malloc(256*sizeof(int));
269 if( count == NULL )
270 return;
271 }
272
273 sp = s;
274 push(a, n, i);
275 while (!empty(s)) {
276 pop(a, n, i);
277 if (n < THRESHOLD) {
278 simplesort(a, n, i, tr, endch);
279 continue;
280 }
281
282 if (nc == 0) {
283 bmin = 255;
284 for (ak = a + n; --ak >= a;) {
285 c = tr[(*ak)[i]];
286 if (++count[c] == 1 && c != endch) {
287 if (c < bmin)
288 bmin = c;
289 nc++;
290 }
291 }
292 if (sp + nc > s + SIZE) {
293 r_sort_b(a, ta, n, i, tr, endch);
294 continue;
295 }
296 }
297
298 sp0 = sp1 = sp;
299 bigc = 2;
300 if (endch == 0) {
301 top[0] = ak = a + count[0];
302 count[0] = 0;
303 } else {
304 ak = a;
305 top[255] = a + n;
306 count[255] = 0;
307 }
308 for (cp = count + bmin; nc > 0; cp++) {
309 while (*cp == 0)
310 cp++;
311 if ((c = *cp) > 1) {
312 if (c > bigc) {
313 bigc = c;
314 sp1 = sp;
315 }
316 push(ak, c, i+1);
317 }
318 top[cp-count] = ak += c;
319 *cp = 0; /* Reset count[]. */
320 nc--;
321 }
322 swap(*sp0, *sp1, temp);
323
324 for (ak = ta + n, ai = a+n; ak > ta;) /* Copy to temp. */
325 *--ak = *--ai;
326 for (ak = ta+n; --ak >= ta;) /* Deal to piles. */
327 *--top[tr[(*ak)[i]]] = *ak;
328 }
329 }
330
331 static inline void
332 simplesort(a, n, b, tr, endch) /* insertion sort */
333 register const u_char **a;
334 int n, b;
335 register const u_char *tr;
336 u_int endch;
337 {
338 register u_char ch;
339 const u_char **ak, **ai, *s, *t;
340
341 for (ak = a+1; --n >= 1; ak++)
342 for (ai = ak; ai > a; ai--) {
343 for (s = ai[0] + b, t = ai[-1] + b;
344 (ch = tr[*s]) != endch; s++, t++)
345 if (ch != tr[*t])
346 break;
347 if (ch >= tr[*t])
348 break;
349 swap(ai[0], ai[-1], s);
350 }
351 }