Clang static analysis builds should use C runtime directly.
This is a little macro magic to use malloc() directly instead of SDL_malloc(),
etc, so static analysis tests that know about the C runtime can function
properly, and understand that we are dealing with heap allocations, etc.
This changed our static analysis report from 5 outstanding bugs to 30.
5x as many bugs were hidden by SDL_malloc() not being recognized as malloc()
by the static analyzer!
2 * (c) 1998 Gareth McCaughan
4 * This is a drop-in replacement for the C library's |qsort()| routine.
7 * - Median-of-three pivoting (and more)
8 * - Truncation and final polishing by a single insertion sort
9 * - Early truncation when no swaps needed in pivoting step
10 * - Explicit recursion, guaranteed not to overflow
11 * - A few little wrinkles stolen from the GNU |qsort()|.
12 * - separate code for non-aligned / aligned / word-size objects
14 * This code may be reproduced freely provided
15 * - this file is retained unaltered apart from minor
16 * changes for portability and efficiency
17 * - no changes are made to this comment
18 * - any changes that *are* made are clearly flagged
19 * - the _ID string below is altered by inserting, after
20 * the date, the string " altered" followed at your option
21 * by other material. (Exceptions: you may change the name
22 * of the exported routine without changing the ID string.
23 * You may change the values of the macros TRUNC_* and
24 * PIVOT_THRESHOLD without changing the ID string, provided
25 * they remain constants with TRUNC_nonaligned, TRUNC_aligned
26 * and TRUNC_words/WORD_BYTES between 8 and 24, and
27 * PIVOT_THRESHOLD between 32 and 200.)
29 * You may use it in anything you like; you may make money
30 * out of it; you may distribute it in object form or as
31 * part of an executable without including source code;
32 * you don't have to credit me. (But it would be nice if
35 * If you find problems with this code, or find ways of
36 * making it significantly faster, please let me know!
37 * My e-mail address, valid as of early 1998 and certainly
38 * OK for at least the next 18 months, is
39 * gjm11@dpmms.cam.ac.uk
42 * Gareth McCaughan Peterhouse Cambridge 1998
45 #if defined(__clang_analyzer__) && !defined(SDL_DISABLE_ANALYZE_MACROS)
46 #define SDL_DISABLE_ANALYZE_MACROS 1
49 #include "../SDL_internal.h"
56 #include "SDL_stdinc.h"
57 #include "SDL_assert.h"
59 #if defined(HAVE_QSORT)
61 SDL_qsort(void *base, size_t nmemb, size_t size, int (*compare) (const void *, const void *))
63 qsort(base, nmemb, size, compare);
70 #define assert(X) SDL_assert(X)
74 #define malloc SDL_malloc
82 #define memcpy SDL_memcpy
86 #define memmove SDL_memmove
90 #define qsort SDL_qsort
92 static const char _ID[] = "<qsort.c gjm 1.12 1998-03-19>";
94 /* How many bytes are there per word? (Must be a power of 2,
95 * and must in fact equal sizeof(int).)
97 #define WORD_BYTES sizeof(int)
99 /* How big does our stack need to be? Answer: one entry per
102 #define STACK_SIZE (8*sizeof(size_t))
104 /* Different situations have slightly different requirements,
105 * and we make life epsilon easier by using different truncation
106 * points for the three different cases.
107 * So far, I have tuned TRUNC_words and guessed that the same
108 * value might work well for the other two cases. Of course
109 * what works well on my machine might work badly on yours.
111 #define TRUNC_nonaligned 12
112 #define TRUNC_aligned 12
113 #define TRUNC_words 12*WORD_BYTES /* nb different meaning */
115 /* We use a simple pivoting algorithm for shortish sub-arrays
116 * and a more complicated one for larger ones. The threshold
117 * is PIVOT_THRESHOLD.
119 #define PIVOT_THRESHOLD 40
126 #define pushLeft {stack[stacktop].first=ffirst;stack[stacktop++].last=last;}
127 #define pushRight {stack[stacktop].first=first;stack[stacktop++].last=llast;}
128 #define doLeft {first=ffirst;llast=last;continue;}
129 #define doRight {ffirst=first;last=llast;continue;}
130 #define pop {if (--stacktop<0) break;\
131 first=ffirst=stack[stacktop].first;\
132 last=llast=stack[stacktop].last;\
135 /* Some comments on the implementation.
136 * 1. When we finish partitioning the array into "low"
137 * and "high", we forget entirely about short subarrays,
138 * because they'll be done later by insertion sort.
139 * Doing lots of little insertion sorts might be a win
140 * on large datasets for locality-of-reference reasons,
141 * but it makes the code much nastier and increases
142 * bookkeeping overhead.
143 * 2. We always save the shorter and get to work on the
144 * longer. This guarantees that every time we push
145 * an item onto the stack its size is <= 1/2 of that
146 * of its parent; so the stack can't need more than
147 * log_2(max-array-size) entries.
148 * 3. We choose a pivot by looking at the first, last
149 * and middle elements. We arrange them into order
150 * because it's easy to do that in conjunction with
151 * choosing the pivot, and it makes things a little
152 * easier in the partitioning step. Anyway, the pivot
153 * is the middle of these three. It's still possible
154 * to construct datasets where the algorithm takes
155 * time of order n^2, but it simply never happens in
157 * 3' Newsflash: On further investigation I find that
158 * it's easy to construct datasets where median-of-3
159 * simply isn't good enough. So on large-ish subarrays
160 * we do a more sophisticated pivoting: we take three
161 * sets of 3 elements, find their medians, and then
162 * take the median of those.
163 * 4. We copy the pivot element to a separate place
164 * because that way we can always do our comparisons
165 * directly against a pointer to that separate place,
166 * and don't have to wonder "did we move the pivot
167 * element?". This makes the inner loop better.
168 * 5. It's possible to make the pivoting even more
169 * reliable by looking at more candidates when n
170 * is larger. (Taking this to its logical conclusion
171 * results in a variant of quicksort that doesn't
172 * have that n^2 worst case.) However, the overhead
173 * from the extra bookkeeping means that it's just
175 * 6. This is pretty clean and portable code. Here are
176 * all the potential portability pitfalls and problems
178 * - In one place (the insertion sort) I construct
179 * a pointer that points just past the end of the
180 * supplied array, and assume that (a) it won't
181 * compare equal to any pointer within the array,
182 * and (b) it will compare equal to a pointer
183 * obtained by stepping off the end of the array.
184 * These might fail on some segmented architectures.
185 * - I assume that there are 8 bits in a |char| when
186 * computing the size of stack needed. This would
187 * fail on machines with 9-bit or 16-bit bytes.
188 * - I assume that if |((int)base&(sizeof(int)-1))==0|
189 * and |(size&(sizeof(int)-1))==0| then it's safe to
190 * get at array elements via |int*|s, and that if
191 * actually |size==sizeof(int)| as well then it's
192 * safe to treat the elements as |int|s. This might
193 * fail on systems that convert pointers to integers
194 * in non-standard ways.
195 * - I assume that |8*sizeof(size_t)<=INT_MAX|. This
196 * would be false on a machine with 8-bit |char|s,
197 * 16-bit |int|s and 4096-bit |size_t|s. :-)
200 /* The recursion logic is the same in each case: */
201 #define Recurse(Trunc) \
202 { size_t l=last-ffirst,r=llast-first; \
204 if (r>=Trunc) doRight \
207 else if (l<=r) { pushLeft; doRight } \
208 else if (r>=Trunc) { pushRight; doLeft }\
212 /* and so is the pivoting logic: */
213 #define Pivot(swapper,sz) \
214 if ((size_t)(last-first)>PIVOT_THRESHOLD*sz) mid=pivot_big(first,mid,last,sz,compare);\
216 if (compare(first,mid)<0) { \
217 if (compare(mid,last)>0) { \
219 if (compare(first,mid)>0) swapper(first,mid);\
223 if (compare(mid,last)>0) swapper(first,last)\
225 swapper(first,mid); \
226 if (compare(mid,last)>0) swapper(mid,last);\
229 first+=sz; last-=sz; \
236 /* and so is the partitioning logic: */
237 #define Partition(swapper,sz) { \
240 while (compare(first,pivot)<0) first+=sz; \
241 while (compare(pivot,last)<0) last-=sz; \
243 swapper(first,last); swapped=1; \
244 first+=sz; last-=sz; } \
245 else if (first==last) { first+=sz; last-=sz; break; }\
246 } while (first<=last); \
250 /* and so is the pre-insertion-sort operation of putting
251 * the smallest element into place as a sentinel.
252 * Doing this makes the inner loop nicer. I got this
253 * idea from the GNU implementation of qsort().
255 #define PreInsertion(swapper,limit,sz) \
257 last=first + (nmemb>limit ? limit : nmemb-1)*sz;\
258 while (last!=base) { \
259 if (compare(first,last)>0) first=last; \
261 if (first!=base) swapper(first,(char*)base);
263 /* and so is the insertion sort, in the first two cases: */
264 #define Insertion(swapper) \
265 last=((char*)base)+nmemb*size; \
266 for (first=((char*)base)+size;first!=last;first+=size) { \
268 /* Find the right place for |first|. \
269 * My apologies for var reuse. */ \
270 for (test=first-size;compare(test,first)>0;test-=size) ; \
273 /* Shift everything in [test,first) \
274 * up by one, and place |first| \
275 * where |test| is. */ \
276 memcpy(pivot,first,size); \
277 memmove(test+size,test,first-test); \
278 memcpy(test,pivot,size); \
282 #define SWAP_nonaligned(a,b) { \
283 register char *aa=(a),*bb=(b); \
284 register size_t sz=size; \
285 do { register char t=*aa; *aa++=*bb; *bb++=t; } while (--sz); }
287 #define SWAP_aligned(a,b) { \
288 register int *aa=(int*)(a),*bb=(int*)(b); \
289 register size_t sz=size; \
290 do { register int t=*aa;*aa++=*bb; *bb++=t; } while (sz-=WORD_BYTES); }
292 #define SWAP_words(a,b) { \
293 register int t=*((int*)a); *((int*)a)=*((int*)b); *((int*)b)=t; }
295 /* ---------------------------------------------------------------------- */
298 pivot_big(char *first, char *mid, char *last, size_t size,
299 int compare(const void *, const void *))
301 size_t d = (((last - first) / size) >> 3) * size;
304 char *a = first, *b = first + d, *c = first + 2 * d;
306 fprintf(stderr, "< %d %d %d\n", *(int *) a, *(int *) b, *(int *) c);
308 m1 = compare(a, b) < 0 ?
309 (compare(b, c) < 0 ? b : (compare(a, c) < 0 ? c : a))
310 : (compare(a, c) < 0 ? a : (compare(b, c) < 0 ? c : b));
313 char *a = mid - d, *b = mid, *c = mid + d;
315 fprintf(stderr, ". %d %d %d\n", *(int *) a, *(int *) b, *(int *) c);
317 m2 = compare(a, b) < 0 ?
318 (compare(b, c) < 0 ? b : (compare(a, c) < 0 ? c : a))
319 : (compare(a, c) < 0 ? a : (compare(b, c) < 0 ? c : b));
322 char *a = last - 2 * d, *b = last - d, *c = last;
324 fprintf(stderr, "> %d %d %d\n", *(int *) a, *(int *) b, *(int *) c);
326 m3 = compare(a, b) < 0 ?
327 (compare(b, c) < 0 ? b : (compare(a, c) < 0 ? c : a))
328 : (compare(a, c) < 0 ? a : (compare(b, c) < 0 ? c : b));
331 fprintf(stderr, "-> %d %d %d\n", *(int *) m1, *(int *) m2, *(int *) m3);
333 return compare(m1, m2) < 0 ?
334 (compare(m2, m3) < 0 ? m2 : (compare(m1, m3) < 0 ? m3 : m1))
335 : (compare(m1, m3) < 0 ? m1 : (compare(m2, m3) < 0 ? m3 : m2));
338 /* ---------------------------------------------------------------------- */
341 qsort_nonaligned(void *base, size_t nmemb, size_t size,
342 int (*compare) (const void *, const void *))
345 stack_entry stack[STACK_SIZE];
348 char *pivot = malloc(size);
349 size_t trunc = TRUNC_nonaligned * size;
352 first = (char *) base;
353 last = first + (nmemb - 1) * size;
355 if ((size_t) (last - first) > trunc) {
356 char *ffirst = first, *llast = last;
360 char *mid = first + size * ((last - first) / size >> 1);
361 Pivot(SWAP_nonaligned, size);
362 memcpy(pivot, mid, size);
365 Partition(SWAP_nonaligned, size);
366 /* Prepare to recurse/iterate. */
369 PreInsertion(SWAP_nonaligned, TRUNC_nonaligned, size);
370 Insertion(SWAP_nonaligned);
375 qsort_aligned(void *base, size_t nmemb, size_t size,
376 int (*compare) (const void *, const void *))
379 stack_entry stack[STACK_SIZE];
382 char *pivot = malloc(size);
383 size_t trunc = TRUNC_aligned * size;
386 first = (char *) base;
387 last = first + (nmemb - 1) * size;
389 if ((size_t) (last - first) > trunc) {
390 char *ffirst = first, *llast = last;
394 char *mid = first + size * ((last - first) / size >> 1);
395 Pivot(SWAP_aligned, size);
396 memcpy(pivot, mid, size);
399 Partition(SWAP_aligned, size);
400 /* Prepare to recurse/iterate. */
403 PreInsertion(SWAP_aligned, TRUNC_aligned, size);
404 Insertion(SWAP_aligned);
409 qsort_words(void *base, size_t nmemb,
410 int (*compare) (const void *, const void *))
413 stack_entry stack[STACK_SIZE];
416 char *pivot = malloc(WORD_BYTES);
419 first = (char *) base;
420 last = first + (nmemb - 1) * WORD_BYTES;
422 if (last - first > TRUNC_words) {
423 char *ffirst = first, *llast = last;
426 fprintf(stderr, "Doing %d:%d: ",
427 (first - (char *) base) / WORD_BYTES,
428 (last - (char *) base) / WORD_BYTES);
433 first + WORD_BYTES * ((last - first) / (2 * WORD_BYTES));
434 Pivot(SWAP_words, WORD_BYTES);
435 *(int *) pivot = *(int *) mid;
438 fprintf(stderr, "pivot=%d\n", *(int *) pivot);
441 Partition(SWAP_words, WORD_BYTES);
442 /* Prepare to recurse/iterate. */
443 Recurse(TRUNC_words)}
445 PreInsertion(SWAP_words, (TRUNC_words / WORD_BYTES), WORD_BYTES);
446 /* Now do insertion sort. */
447 last = ((char *) base) + nmemb * WORD_BYTES;
448 for (first = ((char *) base) + WORD_BYTES; first != last;
449 first += WORD_BYTES) {
450 /* Find the right place for |first|. My apologies for var reuse */
451 int *pl = (int *) (first - WORD_BYTES), *pr = (int *) first;
452 *(int *) pivot = *(int *) first;
453 for (; compare(pl, pivot) > 0; pr = pl, --pl) {
456 if (pr != (int *) first)
457 *pr = *(int *) pivot;
462 /* ---------------------------------------------------------------------- */
465 qsort(void *base, size_t nmemb, size_t size,
466 int (*compare) (const void *, const void *))
471 if (((uintptr_t) base | size) & (WORD_BYTES - 1))
472 qsort_nonaligned(base, nmemb, size, compare);
473 else if (size != WORD_BYTES)
474 qsort_aligned(base, nmemb, size, compare);
476 qsort_words(base, nmemb, compare);
479 #endif /* !SDL_qsort */
481 /* vi: set ts=4 sw=4 expandtab: */