Fix combination-args-flow-cleanly-p.
[sbcl.git] / tests / test-util.lisp
blobaac7a23fb4fed3ea40f500280b8fa6d7b9769a10
1 (defpackage :test-util
2 (:use :cl :sb-ext)
3 (:export #:with-test #:report-test-status #:*failures*
4 #:really-invoke-debugger
5 #:*break-on-failure* #:*break-on-expected-failure*
7 ;; thread tools
8 #:make-kill-thread #:make-join-thread
10 ;; MAP-OPTIMIZATION-*
11 #:map-optimization-quality-combinations
12 #:map-optimize-declarations
14 ;; CHECKED-COMPILE and friends
15 #:checked-compile #:checked-compile-and-assert
16 #:checked-compile-capturing-source-paths
17 #:checked-compile-condition-source-paths
19 #:runtime #:split-string #:shuffle))
21 (in-package :test-util)
23 (defvar *test-count* 0)
24 (defvar *test-file* nil)
25 (defvar *failures* nil)
26 (defvar *break-on-failure* nil)
27 (defvar *break-on-expected-failure* nil)
29 (defvar *threads-to-kill*)
30 (defvar *threads-to-join*)
32 (eval-when (:compile-toplevel :load-toplevel :execute)
33 (require :sb-posix))
35 (sb-posix:putenv (format nil "SBCL_MACHINE_TYPE=~A" (machine-type)))
36 (sb-posix:putenv (format nil "SBCL_SOFTWARE_TYPE=~A" (software-type)))
38 #+sb-thread
39 (defun make-kill-thread (&rest args)
40 (let ((thread (apply #'sb-thread:make-thread args)))
41 #-win32 ;; poor thread interruption on safepoints
42 (when (boundp '*threads-to-kill*)
43 (push thread *threads-to-kill*))
44 thread))
46 #+sb-thread
47 (defun make-join-thread (&rest args)
48 (let ((thread (apply #'sb-thread:make-thread args)))
49 (when (boundp '*threads-to-join*)
50 (push thread *threads-to-join*))
51 thread))
53 (defun log-msg (&rest args)
54 (apply #'format *trace-output* "~&::: ~@?~%" args)
55 (force-output *trace-output*))
57 (defun log-msg/non-pretty (&rest args)
58 (let ((*print-pretty* nil))
59 (apply #'log-msg args)))
61 (defun run-test (test-function name fails-on)
62 (start-test)
63 (let (#+sb-thread (threads (sb-thread:list-all-threads))
64 (*threads-to-join* nil)
65 (*threads-to-kill* nil))
66 (handler-bind ((error (lambda (error)
67 (if (expected-failure-p fails-on)
68 (fail-test :expected-failure name error)
69 (fail-test :unexpected-failure name error))
70 (return-from run-test))))
71 ;; Non-pretty is for cases like (with-test (:name (let ...)) ...
72 (log-msg/non-pretty "Running ~S" name)
73 (funcall test-function)
74 #+sb-thread
75 (let ((any-leftover nil))
76 (dolist (thread *threads-to-join*)
77 (ignore-errors (sb-thread:join-thread thread)))
78 (dolist (thread *threads-to-kill*)
79 (ignore-errors (sb-thread:terminate-thread thread)))
80 (setf threads (union (union *threads-to-kill*
81 *threads-to-join*)
82 threads))
83 #+(and sb-safepoint-strictly (not win32))
84 (dolist (thread (sb-thread:list-all-threads))
85 (when (typep thread 'sb-thread:signal-handling-thread)
86 (ignore-errors (sb-thread:join-thread thread))))
87 (dolist (thread (sb-thread:list-all-threads))
88 (unless (or (not (sb-thread:thread-alive-p thread))
89 (eql (the sb-thread:thread thread)
90 sb-thread:*current-thread*)
91 (member thread threads)
92 (sb-thread:thread-ephemeral-p thread))
93 (setf any-leftover thread)
94 #-win32
95 (ignore-errors (sb-thread:terminate-thread thread))))
96 (when any-leftover
97 (fail-test :leftover-thread name any-leftover)
98 (return-from run-test)))
99 (if (expected-failure-p fails-on)
100 (fail-test :unexpected-success name nil)
101 ;; Non-pretty is for cases like (with-test (:name (let ...)) ...
102 (log-msg/non-pretty "Success ~S" name)))))
104 (defmacro with-test ((&key fails-on broken-on skipped-on name)
105 &body body)
106 (flet ((name-ok (x y)
107 (declare (ignore y))
108 (typecase x
109 (symbol (let ((package (symbol-package x)))
110 (or (null package)
111 (eql package (find-package "CL"))
112 (eql package (find-package "KEYWORD"))
113 (eql (mismatch "SB-" (package-name package)) 3))))
114 (integer t))))
115 (unless (tree-equal name name :test #'name-ok)
116 (error "test name must be all-keywords: ~S" name)))
117 (cond
118 ((broken-p broken-on)
119 `(progn
120 (start-test)
121 (fail-test :skipped-broken ',name "Test broken on this platform")))
122 ((skipped-p skipped-on)
123 `(progn
124 (start-test)
125 (fail-test :skipped-disabled ',name "Test disabled for this combination of platform and features")))
127 `(run-test (lambda ()
128 ,@body)
129 ',name
130 ',fails-on))))
132 (defun report-test-status ()
133 (with-standard-io-syntax
134 (with-open-file (stream "test-status.lisp-expr"
135 :direction :output
136 :if-exists :supersede)
137 (format stream "~s~%" *failures*))))
139 (defun start-test ()
140 (unless (eq *test-file* *load-pathname*)
141 (setf *test-file* *load-pathname*)
142 (setf *test-count* 0))
143 (incf *test-count*))
145 (defun really-invoke-debugger (condition)
146 (with-simple-restart (continue "Continue")
147 (let ((*invoke-debugger-hook* *invoke-debugger-hook*))
148 (enable-debugger)
149 (invoke-debugger condition))))
151 (defun fail-test (type test-name condition)
152 (if (stringp condition)
153 (log-msg "~@<~A ~S ~:_~A~:>"
154 type test-name condition)
155 (log-msg "~@<~A ~S ~:_due to ~S: ~4I~:_\"~A\"~:>"
156 type test-name (type-of condition) condition))
157 (push (list type *test-file* (or test-name *test-count*))
158 *failures*)
159 (unless (stringp condition)
160 (when (or (and *break-on-failure*
161 (not (eq type :expected-failure)))
162 *break-on-expected-failure*)
163 (really-invoke-debugger condition))))
165 (defun expected-failure-p (fails-on)
166 (sb-impl::featurep fails-on))
168 (defun broken-p (broken-on)
169 (sb-impl::featurep broken-on))
171 (defun skipped-p (skipped-on)
172 (sb-impl::featurep skipped-on))
174 ;;;; MAP-{OPTIMIZATION-QUALITY-COMBINATIONS,OPTIMIZE-DECLARATIONS}
176 (sb-int:defconstant-eqx +optimization-quality-names+
177 '(speed safety debug compilation-speed space) #'equal)
179 (sb-int:defconstant-eqx +optimization-quality-keywords+
180 '(:speed :safety :debug :compilation-speed :space) #'equal)
182 (deftype optimization-quality-range-designator ()
183 '(or (eql nil) ; skip quality
184 (integer 0 3) ; one value
185 (cons (or (eql nil) (integer 0 3)) list) ; list of values, nil means skip
186 (eql t))) ; all values
188 ;;; Call FUNCTION with the specified combinations of optimization
189 ;;; quality values.
191 ;;; MAP-OPTIMIZATION-QUALITY-COMBINATIONS calls FUNCTION with keyword
192 ;;; argument thus expecting a lambda list of the form
194 ;;; (&key speed safety debug compilation-speed space)
196 ;;; or any subset compatible with the generated combinations.
198 ;;; MAP-OPTIMIZE-DECLARATIONS calls FUNCTION with a list intended to
199 ;;; be spliced into a DECLARE form like this:
201 ;;; (lambda (quality-values)
202 ;;; `(declare (optimize ,@quality-values)))
204 ;;; The set of combinations is controlled via keyword arguments
206 ;;; :FILTER FILTER-FUNCTION
207 ;;; A function that should be called with optimization quality
208 ;;; keyword arguments and whose return value controls whether
209 ;;; FUNCTION should be called for the given combination.
211 ;;; (:SPEED | :SAFETY | :DEBUG | :COMPILATION-SPEED | :SPACE) SPEC
212 ;;; Specify value range for the given optimization quality. SPEC
213 ;;; can be
215 ;;; NIL
216 ;;; Omit the quality.
218 ;;; (INTEGER 0 3)
220 ;;; Use the specified value for the quality.
222 ;;; (NIL | (INTEGER 0 3))*
223 ;;; Generate the specified values. A "value" of NIL omits the
224 ;;; quality from the combination.
226 ;;; T
227 ;;; Generate all values (0, 1, 2, 3) for the quality.
228 (declaim (ftype (function #.`(function
229 &key
230 ,@(mapcar #'list +optimization-quality-keywords+
231 '#1=(optimization-quality-range-designator . #1#))
232 (:filter function)))
233 map-optimization-quality-combinations
234 map-optimize-declarations))
235 (defun map-optimization-quality-combinations
236 (function &key (speed t) (safety t) (debug t) (compilation-speed t) (space t)
237 filter)
238 (labels ((map-quantity-values (values thunk)
239 (typecase values
240 ((eql t)
241 (dotimes (i 4) (funcall thunk i)))
242 (cons
243 (map nil thunk values))
244 ((integer 0 3)
245 (funcall thunk values))))
246 (one-quality (qualities specs values)
247 (let ((quality (first qualities))
248 (spec (first specs)))
249 (cond
250 ((not quality)
251 (when (or (not filter) (apply filter values))
252 (apply function values)))
253 ((not spec)
254 (one-quality (rest qualities) (rest specs) values))
256 (map-quantity-values
257 spec
258 (lambda (value)
259 (one-quality (rest qualities) (rest specs)
260 (if value
261 (list* quality value values)
262 values)))))))))
263 (one-quality +optimization-quality-keywords+
264 (list speed safety debug compilation-speed space)
265 '())))
267 (defun map-optimize-declarations
268 (function &rest args
269 &key speed safety debug compilation-speed space filter)
270 (declare (ignore speed safety debug compilation-speed space filter))
271 (apply #'map-optimization-quality-combinations
272 (lambda (&rest args &key &allow-other-keys)
273 (funcall function (loop for name in +optimization-quality-names+
274 for keyword in +optimization-quality-keywords+
275 for value = (getf args keyword)
276 when value collect (list name value))))
277 args))
279 (defun expand-optimize-specifier (specifier)
280 (etypecase specifier
281 (cons
282 specifier)
283 ((eql nil)
284 '(:speed nil :safety nil :debug nil :compilation-speed nil :space nil))
285 ((eql :default)
286 '(:speed 1 :safety 1 :debug 1 :compilation-speed 1 :space 1))
287 ((eql :maximally-safe)
288 (list :filter (lambda (&key safety &allow-other-keys)
289 (= safety 3))))
290 ((eql :safe)
291 (list :filter (lambda (&key speed safety &allow-other-keys)
292 (and (> safety 0) (>= safety speed)))))
293 ((eql :quick)
294 '(:compilation-speed 1 :space 1))
295 ((eql :quick/incomplete)
296 '(:compilation-speed nil :space nil))
297 ((eql :all)
298 '())))
300 (defun map-optimization-quality-combinations* (function specifier)
301 (apply #'map-optimization-quality-combinations
302 function (expand-optimize-specifier specifier)))
304 (defun map-optimize-declarations* (function specifier)
305 (apply #'map-optimize-declarations
306 function (expand-optimize-specifier specifier)))
308 ;;;; CHECKED-COMPILE
310 (defun prepare-form (thing &key optimize)
311 (cond
312 ((functionp thing)
313 (error "~@<~S is a function, not a form.~@:>" thing))
314 ((not optimize)
315 thing)
316 ((typep thing '(cons (eql sb-int:named-lambda)))
317 `(,@(subseq thing 0 3)
318 (declare (optimize ,@optimize))
319 ,@(nthcdr 3 thing)))
320 ((typep thing '(cons (eql lambda)))
321 `(,(first thing) ,(second thing)
322 (declare (optimize ,@optimize))
323 ,@(nthcdr 2 thing)))
325 (error "~@<Cannot splice ~A declaration into forms other than ~
326 ~{~S~#[~; and ~:;, ~]~}: ~S.~@:>"
327 'optimize '(lambda sb-int:named-lambda) thing))))
329 (defun compile-capturing-output-and-conditions
330 (form &key name condition-transform)
331 (let ((warnings '())
332 (style-warnings '())
333 (notes '())
334 (compiler-errors '())
335 (error-output (make-string-output-stream)))
336 (flet ((maybe-transform (condition)
337 (if condition-transform
338 (funcall condition-transform condition)
339 condition)))
340 (handler-bind ((sb-ext:compiler-note
341 (lambda (condition)
342 (push (maybe-transform condition) notes)
343 (muffle-warning condition)))
344 (style-warning
345 (lambda (condition)
346 (push (maybe-transform condition) style-warnings)
347 (muffle-warning condition)))
348 (warning
349 (lambda (condition)
350 (push (maybe-transform condition) warnings)
351 (muffle-warning condition)))
352 (sb-c:compiler-error
353 (lambda (condition)
354 (push (maybe-transform condition) compiler-errors))))
355 (multiple-value-bind (function warnings-p failure-p)
356 (let ((*error-output* error-output))
357 (compile name form))
358 (values function warnings-p failure-p
359 warnings style-warnings notes compiler-errors
360 error-output))))))
362 (defun print-form-and-optimize (stream form-and-optimize &optional colonp atp)
363 (declare (ignore colonp atp))
364 (destructuring-bind (form . optimize) form-and-optimize
365 (format stream "~@:_~@:_~2@T~S~@:_~@:_~
366 with ~:[~
367 default optimization policy~
369 ~:*~@:_~@:_~2@T~S~@:_~@:_~
370 optimization policy~
372 form optimize)))
374 (defun print-signaled-conditions (stream conditions &optional colonp atp)
375 (declare (ignore colonp atp))
376 (format stream "~{~@:_~@:_~{~/sb-ext:print-symbol-with-prefix/: ~A~}~}"
377 (mapcar (lambda (condition)
378 (list (type-of condition) condition))
379 conditions)))
381 ;;; Compile FORM capturing and muffling all [style-]warnings and notes
382 ;;; and return six values: 1) the compiled function 2) a Boolean
383 ;;; indicating whether compilation failed 3) a list of warnings 4) a
384 ;;; list of style-warnings 5) a list of notes 6) a list of
385 ;;; SB-C:COMPILER-ERROR conditions.
387 ;;; An error can be signaled when COMPILE indicates failure as well as
388 ;;; in case [style-]warning or note conditions are signaled. The
389 ;;; keyword parameters
390 ;;; ALLOW-{FAILURE,[STYLE-]WARNINGS,NOTES,COMPILER-ERRORS} control
391 ;;; this behavior. All but ALLOW-NOTES default to NIL.
393 ;;; Arguments to the
394 ;;; ALLOW-{FAILURE,[STYLE-]WARNINGS,NOTES,COMPILER-ERRORS} keyword
395 ;;; parameters are interpreted as type specifiers restricting the
396 ;;; allowed conditions of the respective kind.
398 ;;; When supplied, the value of CONDITION-TRANSFORM has to be a
399 ;;; function of one argument, the condition currently being
400 ;;; captured. The returned value is captured and later returned in
401 ;;; place of the condition.
402 (defun checked-compile (form
403 &key
404 name
405 allow-failure
406 allow-warnings
407 allow-style-warnings
408 (allow-notes t)
409 (allow-compiler-errors allow-failure)
410 condition-transform
411 optimize)
412 (sb-int:binding* ((prepared-form (prepare-form form :optimize optimize))
413 ((function nil failure-p
414 warnings style-warnings notes compiler-errors
415 error-output)
416 (compile-capturing-output-and-conditions
417 prepared-form :name name :condition-transform condition-transform)))
418 (labels ((fail (kind conditions &optional allowed-type)
419 (error "~@<Compilation of~/test-util::print-form-and-optimize/ ~
420 signaled ~A~P:~/test-util::print-signaled-conditions/~
421 ~@[~@:_~@:_Allowed type is ~
422 ~/sb-ext:print-type-specifier/.~]~@:>"
423 (cons form optimize) kind (length conditions) conditions
424 allowed-type))
425 (check-conditions (kind conditions allow)
426 (cond
427 (allow
428 (let ((offenders (remove-if (lambda (condition)
429 (typep condition allow))
430 conditions)))
431 (when offenders
432 (fail kind offenders allow))))
433 (conditions
434 (fail kind conditions)))))
436 (when (and (not allow-failure) failure-p)
437 (let ((output (get-output-stream-string error-output)))
438 (error "~@<Compilation of~/test-util::print-form-and-optimize/ ~
439 failed~@[ with output~
440 ~@:_~@:_~2@T~@<~@;~A~:>~@:_~@:_~].~@:>"
441 (cons form optimize) (when (plusp (length output)) output))))
443 (check-conditions "warning" warnings allow-warnings)
444 (check-conditions "style-warning" style-warnings allow-style-warnings)
445 (check-conditions "note" notes allow-notes)
446 (check-conditions "compiler-error" compiler-errors allow-compiler-errors)
448 ;; Since we may have prevented warnings from being taken
449 ;; into account for FAILURE-P by muffling them, adjust the
450 ;; second return value accordingly.
451 (values function (when (or failure-p warnings) t)
452 warnings style-warnings notes compiler-errors))))
454 (defun print-arguments (stream arguments &optional colonp atp)
455 (declare (ignore colonp atp))
456 (format stream "~:[~
457 without arguments ~
458 ~;~:*~
459 with arguments~@:_~@:_~
460 ~2@T~@<~{~S~^~@:_~}~:>~@:_~@:_~
462 arguments))
464 (defun call-capturing-values-and-conditions (function &rest args)
465 (let ((values nil)
466 (conditions '()))
467 (block nil
468 (handler-bind ((condition (lambda (condition)
469 (push condition conditions)
470 (typecase condition
471 (warning
472 (muffle-warning condition))
473 (serious-condition
474 (return))))))
475 (setf values (multiple-value-list (apply function args)))))
476 (values values (nreverse conditions))))
478 (defun %checked-compile-and-assert-one-case
479 (form optimize function args-thunk expected test)
480 (let ((args (multiple-value-list (funcall args-thunk))))
481 (flet ((failed-to-signal (expected-type)
482 (error "~@<Calling the result of compiling~
483 ~/test-util::print-form-and-optimize/ ~
484 ~/test-util::print-arguments/~
485 returned normally instead of signaling a ~
486 condition of type ~
487 ~/sb-ext:print-type-specifier/.~@:>"
488 (cons form optimize) args expected-type))
489 (signaled-unexpected (conditions)
490 (error "~@<Calling the result of compiling~
491 ~/test-util::print-form-and-optimize/ ~
492 ~/test-util::print-arguments/~
493 signaled unexpected condition~P~
494 ~/test-util::print-signaled-conditions/~
495 .~@:>"
496 (cons form optimize) args (length conditions) conditions))
497 (returned-unexpected (values expected test)
498 (error "~@<Calling the result of compiling~
499 ~/test-util::print-form-and-optimize/ ~
500 ~/test-util::print-arguments/~
501 returned values~@:_~@:_~
502 ~2@T~<~{~S~^~@:_~}~:>~@:_~@:_~
503 with is not ~S to~@:_~@:_~
504 ~2@T~<~{~S~^~@:_~}~:>~@:_~@:_~
505 .~@:>"
506 (cons form optimize) args
507 (list values) test (list expected))))
508 (multiple-value-bind (values conditions)
509 (apply #'call-capturing-values-and-conditions function args)
510 (typecase expected
511 ((cons (eql condition) (cons t null))
512 (let* ((expected-condition-type (second expected))
513 (unexpected (remove-if (lambda (condition)
514 (typep condition
515 expected-condition-type))
516 conditions))
517 (expected (set-difference conditions unexpected)))
518 (cond
519 (unexpected
520 (signaled-unexpected unexpected))
521 ((null expected)
522 (failed-to-signal expected-condition-type)))))
524 (let ((expected (funcall expected)))
525 (cond
526 (conditions
527 (signaled-unexpected conditions))
528 ((not (funcall test values expected))
529 (returned-unexpected values expected test))))))))))
531 (defun %checked-compile-and-assert-one-compilation
532 (form optimize other-checked-compile-args cases)
533 (let ((function (apply #'checked-compile form
534 (if optimize
535 (list* :optimize optimize
536 other-checked-compile-args)
537 other-checked-compile-args))))
538 (loop for (args-thunk values test) in cases
539 do (%checked-compile-and-assert-one-case
540 form optimize function args-thunk values test))))
542 (defun %checked-compile-and-assert (form checked-compile-args cases)
543 (let ((optimize (getf checked-compile-args :optimize))
544 (other-args (loop for (key value) on checked-compile-args by #'cddr
545 unless (eq key :optimize)
546 collect key and collect value)))
547 (map-optimize-declarations*
548 (lambda (&optional optimize)
549 (%checked-compile-and-assert-one-compilation
550 form optimize other-args cases))
551 optimize)))
553 ;;; Compile FORM using CHECKED-COMPILE, then call the resulting
554 ;;; function with arguments and assert expected return values
555 ;;; according to CASES.
557 ;;; Elements of CASES are of the form
559 ;;; ((&rest ARGUMENT-FORMS) VALUES-FORM &optional TEST)
561 ;;; where ARGUMENT-FORMS are evaluated to produce the arguments for
562 ;;; one call of the function and VALUES-FORM is evaluated to produce
563 ;;; the expected return values for that function call. TEST is used to
564 ;;; compare a list of the values returned by the function call to the
565 ;;; list of values obtained by calling VALUES-FORM.
567 ;;; If VALUES-FORM is of the form
569 ;;; (CONDITION CONDITION-TYPE)
571 ;;; the function call is expected to signal the designated condition
572 ;;; instead of returning values. CONDITION-TYPE is evaluated.
574 ;;; The OPTIMIZE keyword parameter controls the optimization policies
575 ;;; (or policy) used when compiling FORM. The argument is interpreted
576 ;;; as described for MAP-OPTIMIZE-DECLARATIONS*.
578 ;;; The other keyword parameters, NAME and
579 ;;; ALLOW-{WARNINGS,STYLE-WARNINGS,NOTES}, behave as with
580 ;;; CHECKED-COMPILE.
581 (defmacro checked-compile-and-assert ((&key name
582 allow-warnings
583 allow-style-warnings
584 (allow-notes t)
585 (optimize :quick))
586 form &body cases)
587 (flet ((make-case-form (case)
588 (destructuring-bind (args values &key (test ''equal testp))
589 case
590 (let ((conditionp (typep values '(cons (eql condition) (cons t null)))))
591 (when (and testp conditionp)
592 (sb-ext:with-current-source-form (case)
593 (error "~@<Cannot use ~S with ~S ~S.~@:>"
594 values :test test)))
595 `(list (lambda () (values ,@args))
596 ,(if conditionp
597 `(list 'condition ,(second values))
598 `(lambda () (multiple-value-list ,values)))
599 ,test)))))
600 `(%checked-compile-and-assert
601 ,form (list :name ,name
602 :allow-warnings ,allow-warnings
603 :allow-style-warnings ,allow-style-warnings
604 :allow-notes ,allow-notes
605 :optimize ,optimize)
606 (list ,@(mapcar #'make-case-form cases)))))
608 ;;; Like CHECKED-COMPILE, but for each captured condition, capture and
609 ;;; later return a cons
611 ;;; (CONDITION . SOURCE-PATH)
613 ;;; instead. SOURCE-PATH is the path of the source form associated to
614 ;;; CONDITION.
615 (defun checked-compile-capturing-source-paths (form &rest args)
616 (labels ((context-source-path ()
617 (let ((context (sb-c::find-error-context nil)))
618 (sb-c::compiler-error-context-original-source-path
619 context)))
620 (add-source-path (condition)
621 (cons condition (context-source-path))))
622 (apply #'checked-compile form :condition-transform #'add-source-path
623 args)))
625 ;;; Similar to CHECKED-COMPILE, but allow compilation failure and
626 ;;; warnings and only return source paths associated to those
627 ;;; conditions.
628 (defun checked-compile-condition-source-paths (form)
629 (let ((source-paths '()))
630 (labels ((context-source-path ()
631 (let ((context (sb-c::find-error-context nil)))
632 (sb-c::compiler-error-context-original-source-path
633 context)))
634 (push-source-path (condition)
635 (declare (ignore condition))
636 (push (context-source-path) source-paths)))
637 (checked-compile form
638 :allow-failure t
639 :allow-warnings t
640 :allow-style-warnings t
641 :condition-transform #'push-source-path))
642 (nreverse source-paths)))
644 ;;; Repeat calling THUNK until its cumulated runtime, measured using
645 ;;; GET-INTERNAL-RUN-TIME, is larger than PRECISION. Repeat this
646 ;;; REPETITIONS many times and return the time one call to THUNK took
647 ;;; in seconds as a float, according to the minimum of the cumulated
648 ;;; runtimes over the repetitions.
649 ;;; This allows to easily measure the runtime of expressions that take
650 ;;; much less time than one internal time unit. Also, the results are
651 ;;; unaffected, modulo quantization effects, by changes to
652 ;;; INTERNAL-TIME-UNITS-PER-SECOND.
653 ;;; Taking the minimum is intended to reduce the error introduced by
654 ;;; garbage collections occurring at unpredictable times. The inner
655 ;;; loop doubles the number of calls to THUNK each time before again
656 ;;; measuring the time spent, so that the time measurement overhead
657 ;;; doesn't distort the result if calling THUNK takes very little time.
658 (defun runtime* (thunk repetitions precision)
659 (loop repeat repetitions
660 minimize
661 (loop with start = (get-internal-run-time)
662 with duration = 0
663 for n = 1 then (* n 2)
664 for total-runs = n then (+ total-runs n)
665 for gc-start = *gc-run-time*
666 do (dotimes (i n)
667 (funcall thunk))
668 (setf duration (- (get-internal-run-time) start
669 (- *gc-run-time* gc-start)))
670 when (> duration precision)
671 return (/ (float duration)
672 (float total-runs)))
673 into min-internal-time-units-per-call
674 finally (return (/ min-internal-time-units-per-call
675 (float internal-time-units-per-second)))))
677 (defmacro runtime (form &key (repetitions 5) (precision 30))
678 `(runtime* (lambda () ,form) ,repetitions ,precision))
680 (defun split-string (string delimiter)
681 (loop for begin = 0 then (1+ end)
682 for end = (position delimiter string) then (position delimiter string :start begin)
683 collect (subseq string begin end)
684 while end))
686 (defun shuffle (sequence)
687 (typecase sequence
688 (list
689 (coerce (shuffle (coerce sequence 'vector)) 'list))
690 (vector ; destructive
691 (let ((vector sequence))
692 (loop for lim from (1- (length vector)) downto 0
693 for chosen = (random (1+ lim))
694 unless (= chosen lim)
695 do (rotatef (aref vector chosen) (aref vector lim)))
696 vector))))