11573Srgrimes/*-
21573Srgrimes * Copyright (c) 1990, 1993
31573Srgrimes *	The Regents of the University of California.  All rights reserved.
41573Srgrimes *
51573Srgrimes * This code is derived from software contributed to Berkeley by
68870Srgrimes * Peter McIlroy and by Dan Bernstein at New York University,
71573Srgrimes *
81573Srgrimes * Redistribution and use in source and binary forms, with or without
91573Srgrimes * modification, are permitted provided that the following conditions
101573Srgrimes * are met:
111573Srgrimes * 1. Redistributions of source code must retain the above copyright
121573Srgrimes *    notice, this list of conditions and the following disclaimer.
131573Srgrimes * 2. Redistributions in binary form must reproduce the above copyright
141573Srgrimes *    notice, this list of conditions and the following disclaimer in the
151573Srgrimes *    documentation and/or other materials provided with the distribution.
16251672Semaste * 3. Neither the name of the University nor the names of its contributors
171573Srgrimes *    may be used to endorse or promote products derived from this software
181573Srgrimes *    without specific prior written permission.
191573Srgrimes *
201573Srgrimes * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
211573Srgrimes * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
221573Srgrimes * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
231573Srgrimes * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
241573Srgrimes * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
251573Srgrimes * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
261573Srgrimes * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
271573Srgrimes * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
281573Srgrimes * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
291573Srgrimes * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
301573Srgrimes * SUCH DAMAGE.
311573Srgrimes */
321573Srgrimes
331573Srgrimes#if defined(LIBC_SCCS) && !defined(lint)
3423662Speterstatic char sccsid[] = "@(#)radixsort.c	8.2 (Berkeley) 4/28/95";
351573Srgrimes#endif /* LIBC_SCCS and not lint */
3692889Sobrien#include <sys/cdefs.h>
3792889Sobrien__FBSDID("$FreeBSD$");
381573Srgrimes
391573Srgrimes/*
401573Srgrimes * Radixsort routines.
418870Srgrimes *
421573Srgrimes * Program r_sort_a() is unstable but uses O(logN) extra memory for a stack.
431573Srgrimes * Use radixsort(a, n, trace, endchar) for this case.
448870Srgrimes *
451573Srgrimes * For stable sorting (using N extra pointers) use sradixsort(), which calls
461573Srgrimes * r_sort_b().
478870Srgrimes *
481573Srgrimes * For a description of this code, see D. McIlroy, P. McIlroy, K. Bostic,
491573Srgrimes * "Engineering Radix Sort".
501573Srgrimes */
511573Srgrimes
521573Srgrimes#include <sys/types.h>
531573Srgrimes#include <stdlib.h>
541573Srgrimes#include <stddef.h>
551573Srgrimes#include <errno.h>
561573Srgrimes
571573Srgrimestypedef struct {
581573Srgrimes	const u_char **sa;
591573Srgrimes	int sn, si;
601573Srgrimes} stack;
611573Srgrimes
621573Srgrimesstatic inline void simplesort
6392905Sobrien(const u_char **, int, int, const u_char *, u_int);
6492905Sobrienstatic void r_sort_a(const u_char **, int, int, const u_char *, u_int);
6592941Sobrienstatic void r_sort_b(const u_char **, const u_char **, int, int,
6692941Sobrien    const u_char *, u_int);
671573Srgrimes
681573Srgrimes#define	THRESHOLD	20		/* Divert to simplesort(). */
691573Srgrimes#define	SIZE		512		/* Default stack size. */
701573Srgrimes
711573Srgrimes#define SETUP {								\
721573Srgrimes	if (tab == NULL) {						\
731573Srgrimes		tr = tr0;						\
741573Srgrimes		for (c = 0; c < endch; c++)				\
751573Srgrimes			tr0[c] = c + 1;					\
761573Srgrimes		tr0[c] = 0;						\
771573Srgrimes		for (c++; c < 256; c++)					\
781573Srgrimes			tr0[c] = c;					\
791573Srgrimes		endch = 0;						\
801573Srgrimes	} else {							\
811573Srgrimes		endch = tab[endch];					\
821573Srgrimes		tr = tab;						\
831573Srgrimes		if (endch != 0 && endch != 255) {			\
841573Srgrimes			errno = EINVAL;					\
851573Srgrimes			return (-1);					\
861573Srgrimes		}							\
871573Srgrimes	}								\
881573Srgrimes}
891573Srgrimes
901573Srgrimesint
911573Srgrimesradixsort(a, n, tab, endch)
921573Srgrimes	const u_char **a, *tab;
931573Srgrimes	int n;
941573Srgrimes	u_int endch;
951573Srgrimes{
961573Srgrimes	const u_char *tr;
971573Srgrimes	int c;
981573Srgrimes	u_char tr0[256];
991573Srgrimes
1001573Srgrimes	SETUP;
1011573Srgrimes	r_sort_a(a, n, 0, tr, endch);
1021573Srgrimes	return (0);
1031573Srgrimes}
1041573Srgrimes
1051573Srgrimesint
1061573Srgrimessradixsort(a, n, tab, endch)
1071573Srgrimes	const u_char **a, *tab;
1081573Srgrimes	int n;
1091573Srgrimes	u_int endch;
1101573Srgrimes{
1111573Srgrimes	const u_char *tr, **ta;
1121573Srgrimes	int c;
1131573Srgrimes	u_char tr0[256];
1141573Srgrimes
1151573Srgrimes	SETUP;
1161573Srgrimes	if (n < THRESHOLD)
1171573Srgrimes		simplesort(a, n, 0, tr, endch);
1181573Srgrimes	else {
1191573Srgrimes		if ((ta = malloc(n * sizeof(a))) == NULL)
1201573Srgrimes			return (-1);
1211573Srgrimes		r_sort_b(a, ta, n, 0, tr, endch);
1221573Srgrimes		free(ta);
1231573Srgrimes	}
1241573Srgrimes	return (0);
1251573Srgrimes}
1261573Srgrimes
1271573Srgrimes#define empty(s)	(s >= sp)
1281573Srgrimes#define pop(a, n, i)	a = (--sp)->sa, n = sp->sn, i = sp->si
1291573Srgrimes#define push(a, n, i)	sp->sa = a, sp->sn = n, (sp++)->si = i
1301573Srgrimes#define swap(a, b, t)	t = a, a = b, b = t
1311573Srgrimes
1321573Srgrimes/* Unstable, in-place sort. */
13323662Speterstatic void
1341573Srgrimesr_sort_a(a, n, i, tr, endch)
1351573Srgrimes	const u_char **a;
1361573Srgrimes	int n, i;
1371573Srgrimes	const u_char *tr;
1381573Srgrimes	u_int endch;
1391573Srgrimes{
1401573Srgrimes	static int count[256], nc, bmin;
14192889Sobrien	int c;
14292889Sobrien	const u_char **ak, *r;
1431573Srgrimes	stack s[SIZE], *sp, *sp0, *sp1, temp;
1441573Srgrimes	int *cp, bigc;
1451573Srgrimes	const u_char **an, *t, **aj, **top[256];
1461573Srgrimes
1471573Srgrimes	/* Set up stack. */
1481573Srgrimes	sp = s;
1491573Srgrimes	push(a, n, i);
1501573Srgrimes	while (!empty(s)) {
1511573Srgrimes		pop(a, n, i);
1521573Srgrimes		if (n < THRESHOLD) {
1531573Srgrimes			simplesort(a, n, i, tr, endch);
1541573Srgrimes			continue;
1551573Srgrimes		}
1561573Srgrimes		an = a + n;
1571573Srgrimes
1581573Srgrimes		/* Make character histogram. */
1591573Srgrimes		if (nc == 0) {
1601573Srgrimes			bmin = 255;	/* First occupied bin, excluding eos. */
1611573Srgrimes			for (ak = a; ak < an;) {
1621573Srgrimes				c = tr[(*ak++)[i]];
1631573Srgrimes				if (++count[c] == 1 && c != endch) {
1641573Srgrimes					if (c < bmin)
1651573Srgrimes						bmin = c;
1661573Srgrimes					nc++;
1671573Srgrimes				}
1681573Srgrimes			}
1691573Srgrimes			if (sp + nc > s + SIZE) {	/* Get more stack. */
1701573Srgrimes				r_sort_a(a, n, i, tr, endch);
1711573Srgrimes				continue;
1721573Srgrimes			}
1731573Srgrimes		}
1741573Srgrimes
1751573Srgrimes		/*
176122458Skientzle		 * Special case: if all strings have the same
177122458Skientzle		 * character at position i, move on to the next
178122458Skientzle		 * character.
179122458Skientzle		 */
180122458Skientzle		if (nc == 1 && count[bmin] == n) {
181122458Skientzle			push(a, n, i+1);
182122458Skientzle			nc = count[bmin] = 0;
183122458Skientzle			continue;
184122458Skientzle		}
185122458Skientzle
186122458Skientzle		/*
1871573Srgrimes		 * Set top[]; push incompletely sorted bins onto stack.
1881573Srgrimes		 * top[] = pointers to last out-of-place element in bins.
1891573Srgrimes		 * count[] = counts of elements in bins.
1901573Srgrimes		 * Before permuting: top[c-1] + count[c] = top[c];
1911573Srgrimes		 * during deal: top[c] counts down to top[c-1].
1921573Srgrimes		 */
1931573Srgrimes		sp0 = sp1 = sp;		/* Stack position of biggest bin. */
1941573Srgrimes		bigc = 2;		/* Size of biggest bin. */
1951573Srgrimes		if (endch == 0)		/* Special case: set top[eos]. */
1961573Srgrimes			top[0] = ak = a + count[0];
1971573Srgrimes		else {
1981573Srgrimes			ak = a;
1991573Srgrimes			top[255] = an;
2001573Srgrimes		}
2011573Srgrimes		for (cp = count + bmin; nc > 0; cp++) {
2021573Srgrimes			while (*cp == 0)	/* Find next non-empty pile. */
2031573Srgrimes				cp++;
2041573Srgrimes			if (*cp > 1) {
2051573Srgrimes				if (*cp > bigc) {
2061573Srgrimes					bigc = *cp;
2071573Srgrimes					sp1 = sp;
2081573Srgrimes				}
2091573Srgrimes				push(ak, *cp, i+1);
2101573Srgrimes			}
2111573Srgrimes			top[cp-count] = ak += *cp;
2121573Srgrimes			nc--;
2131573Srgrimes		}
2141573Srgrimes		swap(*sp0, *sp1, temp);	/* Play it safe -- biggest bin last. */
2151573Srgrimes
2161573Srgrimes		/*
2171573Srgrimes		 * Permute misplacements home.  Already home: everything
2181573Srgrimes		 * before aj, and in bin[c], items from top[c] on.
2191573Srgrimes		 * Inner loop:
2201573Srgrimes		 *	r = next element to put in place;
2211573Srgrimes		 *	ak = top[r[i]] = location to put the next element.
2221573Srgrimes		 *	aj = bottom of 1st disordered bin.
2231573Srgrimes		 * Outer loop:
2241573Srgrimes		 *	Once the 1st disordered bin is done, ie. aj >= ak,
2251573Srgrimes		 *	aj<-aj + count[c] connects the bins in a linked list;
2261573Srgrimes		 *	reset count[c].
2271573Srgrimes		 */
2281573Srgrimes		for (aj = a; aj < an;  *aj = r, aj += count[c], count[c] = 0)
2291573Srgrimes			for (r = *aj;  aj < (ak = --top[c = tr[r[i]]]);)
2301573Srgrimes				swap(*ak, r, t);
2311573Srgrimes	}
2321573Srgrimes}
2331573Srgrimes
2341573Srgrimes/* Stable sort, requiring additional memory. */
23523662Speterstatic void
2361573Srgrimesr_sort_b(a, ta, n, i, tr, endch)
2371573Srgrimes	const u_char **a, **ta;
2381573Srgrimes	int n, i;
2391573Srgrimes	const u_char *tr;
2401573Srgrimes	u_int endch;
2411573Srgrimes{
2421573Srgrimes	static int count[256], nc, bmin;
24392889Sobrien	int c;
24492889Sobrien	const u_char **ak, **ai;
2451573Srgrimes	stack s[512], *sp, *sp0, *sp1, temp;
2461573Srgrimes	const u_char **top[256];
2471573Srgrimes	int *cp, bigc;
2481573Srgrimes
2491573Srgrimes	sp = s;
2501573Srgrimes	push(a, n, i);
2511573Srgrimes	while (!empty(s)) {
2521573Srgrimes		pop(a, n, i);
2531573Srgrimes		if (n < THRESHOLD) {
2541573Srgrimes			simplesort(a, n, i, tr, endch);
2551573Srgrimes			continue;
2561573Srgrimes		}
2571573Srgrimes
2581573Srgrimes		if (nc == 0) {
2591573Srgrimes			bmin = 255;
2601573Srgrimes			for (ak = a + n; --ak >= a;) {
2611573Srgrimes				c = tr[(*ak)[i]];
2621573Srgrimes				if (++count[c] == 1 && c != endch) {
2631573Srgrimes					if (c < bmin)
2641573Srgrimes						bmin = c;
2651573Srgrimes					nc++;
2661573Srgrimes				}
2671573Srgrimes			}
2681573Srgrimes			if (sp + nc > s + SIZE) {
2691573Srgrimes				r_sort_b(a, ta, n, i, tr, endch);
2701573Srgrimes				continue;
2711573Srgrimes			}
2721573Srgrimes		}
2731573Srgrimes
2741573Srgrimes		sp0 = sp1 = sp;
2751573Srgrimes		bigc = 2;
2761573Srgrimes		if (endch == 0) {
2771573Srgrimes			top[0] = ak = a + count[0];
2781573Srgrimes			count[0] = 0;
2791573Srgrimes		} else {
2801573Srgrimes			ak = a;
2811573Srgrimes			top[255] = a + n;
2821573Srgrimes			count[255] = 0;
2831573Srgrimes		}
2841573Srgrimes		for (cp = count + bmin; nc > 0; cp++) {
2851573Srgrimes			while (*cp == 0)
2861573Srgrimes				cp++;
2871573Srgrimes			if ((c = *cp) > 1) {
2881573Srgrimes				if (c > bigc) {
2891573Srgrimes					bigc = c;
2901573Srgrimes					sp1 = sp;
2911573Srgrimes				}
2921573Srgrimes				push(ak, c, i+1);
2931573Srgrimes			}
2941573Srgrimes			top[cp-count] = ak += c;
2951573Srgrimes			*cp = 0;			/* Reset count[]. */
2961573Srgrimes			nc--;
2971573Srgrimes		}
2981573Srgrimes		swap(*sp0, *sp1, temp);
2991573Srgrimes
3001573Srgrimes		for (ak = ta + n, ai = a+n; ak > ta;)	/* Copy to temp. */
3011573Srgrimes			*--ak = *--ai;
3021573Srgrimes		for (ak = ta+n; --ak >= ta;)		/* Deal to piles. */
3031573Srgrimes			*--top[tr[(*ak)[i]]] = *ak;
3041573Srgrimes	}
3051573Srgrimes}
3068870Srgrimes
3071573Srgrimesstatic inline void
3081573Srgrimessimplesort(a, n, b, tr, endch)	/* insertion sort */
30992889Sobrien	const u_char **a;
3101573Srgrimes	int n, b;
31192889Sobrien	const u_char *tr;
3121573Srgrimes	u_int endch;
3131573Srgrimes{
31492889Sobrien	u_char ch;
3151573Srgrimes	const u_char  **ak, **ai, *s, *t;
3161573Srgrimes
3171573Srgrimes	for (ak = a+1; --n >= 1; ak++)
3181573Srgrimes		for (ai = ak; ai > a; ai--) {
3191573Srgrimes			for (s = ai[0] + b, t = ai[-1] + b;
3201573Srgrimes			    (ch = tr[*s]) != endch; s++, t++)
3211573Srgrimes				if (ch != tr[*t])
3221573Srgrimes					break;
3231573Srgrimes			if (ch >= tr[*t])
3241573Srgrimes				break;
3251573Srgrimes			swap(ai[0], ai[-1], s);
3261573Srgrimes		}
3271573Srgrimes}
328