1\documentclass[11pt]{article}
2\usepackage{times}
3\usepackage{pl}
4\usepackage{html}
5\usepackage{plpage}
6\sloppy
7\makeindex
8
9\onefile
10\htmloutput{.}					% Output directory
11\htmlmainfile{plunit}				% Main document file
12\bodycolor{white}				% Page colour
13
14\renewcommand{\runningtitle}{Prolog Unit Tests}
15
16\begin{document}
17
18\title{Prolog Unit Tests}
19\author{Jan Wielemaker \\
20	University of Amsterdam \\
21	VU University Amsterdam \\
22	The Netherlands \\
23	E-mail: \email{jan@swi-prolog.org}}
24
25\maketitle
26
27\begin{abstract}
28This document describes a Prolog unit-test framework. This framework was
29initially developed for \href{http://www.swi-prolog.org}{SWI-Prolog}.
30The current version also runs on
31\href{http://www.sics.se/sicstus/}{SICStus Prolog}, providing a portable
32testing framework. See \secref{sicstus}.
33\end{abstract}
34
35\pagebreak
36\tableofcontents
37
38\vfill
39\vfill
40
41\newpage
42
43\section{Introduction}
44\label{sec:plunit-intro}
45
46There is really no excuse not to write tests!
47
48Automatic testing of software during development is probably the most
49important Quality Assurance measure. Tests can validate the final
50system, which is nice for your users.  However, most (Prolog) developers
51forget that it is not just a burden during development.
52
53\begin{itemize}
54    \item Tests document how the code is supposed to be used.
55    \item Tests can validate claims you make on the Prolog
56          implementation.  Writing a test makes the claim
57	  explicit.
58    \item Tests avoid big applications saying `No' after
59          modifications.  This saves time during development,
60	  and it saves \emph{a lot} of time if you must return
61	  to the application a few years later or you must
62	  modify and debug someone else's application.
63\end{itemize}
64
65
66%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
67\section{A Unit Test box}
68\label{sec:unitbox}
69
70Tests are written in pure Prolog and enclosed within the directives
71begin_tests/1,2 and end_tests/1. They can be embedded inside a normal
72source module, or be placed in a separate test-file that loads the files
73to be tested. Code inside a test box is normal Prolog code. The
74entry points are defined by rules using the head \term{test}{Name} or
75\term{test}{Name, Options}, where \arg{Name} is a ground term and
76\arg{Options} is a list describing additional properties of the test.
77Here is a very simple example:
78
79\begin{code}
80:- begin_tests(lists).
81:- use_module(library(lists)).
82
83test(reverse) :-
84	reverse([a,b], [b,a]).
85
86:- end_tests(lists).
87\end{code}
88
89The optional second argument of the test-head defines additional processing
90options.  Defined options are:
91
92\begin{description}
93    \termitem{blocked}{+Reason:atom}
94The test is currently disabled.   Tests are flagged as blocked if they
95cannot be run for some reason.  E.g.\ they crash Prolog, they rely on
96some service that is not available, they take too much resources, etc.
97Tests that fail but do not crash, etc.\ should be flagged using
98\term{fixme}{Fixme}.
99
100    \termitem{fixme}{+Reason:atom}
101Similar to \term{blocked}{Reason}, but the test it executed anyway.  If
102it fails, a \const{-} is printed instead of the \const{.} character.  If
103it passes a \const{+} and if it passes with a choicepoint, \const{!}.
104A summary is printed at the end of the test run and the goal
105\term{test_report}{fixme} can be used to get details.
106
107    \termitem{condition}{:Goal}
108Pre-condition for running the test.  If the condition fails
109the test is skipped.  The condition can be used as an alternative
110to the \const{setup} option.  The only difference is that failure
111of a condition skips the test and is considered an error when using
112the \const{setup} option.
113
114    \termitem{cleanup}{:Goal}
115\arg{Goal} is always called after completion of the test-body,
116regardless of whether it fails, succeeds or throws an exception.  This
117option or call_cleanup/2 must be used by tests that require side-effects
118that must be reverted after the test completes.  \arg{Goal} may share
119variables with the test body.
120
121\begin{code}
122create_file(Tmp) :-
123	tmp_file(plunit, Tmp),
124	open(Tmp, write, Out),
125	write(Out, 'hello(World).\n'),
126	close(Out).
127
128test(read, [ setup(create_file(Tmp)),
129	     cleanup(delete_file(Tmp))
130	   ]) :-
131	read_file_to_terms(Tmp, Terms, []),
132	Term = hello(_).
133\end{code}
134
135    \termitem{setup}{:Goal}
136\arg{Goal} is run before the test-body.  Typically used together with
137the \const{cleanup} option to create and destroy the required execution
138environment.
139
140    \termitem{forall}{:Generator}
141Run the same test for each solution of \arg{Generator}. Each run invokes
142the setup and cleanup handlers. This can be used to run the same test
143with different inputs.  If an error occurs, the test is reported as
144\mbox{\texttt{name (forall bindings = } <vars> \texttt{)}}, where
145<vars> indicates the bindings of variables in \arg{Generator}.
146
147    \termitem{true}{AnswerTerm Cmp Value}
148Body should succeed deterministically. If a choicepoint is left open, a
149warning is printed to STDERR ("Test succeeded with choicepoint"). That
150warning can be suppressed by adding the \term{nondet} keyword. \arg{AnswerTerm}
151is compared to \arg{Value} using the comparison operator \arg{Cmp}. \arg{Cmp}
152is typically one of =/2, ==/2, =:=/2 or =@=/2,%
153    \footnote{The =@= predicate (denoted \emph{structural equivalence})
154	      is the same as variant/2 in SICStus.}
155but any test can be used. This is the same as inserting the test at the
156end of the conjunction, but it allows the test engine to distinguish
157between failure of copy_term/2 and producing the wrong value. Multiple
158variables must be combined in an arbitrary compound term. E.g.\
159\verb$A1-A2 == v1-v2$
160
161\begin{code}
162test(copy, [ true(Copy =@= hello(X,X))
163	   ]) :-
164	copy_term(hello(Y,Y), Copy).
165\end{code}
166
167    \termitem{AnswerTerm Cmp Value}
168Equivalent to \term{true}{AnswerTerm Cmp Value} if \arg{Cmp} is one
169of the comparison operators given above.
170
171    \termitem{fail}{}
172Body must fail.
173
174    \termitem{throws}{Error}
175Body must throw \arg{Error}. The thrown error term is matched against
176term \arg{Error} using \term{subsumes_term}{Error, ThrownError}. I.e., the
177thrown error must be more specific than the specified \arg{Error}.  See
178subsumes_term/2.
179
180    \termitem{error}{Error}
181Body must throw \term{error}{Error, _Context}.  See keyword \const{throws}
182(as well as predicate throw/1 and library(error)) for details.
183
184    \termitem{all}{AnswerTerm Cmp Instances}
185Similar to \term{true}{AnswerTerm Cmp Values}, but used for non-deterministic
186predicates. Each element is compared using \arg{Cmp}. Order matters. For
187example:
188
189\begin{code}
190test(or, all(X == [1,2])) :-
191	( X = 1 ; X = 2 ).
192\end{code}
193
194    \termitem{set}{AnswerTerm Cmp Instances}
195Similar to \term{all}{AnswerTerm Cmp Instances}, but before testing both
196the bindings of \arg{AnswerTerm} and \arg{Instances} are sorted using
197sort/2. This removes duplicates and places both sets in the same
198order.\footnote{The result is only well-defined of \arg{Cmp} is
199\texttt{==}.}
200
201    \termitem{nondet}{}
202If this keyword appears in the option list, non-deterministic success
203of the body is not considered an error.
204
205    \termitem{sto}{Terms}
206Declares that executing body is subject to occurs-check (STO).  The
207test is executed with \arg{Terms}.  \arg{Terms} is either
208\const{rational_trees} or \const{finite_trees}.  STO programs are not
209portable between different kinds of terms.  Only programs \emph{not}
210subject to occurs-check (NSTO) are portable\footnote{See 7.3.3 of
211ISO/IEC 13211-1 PROLOG: Part 1 - General Core, for a detailed
212discussion of STO and NSTO}.  Fortunately, most practical programs are
213NSTO.  Writing tests that are STO is still useful to ensure the
214robustness of a predicate.  In case sto4 and sto5 below, an infinite
215list (a rational tree) is created prior to calling the actual
216predicate.  Ideally, such cases produce a type error or fail silently.
217
218\begin{code}
219test(sto1, [sto(rational_trees)]) :-
220	X=s(X).
221test(sto2, [sto(finite_trees),fail]) :-
222	X=s(X).
223test(sto3, [sto(rational_trees), fail]) :-
224	X=s(X), fail.
225test(sto4, [sto(rational_trees),error(type_error(list,L))]) :-
226	L = [_|L], length(L,_).
227test(sto5, [sto(rational_trees),fail]) :-
228	L = [_|L], length(L,3).
229\end{code}
230
231Programs that depend on STO cases tend to be inefficient, even
232incorrect, are hard to understand and debug, and terminate poorly.  It
233is therefore advisable to avoid STO programs whenever possible.
234
235SWI's Prolog flag \prologflag{occurs_check} must not be modified
236within plunit tests.
237
238\end{description}
239
240%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
241\subsection{Test Unit options}
242\label{sec:unitoptions}
243
244\begin{description}
245    \predicate{begin_tests}{1}{+Name}
246Start named test-unit.  Same as \verb$begin_tests(Name, [])$.
247
248    \predicate{begin_tests}{2}{+Name, +Options}
249Start named test-unit with options. Options provide conditional
250processing, setup and cleanup similar to individual tests (second
251argument of test/2 rules).
252
253Defined options are:
254    \begin{description}
255	\termitem{blocked}{+Reason}
256Test-unit has been blocked for the given \arg{Reason}.
257
258        \termitem{condition}{:Goal}
259Executed before executing any of the tests.  If \arg{Goal} fails,
260the test of this unit is skipped.
261
262        \termitem{setup}{:Goal}
263Executed before executing any of the tests.
264
265        \termitem{cleanup}{:Goal}
266Executed after completion of all tests in the unit.
267
268	\termitem{sto}{+Terms}
269Specify default for subject-to-occurs-check mode. See \secref{unitbox}
270for details on the sto option.
271    \end{description}
272\end{description}
273
274
275
276%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
277\subsection{Writing the test body}
278\label{sec:testbody}
279
280The test-body is ordinary Prolog code. Without any options, the body
281must be designed to succeed \emph{deterministically}. Any other result
282is considered a failure. One of the options \const{fail}, \const{true},
283\const{throws}, \const{all} or \const{set} can be used to specify a
284different expected result. See \secref{unitbox} for details.  In this
285section we illustrate typical test-scenarios by testing SWI-Prolog
286built-in and library predicates.
287
288\subsubsection{Testing deterministic predicates}
289\label{sec:testdet}
290
291Deterministic predicates are predicates that must succeed exactly once
292and, for well behaved predicates, leave no choicepoints. Typically they
293have zero or more input- and zero or more output arguments. The test
294goal supplies proper values for the input arguments and verifies the
295output arguments. Verification can use test-options or be explicit in
296the body.  The tests in the example below are equivalent.
297
298\begin{code}
299test(add) :-
300	A is 1 + 2,
301	A =:= 3.
302
303test(add, [true(A =:= 3)]) :-
304	A is 1 + 2.
305\end{code}
306
307The test engine verifies that the test-body does not leave a
308choicepoint.  We illustrate that using the test below:
309
310\begin{code}
311test(member) :-
312	member(b, [a,b,c]).
313\end{code}
314
315Although this test succeeds, member/2 leaves a choicepoint which is
316reported by the test subsystem.  To make the test silent, use one of
317the alternatives below.
318
319\begin{code}
320test(member) :-
321	member(b, [a,b,c]), !.
322
323test(member, [nondet]) :-
324	member(b, [a,b,c]).
325\end{code}
326
327\subsubsection{Testing semi-deterministic predicates}
328\label{sec:testsemidet}
329
330Semi-deterministic predicates are predicates that either fail or succeed
331exactly once and, for well behaved predicates, leave no choicepoints.
332Testing such predicates is the same as testing deterministic
333predicates.  Negative tests must be specified using the option
334\const{fail} or by negating the body using \verb$\+/1$.
335
336\begin{code}
337test(is_set) :-
338	\+ is_set([a,a]).
339
340test(is_set, [fail]) :-
341	is_set([a,a]).
342\end{code}
343
344
345\subsubsection{Testing non-deterministic predicates}
346\label{sec:testnondet}
347
348Non-deterministic predicates succeed zero or more times.  Their results
349are tested either using findall/3 or setof/3 followed by a value-check
350or using the \const{all} or \const{set} options.  The following are
351equivalent tests:
352
353\begin{code}
354test(member) :-
355	findall(X, member(X, [a,b,c]), Xs),
356	Xs == [a,b,c].
357
358test(member, all(X == [a,b,c])) :-
359	member(X, [a,b,c]).
360\end{code}
361
362\subsubsection{Testing error conditions}
363\label{sec:testerror}
364
365Error-conditions are tested using the option \term{throws}{Error} or
366by wrapping the test in a catch/3.  The following tests are equivalent:
367
368\begin{code}
369test(div0) :-
370     catch(A is 1/0, error(E, _), true),
371     E =@= evaluation_error(zero_divisor).
372
373test(div0, [error(evaluation_error(zero_divisor))]) :-
374     A is 1/0.
375\end{code}
376
377
378\subsubsection{One body with multiple tests using assertions}
379\label{sec:testassertion}
380
381PlUnit is designed to cooperate with the assertion/1 test provided by
382library(debug).\footnote{This integration was suggested by G\"unter
383Kniesel.} If an assertion fails in the context of a test, the test
384framework reports this and considers the test failed, but does not trap
385the debugger. Using assertion/1 in the test-body is attractive for two
386scenarios:
387
388\begin{itemize}
389    \item Confirm that multiple claims hold.  Where multiple claims
390	  about variable bindings can be tested using the == option
391	  in the test header, arbitrary boolean tests, notably about
392	  the state of the database, are harder to combine.  Simply
393	  adding them in the body of the test has two disadvantages:
394	  it is less obvious to distinguish the tested code from the
395	  test and if one of the tests fails there is no easy way to
396	  find out which one.
397    \item Testing `scenarios' or sequences of actions.  If one step
398          in such a sequence fails there is again no easy way to find
399	  out which one.  By inserting assertions into the sequence
400	  this becomes obvious.
401\end{itemize}
402
403Below is a simple example, showing two failing assertions. The first
404line of the failure message gives the test. The second reports the
405location of the assertion.\footnote{If known. The location is determined
406by analysing the stack. The second failure shows a case where this does
407not work because last-call optimization has already removed the context
408of the test-body.} If the assertion call originates from a different
409file this is reported appropriately. The last line gives the actually
410failed goal.
411
412\begin{code}
413:- begin_tests(test).
414
415test(a) :-
416	A is 2^3,
417	assertion(float(A)),
418	assertion(A == 9).
419
420:- end_tests(test).
421\end{code}
422
423\begin{code}
424?- run_tests.
425% PL-Unit: test
426ERROR: /home/jan/src/pl-devel/linux/t.pl:5:
427	test a: assertion at line 7 failed
428	Assertion: float(8)
429ERROR: /home/jan/src/pl-devel/linux/t.pl:5:
430	test a: assertion failed
431	Assertion: 8==9
432. done
433% 2 assertions failed
434\end{code}
435
436
437%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
438\section{Using separate test files}
439\label{sec:testfiles}
440
441Test-units can be embedded in normal Prolog source-files. Alternatively,
442tests for a source-file can be placed in another file alongside the file
443to be tested. Test files use the extension \fileext{plt}. The predicate
444load_test_files/1 can load all files that are related to source-files
445loaded into the current project.
446
447
448%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
449\section{Running the test-suite}
450\label{sec:pldoc-running}
451
452At any time, the tests can be executed by loading the program and
453running run_tests/0 or run_tests(+Unit).
454
455\begin{description}
456    \predicate{run_tests}{0}{}
457Run all test-units.
458
459    \predicate{run_tests}{1}{+Spec}
460Run only the specified tests.  \arg{Spec} can be a list to run multiple
461tests.  A single specification is either the name of a test unit or
462a term <Unit>:<Tests>, running only the specified test.  <Tests> is
463either the name of a test or a list of names. Running particular
464tests is particularly useful for tracing a test:%
465\footnote{Unfortunately the body of the test is called through
466meta-calling, so it cannot be traced. The called user-code can be traced
467normally though.}
468
469\begin{code}
470?- gtrace, run_tests(lists:member).
471\end{code}
472\end{description}
473
474To identify nonterminating tests, interrupt the looping process with
475\emph{Control-C}. The test name and location will be displayed.
476
477%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
478\section{Tests and production systems}
479\label{sec:state}
480
481Most applications do not want the test-suite to end up in the
482final application.  There are several ways to achieve this.  One
483is to place all tests in separate files and not to load the tests
484when creating the production environment.  Alternatively, use the
485directive below before loading the application.
486
487\begin{code}
488:- set_test_options([load(never)]).
489\end{code}
490
491
492%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
493\section{Controlling the test suite}
494\label{sec:options}
495
496\begin{description}
497    \predicate{set_test_options}{1}{+Options}
498Defined options are:
499
500\begin{description}
501    \termitem{load}{+Load}
502Determines whether or not tests are loaded. When \const{never},
503everything between begin_tests/1 and end_tests/1 is simply ignored.
504When \const{always}, tests are always loaded.  Finally, when using
505the default value \const{normal}, tests are loaded if the code is
506not compiled with optimisation turned on.
507
508    \termitem{run}{+Run}
509Specifies when tests are run. Using \const{manual}, tests can only be
510run using run_tests/0 or run_tests/1. Using \const{make}, tests will be
511run for reloaded files, but not for files loaded the first time. Using
512\const{make(all)} make/0 will run all test-suites, not only those that
513belong to files that are reloaded.
514
515    \termitem{silent}{+Bool}
516When \const{true} (default is \const{false}), send informational
517messages using the `silent' level.  In practice this means there
518is no output except for errors.
519
520    \termitem{sto}{+Bool}
521When \const{true} (default \const{false}), assume tests are not subject
522to occurs check (non-STO) and verify this if the Prolog implementation
523supports testing this.
524\end{description}
525
526    \predicate{load_test_files}{1}{+Options}
527Load \fileext{plt} test-files that belong to the currently loaded
528sources.
529
530    \predicate{running_tests}{0}{}
531Print all currently running tests to the terminal.  It can be used
532to find running thread in multi-threaded test operation or find the
533currently running test if a test appears to be blocking.
534
535    \predicate{test_report}{1}{+What}
536Print report on the executed tests.  \arg{What} defines the type
537of report.  Currently this only supports \const{fixme}, providing
538details on how the fixme-flagged tests proceeded.
539\end{description}
540
541
542%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
543\section{Auto-generating tests}
544\label{sec:wizard}
545
546Prolog is an interactive environment. Where users of non-interactive
547systems tend to write tests as code, Prolog developers tend to run
548queries interactively during development. This interactive testing is
549generally faster, but the disadvantage is that the tests are lost at the
550end of the session. The test-wizard tries to combine the advantages. It
551collects toplevel queries and saves them to a specified file.  Later,
552it extracts these queries from the file and locates the predicates that
553are tested by the queries.  It runs the query and creates a test clause
554from the query.
555
556Auto-generating test cases is experimentally supported through the
557library \pllib{test_wizard}. We briefly introduce the functionality
558using examples. First step is to log the queries into a file. This is
559accomplished with the commands below. \file{Queries.pl} is the name in
560which to store all queries. The user can choose any filename for this
561purpose.   Multiple Prolog instances can share the same name, as data
562is appended to this file and write is properly locked to avoid file
563corruption.
564
565\begin{code}
566:- use_module(library(test_wizard)).
567:- set_prolog_flag(log_query_file, 'Queries.pl').
568\end{code}
569
570Next, we will illustrate using the library by testing the predicates
571from library \pllib{lists}.  To generate test cases we just make calls
572on the terminal.  Note that all queries are recorded and the system will
573select the appropriate ones when generating the test unit for a
574particular module.
575
576\begin{code}
577?- member(b, [a,b]).
578Yes
579?- reverse([a,b], [b|A]).
580A = [a] ;
581No
582\end{code}
583
584Now we can generate the test-cases for the module list using
585make_tests/3:
586
587\begin{code}
588?- make_tests(lists, 'Queries.pl', current_output).
589:- begin_tests(lists).
590
591test(member, [nondet]) :-
592        member(b, [a, b]).
593test(reverse, [true(A==[a])]) :-
594        reverse([a, b], [b|A]).
595
596:- end_tests(lists).
597\end{code}
598
599%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
600\section{Coverage analysis}
601\label{sec:cover}
602
603An important aspect of tests is to know which parts of program
604is used (\emph{covered}) by the tests.  An experimental analysis
605is provided by the library \pllib{test_cover}.
606
607\begin{description}
608    \predicate{show_coverage}{1}{:Goal}
609Run \arg{Goal} and write a report on which percentage of the clauses in
610each file are used by the program and which percentage of the clauses
611always fail.
612
613    \predicate{show_coverage}{2}{:Goal, +Modules}
614As show_coverage/1, but only report on modules in the list
615\arg{Modules}.
616\end{description}
617
618We illustrate this here using CHAT, a natural language question and
619answer application by David H.D. Warren and Fernando C.N. Pereira.
620
621\begin{code}
6221 ?- show_coverage(test_chat).
623Chat Natural Language Question Answering Test
624...
625
626==================================================================
627                         Coverage by File
628==================================================================
629File                                        Clauses    %Cov %Fail
630==================================================================
631/staff/jan/lib/prolog/chat/xgrun.pl                5   100.0   0.0
632/staff/jan/lib/prolog/chat/newg.pl               186    89.2  18.3
633/staff/jan/lib/prolog/chat/clotab.pl              28    89.3   0.0
634/staff/jan/lib/prolog/chat/newdic.pl             275    35.6   0.0
635/staff/jan/lib/prolog/chat/slots.pl              128    74.2   1.6
636/staff/jan/lib/prolog/chat/scopes.pl             132    70.5   3.0
637/staff/jan/lib/prolog/chat/templa.pl              67    55.2   1.5
638/staff/jan/lib/prolog/chat/qplan.pl              106    75.5   0.9
639/staff/jan/lib/prolog/chat/talkr.pl               60    20.0   1.7
640/staff/jan/lib/prolog/chat/ndtabl.pl              42    59.5   0.0
641/staff/jan/lib/prolog/chat/aggreg.pl              47    48.9   2.1
642/staff/jan/lib/prolog/chat/world0.pl             131    71.8   1.5
643/staff/jan/lib/prolog/chat/rivers.pl              41   100.0   0.0
644/staff/jan/lib/prolog/chat/cities.pl              76    43.4   0.0
645/staff/jan/lib/prolog/chat/countr.pl             156   100.0   0.0
646/staff/jan/lib/prolog/chat/contai.pl             334   100.0   0.0
647/staff/jan/lib/prolog/chat/border.pl             857    98.6   0.0
648/staff/jan/lib/prolog/chat/chattop.pl            139    43.9   0.7
649==================================================================
650\end{code}
651
652Using \verb$?- show_coverage(run_tests).$, this library currently only
653shows some rough quality measure for test-suite.  Later versions should
654provide a report to the developer identifying which clauses are covered,
655not covered and always failed.
656
657
658%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
659\section{Portability of the test-suite}
660\label{sec:porting}
661
662One of the reasons to have tests is to simplify migrating code between
663Prolog implementations. Unfortunately creating a portable test-suite
664implies a poor integration into the development environment. Luckily,
665the specification of the test-system proposed here can be ported quite
666easily to most Prolog systems sufficiently compatible to SWI-Prolog to
667consider porting your application. Most important is to have support for
668term_expansion/2.
669
670In the current system, test units are compiled into sub-modules of the
671module in which they appear.  Few Prolog systems allow for sub-modules
672and therefore ports may have to fall-back to inject the code in the
673surrounding module.  This implies that support predicates used inside
674the test unit should not conflict with predicates of the module being
675tested.
676
677
678%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
679\subsection{PlUnit on SICStus}
680\label{sec:sicstus}
681
682The directory of \file{plunit.pl} and \file{swi.pl} must be in the
683\const{library} search-path.  With PLUNITDIR replaced accordingly,
684add the following into your \file{.sicstusrc} or \file{sicstus.ini}.
685
686\begin{code}
687:- set_prolog_flag(language, iso). % for maximal compatibility
688library_directory('PLUNITDIR').
689\end{code}
690
691The current version runs under SICStus 3.  Open issues:
692
693\begin{itemize}
694
695    \item Some messages are unformatted because SICStus 3 reports
696          all ISO errors as instantiation errors.
697
698    \item Only \file{plunit.pl}.  Both coverage analysis and the test
699	  generation wizard currently require SWI-Prolog.
700
701    \item The \const{load} option \const{normal} is the same as \const{always}.
702	  Use \exam{set_test_options(load, never)} to avoid loading the
703	  test suites.
704
705    \item The \const{run} option is not supported.
706
707    \item Tests are loaded into the enclosing module instead of a separate
708          test module. This means that predicates in the test module must
709	  not conflict with the enclosing module, nor with other test
710	  modules loaded into the same module.
711\end{itemize}
712
713
714%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
715\section{Motivation of choices}
716\label{sec:plunit-motivation}
717
718\subsection*{Easy to understand and flexible}
719
720There are two approaches for testing. In one extreme the tests are
721written using declarations dealing with setup, cleanup, running and
722testing the result. In the other extreme a test is simply a Prolog goal
723that is supposed to succeed. We have chosen to allow for any mixture of
724these approaches. Written down as test/1 we opt for the simple
725succeeding goal approach. Using options to the test the user can choose
726for a more declarative specification.  The user can mix both approaches.
727
728The body of the test appears at the position of a clause-body. This
729simplifies identification of the test body and ensures proper layout and
730colouring support from the editor without the need for explicit support
731of the unit test module. Only clauses of test/1 and test/2 may be marked
732as non-called in environments that perform cross-referencing.
733
734%\subsection*{Well integrated}
735
736\printindex
737
738\end{document}
739
740