Simpler suites list.
[fiveam.git] / src / run.lisp
1 ;;;; -*- Mode: Lisp; indent-tabs-mode: nil -*-
2
3 (in-package :it.bese.fiveam)
4
5 ;;;; * Running Tests
6
7 ;;;; Once the programmer has defined what the tests are these need to
8 ;;;; be run and the expected effects should be compared with the
9 ;;;; actual effects. FiveAM provides the function RUN for this
10 ;;;; purpose, RUN executes a number of tests and collects the results
11 ;;;; of each individual check into a list which is then
12 ;;;; returned. There are three types of test results: passed, failed
13 ;;;; and skipped, these are represented by TEST-RESULT objects.
14
15 ;;;; Generally running a test will return normally, but there are two
16 ;;;; exceptional situations which can occur:
17
18 ;;;; - An exception is signaled while running the test. If the
19 ;;;;   variable *debug-on-error* is T than FiveAM will enter the
20 ;;;;   debugger, otherwise a test failure (of type
21 ;;;;   unexpected-test-failure) is returned. When entering the
22 ;;;;   debugger two restarts are made available, one simply reruns the
23 ;;;;   current test and another signals a test-failure and continues
24 ;;;;   with the remaining tests.
25
26 ;;;; - A circular dependency is detected. An error is signaled and a
27 ;;;;   restart is made available which signals a test-skipped and
28 ;;;;   continues with the remaining tests. This restart also sets the
29 ;;;;   dependency status of the test to nil, so any tests which depend
30 ;;;;   on this one (even if the dependency is not circular) will be
31 ;;;;   skipped.
32
33 ;;;; The functions RUN! is a convenient wrapper around RUN and
34 ;;;; EXPLAIN.
35
36 (defparameter *debug-on-error* nil
37   "T if we should drop into a debugger on error, NIL otherwise.")
38
39 (defparameter *debug-on-failure* nil
40   "T if we should drop into a debugger on a failing check, NIL otherwise.")
41
42 (defun import-testing-symbols (package-designator)
43   (import '(5am::is 5am::is-true 5am::is-false 5am::signals 5am::finishes)
44           package-designator))
45
46 (defparameter *run-queue* '()
47   "List of test waiting to be run.")
48
49 (define-condition circular-dependency (error)
50   ((test-case :initarg :test-case))
51   (:report (lambda (cd stream)
52              (format stream "A circular dependency wes detected in ~S." (slot-value cd 'test-case))))
53   (:documentation "Condition signaled when a circular dependency
54 between test-cases has been detected."))
55
56 (defgeneric run-resolving-dependencies (test)
57   (:documentation "Given a dependency spec determine if the spec
58 is satisfied or not, this will generally involve running other
59 tests. If the dependency spec can be satisfied the test is also
60 run."))
61
62 (defmethod run-resolving-dependencies ((test test-case))
63   "Return true if this test, and its dependencies, are satisfied,
64   NIL otherwise."
65   (case (status test)
66     (:unknown
67      (setf (status test) :resolving)
68      (if (or (not (depends-on test))
69              (eql t (resolve-dependencies (depends-on test))))
70          (progn
71            (run-test-lambda test)
72            (status test))
73          (with-run-state (result-list)
74            (unless (eql :circular (status test))
75              (push (make-instance 'test-skipped
76                                   :test-case test
77                                   :reason "Dependencies not satisfied")
78                    result-list)
79              (setf (status test) :depends-not-satisfied)))))
80     (:resolving
81      (restart-case
82          (error 'circular-dependency :test-case test)
83        (skip ()
84          :report (lambda (s)
85                    (format s "Skip the test ~S and all its dependencies." (name test)))
86          (with-run-state (result-list)
87            (push (make-instance 'test-skipped :reason "Circular dependencies" :test-case test)
88                  result-list))
89          (setf (status test) :circular))))
90     (t (status test))))
91
92 (defgeneric resolve-dependencies (depends-on))
93
94 (defmethod resolve-dependencies ((depends-on symbol))
95   "A test which depends on a symbol is interpreted as `(AND
96   ,DEPENDS-ON)."
97   (run-resolving-dependencies (get-test depends-on)))
98
99 (defmethod resolve-dependencies ((depends-on list))
100   "Return true if the dependency spec DEPENDS-ON is satisfied,
101   nil otherwise."
102   (if (null depends-on)
103       t
104       (flet ((satisfies-depends-p (test)
105                (funcall test (lambda (dep)
106                                (eql t (resolve-dependencies dep)))
107                         (cdr depends-on))))
108         (ecase (car depends-on)
109           (and (satisfies-depends-p #'every))
110           (or  (satisfies-depends-p #'some))
111           (not (satisfies-depends-p #'notany))
112           (:before (every #'(lambda (dep)
113                               (eql :unknown (status (get-test dep))))
114                           (cdr depends-on)))))))
115
116 (defun results-status (result-list)
117   "Given a list of test results (generated while running a test)
118   return true if all of the results are of type TEST-PASSED,
119   fail otherwise.
120   Returns a second value, which is the set of failed tests."
121   (let ((failed-tests
122           (remove-if #'test-passed-p result-list)))
123     (values (null failed-tests)
124             failed-tests)))
125
126 (defun return-result-list (test-lambda)
127   "Run the test function TEST-LAMBDA and return a list of all
128   test results generated, does not modify the special environment
129   variable RESULT-LIST."
130   (bind-run-state ((result-list '()))
131     (funcall test-lambda)
132     result-list))
133
134 (defgeneric run-test-lambda (test))
135
136 (defmethod run-test-lambda ((test test-case))
137   (with-run-state (result-list)
138     (bind-run-state ((current-test test))
139       (labels ((abort-test (e)
140                  (add-result 'unexpected-test-failure
141                              :test-expr nil
142                              :test-case test
143                              :reason (format nil "Unexpected Error: ~S~%~A." e e)
144                              :condition e))
145                (run-it ()
146                  (let ((result-list '()))
147                    (declare (special result-list))
148                    (handler-bind ((check-failure (lambda (e)
149                                                    (declare (ignore e))
150                                                    (unless *debug-on-failure*
151                                                      (invoke-restart
152                                                       (find-restart 'ignore-failure)))))
153                                   (error (lambda (e)
154                                            (unless (or *debug-on-error*
155                                                        (typep e 'check-failure))
156                                              (abort-test e)
157                                              (return-from run-it result-list)))))
158                      (restart-case
159                          (let ((*readtable* (copy-readtable))
160                                (*package* (runtime-package test)))
161                            (if (collect-profiling-info test)
162                                ;; Timing info doesn't get collected ATM, we need a portable library
163                                ;; (setf (profiling-info test) (collect-timing (test-lambda test)))
164                                (funcall (test-lambda test))
165                                (funcall (test-lambda test))))
166                        (retest ()
167                          :report (lambda (stream)
168                                    (format stream "~@<Rerun the test ~S~@:>" test))
169                          (return-from run-it (run-it)))
170                        (ignore ()
171                          :report (lambda (stream)
172                                    (format stream "~@<Signal an exceptional test failure and abort the test ~S.~@:>" test))
173                          (abort-test (make-instance 'test-failure :test-case test
174                                                     :reason "Failure restart."))))
175                      result-list))))
176         (let ((results (run-it)))
177           (setf (status test) (results-status results)
178                 result-list (nconc result-list results)))))))
179
180 (defgeneric %run (test-spec)
181   (:documentation "Internal method for running a test. Does not
182   update the status of the tests nor the special variables !,
183   !!, !!!"))
184
185 (defmethod %run ((test test-case))
186   (run-resolving-dependencies test))
187
188 (defmethod %run ((tests list))
189   (mapc #'%run tests))
190
191 (defmethod %run ((suite test-suite))
192   (let ((suite-results '()))
193     (flet ((run-tests ()
194              (loop
195                 for test being the hash-values of (tests suite)
196                 do (%run test))))
197       (unwind-protect
198            (bind-run-state ((result-list '()))
199              (unwind-protect
200                   (if (collect-profiling-info suite)
201                       ;; Timing info doesn't get collected ATM, we need a portable library
202                       ;; (setf (profiling-info suite) (collect-timing #'run-tests))
203                       (run-tests)
204                       (run-tests)))
205              (setf suite-results result-list
206                    (status suite) (every #'test-passed-p suite-results)))
207         (with-run-state (result-list)
208           (setf result-list (nconc result-list suite-results)))))))
209
210 (defmethod %run ((test-name symbol))
211   (when-let (test (get-test test-name))
212     (%run test)))
213
214 (defvar *initial-!* (lambda () (format t "Haven't run that many tests yet.~%")))
215
216 (defvar *!* *initial-!*)
217 (defvar *!!* *initial-!*)
218 (defvar *!!!* *initial-!*)
219
220 ;;;; ** Public entry points
221
222 (defun run! (&optional (test-spec *suite*))
223   "Equivalent to (explain! (run TEST-SPEC))."
224   (explain! (run test-spec)))
225
226 (defun explain! (result-list)
227   "Explain the results of RESULT-LIST using a
228 detailed-text-explainer with output going to `*test-dribble*`"
229   (explain (make-instance 'detailed-text-explainer) result-list *test-dribble*))
230
231 (defun debug! (&optional (test-spec *suite*))
232   "Calls (run! test-spec) but enters the debugger if any kind of error happens."
233   (let ((*debug-on-error* t)
234         (*debug-on-failure* t))
235     (run! test-spec)))
236
237 (defun reset-all-tests-status (&optional (tests *test*))
238   "Resets the status of all TESTS to :unknown."
239   (maphash-values
240    (lambda (test)
241      (setf (status test) :unknown))
242    tests))
243
244 (defun run-and-set-recently (function)
245   "Shifts the recently executed tests and lastly executes FUNCTION."
246   (shiftf *!!!* *!!* *!* function)
247   (funcall function))
248
249 (defun run-and-bind-result-list (function)
250   (run-and-set-recently
251    (lambda ()
252      (reset-all-tests-status)
253      (bind-run-state ((result-list '()))
254        (with-simple-restart
255            (explain "Ignore the rest of the tests and explain current results")
256          (funcall function))
257        result-list))))
258
259 (defun run (test-spec)
260   "Run the test specified by TEST-SPEC.
261
262 TEST-SPEC can be either a symbol naming a test or test suite, or
263 a testable-object object. This function changes the operations
264 performed by the !, !! and !!! functions."
265   (run-and-bind-result-list (lambda () (%run test-spec))))
266
267 (defun run-all-tests ()
268   "Run all tests in arbitrary order."
269   (run-and-bind-result-list
270    (lambda ()
271      (maphash-values
272       (lambda (test)
273         (when (typep test 'test-case)
274           (%run test)))
275       *test*))))
276
277 (defun run-all-tests! ()
278   "Equivalent to (explain! (run-all-tests))."
279   (explain! (run-all-tests)))
280
281 (defun run-all-test-suites ()
282   "Run all test suites in arbitrary order."
283   (run-and-bind-result-list
284    (lambda ()
285      (maphash-values
286       (lambda (test)
287         (when (typep test 'test-suite)
288           (format *test-dribble* "~& ~A: " (name test))
289           (%run test)))
290       *test*))))
291
292 (defun run-all-test-suites! ()
293   "Equivalent to (explain (run-all-test-suites))."
294   (explain! (run-all-test-suites)))
295
296 ;; Copyright (c) 2002-2003, Edward Marco Baringer
297 ;; All rights reserved.
298 ;;
299 ;; Redistribution and use in source and binary forms, with or without
300 ;; modification, are permitted provided that the following conditions are
301 ;; met:
302 ;;
303 ;;  - Redistributions of source code must retain the above copyright
304 ;;    notice, this list of conditions and the following disclaimer.
305 ;;
306 ;;  - Redistributions in binary form must reproduce the above copyright
307 ;;    notice, this list of conditions and the following disclaimer in the
308 ;;    documentation and/or other materials provided with the distribution.
309 ;;
310 ;;  - Neither the name of Edward Marco Baringer, nor BESE, nor the names
311 ;;    of its contributors may be used to endorse or promote products
312 ;;    derived from this software without specific prior written permission.
313 ;;
314 ;; THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
315 ;; "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
316 ;; LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
317 ;; A PARTICULAR PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE COPYRIGHT
318 ;; OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
319 ;; SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
320 ;; LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
321 ;; DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
322 ;; THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
323 ;; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
324 ;; OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.