The executable specification of Standard Prolog A manual Version 1.0 April 1996 CONTENTS 1 Introduction 2 Using the executable specification 2.1 Preparations 2.2 Facilities 2.3 Options 2.4 Flags 2.5 Completeness, limitations and bugs 3 Examples 3.1 Getting started 3.2 run_subs(Program) 3.3 run_forest(Program) 3.4 Testing simple programs 3.5 Testing built-in predicates 3.6 Testing input-output 4 Testing Built-in predicates - The run_bip/1 predicate 4.1 functor/3 4.2 current_predicate/1 1- INTRODUCTION Pierre Deransart (INRIA) and AbdelAli Ed-Dbali (University of Orleans) have produced an executable version of the formal definition of ISO standard Prolog (Informative Annex). These notes describe the executable specification of standard Prolog. It has been designed with facilities to help test, design, and improve the standard. Sample tests of built-in predicates are included in the files of directory bips (some copied from standard Prolog document). Users are invited to send the authors further tests together with the expected results. Remember that an executable specification is not a specification. In particular the results will depend on the processor which you are using. The executable specification has been tested on SICStus and SWI Prolog processors, but it is likely to have the same behaviour on several other processors because it uses standard parts of the above processors. Note also that the executable specification is a specific implemen- tation of the formal one. In particular you may be surprised by the behaviour of unification which conforms to the standard, but is unde- fined in some cases. The executable specification provides a valuable consistency check on the standard because it links the descriptions of the built-in predicates in chapter 5 of the "Prolog: The Standard" book (and section 8 of the International Standard document) with the formal semantics in annex A (of the same document). When all the examples for a predicate give the expected result, we can have confidence that this part of the standard has been defined consistently. The code of executable specification is very close to the text of formal one. Thus it is usually quicker and sounder to test a goal using it rather than to try to figure out what happens for a particular goal with the text of the formal specification. Notes: 1. This executable specification comes with ABSOLUTELY NO WARRANTY. It is an inefficient Prolog meta-interpreter. 2. Updated version of executable specification of standard PROLOG can be received by anonymous ftp form: ftp-lifo.univ-orleans.fr:/pub/Users/eddbali/SdProlog 3. Bug reports, interesting results, comments or suggestions of modification are welcome: eddbali@lifo.univ-orleans.fr. 2 - USING THE EXECUTABLE SPECIFICATION 2.1 - PREPARATIONS To run the executable specification you need the following text files: 1. Prolog source files: EXE-SPEC.PL (Prolog translation of the formal specification: the kernel and built-in predicates definitions), L-PRED.PL (all undefined features used in the formal specification: arithmetics, unification, ...), INTERF.PL (environment to use easily the executable specification) EX-TEST.PL (special environment to test all the examples in bips files), SYNTAX.PL (syntactic analyser of ISO Standard Prolog texts and terms), UTIL.PL (other features like negation by failure, ...) and MAKE (to load the previous files). 2. EXAMPLES: directory containing some standard Prolog source files you want to test. It is recommended that you test only very short examples. 3. BIP-EX: directory containing sample test files. There is one file for each built-in predicate. The file corresponding to a built-in predicate has the same name, except for some cases where another mnemonic name is used (e.g. "arith-eq" instead of (=:=)/2, or "not_provable" instead of ('\+')/1, ...). To start the executable specification, prepare some files with examples (written in standard Prolog style) and consult "make" from Prolog (see 3.1). 2.2 - Facilities At present you can do the following: 1. Look at answer substitutions: call: run_subs(Program_File_Name). It behaves like a Prolog session where the consulted program is Program_File_Name. You will be asked for goals. The results are "success", "failure", a system error or a substitutions. For an example, see 3.2 2. Look at the search tree: call: run_forest(Program_File_Name). You will be asked for goals and the search tree will be displayed. This should be self-explanatory. But remember that the nodes are numbered in a dewey-like notation. Do not worry if you need to wait some time before results are displayed: the search tree is completely computed before any output. The computation introduces other goals than thoses given by the user. We will try to give an explanation in section 3.3. 3. Test a sample of examples for a given built-in predicate: call: run_bip(Bip_File_Name). This is a utility predicate: all the examples of the built-in predicate will be tested and compared with the expected result. If you get INTENDED RESULT the example is conforming. If you get an other message there is a deviation. For an example, see 4. 4. Stop the current session: type instead of a goal ^d or the atom end_of_file. 2.3 - OPTIONS The execution of the runable specification can be controlled with various options: 1. After a 'run_subs' or a 'run_forest' goal you can give the goal: list_prog. to remember the contents of the file (database) being processed. 2. To have a short help, give (at the top level) the goal: help_me. 3. To limit the computation in the unification algorithm. There is a limit (40 by default) on number of recursions in unification. This prevents the executable specification from looping in the case of a non-terminating unification. If the default value is too small, it may be increased by giving the goal: max_loop(Integer). 4. To test a built-in predicate (wich not need a database) simply, call: bip_subs. or bip_forest. and give goals (see 3.1). Built-in predicates can be tested in this way, but it is usually more convenient to prepare your examples in a bip file. It is also possible to introduce examples as a list whose elements are in the following order (see 4): (a) A goal, (b) (optional) A program, entered as a list of clauses or by its file name. Example: [(nat(0) :- true), (nat(suc(X)) :- nat(X))] or program(natural) where 'natural' is the file containing the definition of 'nat'. (c) An expected answer: - A list of answer substitutions in the order in which they are expected. The operator substitution is: <--. Example: [[Var1 <-- Term11, ..., VarN <-- Term1N], [Var1 <-- term21, ..., VarN <-- Term2N], ...] or - "success" if a success with an empty answer substitution is expected, or - "failure" if a finitely failed search tree is expected, or - error-identifier which is a term identifing the expected error. Examples: instantiation_error, type_error(atom, 1), permission_error(modify, static_procedure, foo/2), ..., or - "impl_dep" or "impl_defined" or "undefined" if the expected behaviour is implementation dependent or implementation defined or undefined. Examples: [ (X=1;X=2),[ [X <-- 1], [X <-- 2] ] ]. [ 1 =:= 1.0, success ]. [ 2 < 1, failure ]. [ functor(A,B,3), instantiation_error ]. [ f(X,1) = f(a(X),2), undefined ]. [ f(X,1) @< f(Y,2), impl_dep ]. 2.4 - FLAGS Three flags determine the environment while running the executable specification. Each flag is represented by a predicate defined by a single fact, and whose argument defines the value of the flag. 1. max_loop/1 (see 2.3). 2. sto_test/1 to test whether unification is "subject to occur check" (STO). The flag has a value 'on' or 'off'. When the flag is 'on' the executable specification computes whether or not unification of two terms is implementation dependent at every invocation of unification. This obviously slows the execution but provides a means of checking that a program without input is standard conforming with respect to unification. 3. In the case of running "run_subs" predicate, you can see also the contains of input and output streams by turning 'on' the display_io flag (call: display_io(on)). To turn it 'off', simply call: display_io(off) (see 3.1). 2.5 - COMPLETENESS, LIMITATIONS and BUGS The executable specification successfully emulates very large parts of standard Prolog - including some of the controversial, for example 1. a logical view of the database (see 3.4). 2. Unification (see 2.4) But there are some limitations and bugs: 1. The executable specification has been designed as closely as possible to the formal one. It is extremely inefficient - do not try big programs! 2. Some built-in predicates are NOT YET defined: char_conversion/2, current_char_conversion/2, flush_output/0/1, set_stream_position/2, stream_property/2. The follwing directives are NOT YET defined: multifile/1, 3. Bugs are essentialy on input/output built-in predicates. The following bugs willbe fixed in the next version: - read/1/2 and read_term/2/3 work on user_input stream only. - read options (variables, variable_names and singletons) are not yet supported. - The write option quoted(true) quotes all atoms in a term. - input/output are tested only on text streams. Operations on binary streams are specified but never been tested on real binary stream. - As it is defined in the formal specification, a database is a local data-structure. The database is modified during a database updating goal, but this change is not visible in the rest of the session. However, streams are global data-structres and works as usual. 3 - EXAMPLES Comments have been inserted in the listing as annotations. 3.1 - GETTING STARTED my_machine% prolog SICStus 2.1 #8: Mon Apr 1 12:41:57 MET DST 1996 | ?- [make]. % consulting make-file ... make consulted, 14990 msec 395232 bytes yes | ?- help_me. Executable Specification Help ============================= - run_subs(Prog): gives substitution responses when executing goals on Prog - run_forest(Prog): gives the search-tree when executing goals on Prog - run_subs: equivalent to run_subs without program (usefull to test some BIPs) - run_forest: equivalent to run_forest without program (usefull to test some BIPs) - run_bip(ExamplesBipFile): test examples in ExamplesBipFile (usefull to test a set of examples BIP) yes | ?- run_subs. [] goal ?- findall(X, (X=1; X=2), S). findall(A, (A = 1 ; A = 2), B) % The goal is reprinted with a renaming % of variables (A,B,....). This is because % the terms have been translated into % the abstract syntax B <-- [1, 2] % The goal succeeds and unifies B with [1, 2] success ------- [] goal ?- ... etc [] goal ?- ^d yes | ?- 3.2 - run_subs(Program) | ?- run_subs('examples/plus'). [examples/plus] goal ?- % The name of the program is indicated during the session [examples/plus] goal ?- list_prog. plus(0,A,A):-true plus(s(A),B,s(C)):-plus(A,B,C) end --------- [examples/plus] goal ?- plus(0,s(0),s(0)). plus(0,s(0),s(0)) success ------- % success with empty substitution [examples/plus] goal ?- plus(0,s(0),X). plus(0,s(0),A) % The goal is reprinted A <-- s(0) success ------- % The goal succeeds and unifies A with s(0) [examples/plus] goal ?- plus(X,Y,s(0)). plus(A,B,s(0)) A <-- 0 % All substitutions are given B <-- s(0) success ------- A <-- s(0) B <-- 0 success ------- [examples/plus] goal ?- plus(0,s(0),s(s(0))). plus(0,s(0),s(s(0))) failure ------- % The goal fails [examples/plus] goal ?- ^d % To quit the session 3.3 - run_forest(Program) This is the same as run_subs(Program) except that the search tree is printed for each resolution. | ?- run_forest('examples/plus'). [examples/plus] goal ?- plus(0,s(0),X). ================= forest is ==================== ::::::::::::: | Id: % This is the root of the search-tree ::::::::::::: Goal: catch(call(plus(0, s(0), A)), B, special_pred(system_error_action(B))) % The initial goal is enveloped in the built-in catch/3 in order to catch a % possibly error raised during the execution of the goal. Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- % The program is displayed at each node to show its evolution on executing % database BIPs like assert, retract and abolish. Input(s) and output(s): user_input: | user_output: | % The input and output streams are displayed also. "user_input" and % "user_output" in this example are always empty. The character "|" marks % the point at which input and output would take place. local substitution: success ------- % The substitution resulting from executing the parent node (here empty) ::::::::::::: | Id: 1 ::::::::::::: Goal: call(call(plus(0, s(0), A))), inactivate( ), true Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- Input(s) and output(s): user_input: | user_output: | local substitution: success ------- ::::::::::::: | Id: 11 ::::::::::::: Goal: call(plus(0, s(0), A)), inactivate( ), true Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- Input(s) and output(s): user_input: | user_output: | local substitution: success ------- ::::::::::::: | Id: 111 ::::::::::::: % Nodes are numbered in a dewey-like notation. This the first child of % node 11 Goal: plus(0, s(0), A), inactivate( ), true Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- Input(s) and output(s): user_input: | user_output: | local substitution: success ------- ::::::::::::: | Id: 1111 ::::::::::::: Goal: true, inactivate( ), true % ---- ---- % The first clause " plus(0,A,A) :- true" is chosen to construct this node. % After renaming of variables, the clause become: plus(0,A2,A2) :- true. Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- Input(s) and output(s): user_input: | user_output: | local substitution: % The result of unifying "plus(0,s(0),A)" and the renamed fact: % "plus(0,A2,A2)" A2 <-- s(0) A <-- s(0) success ------- ::::::::::::: | Id: 11111 ::::::::::::: Goal: inactivate( ), true % inactivate( ) removes the catcher point from the root (no error). Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- Input(s) and output(s): user_input: | user_output: | local substitution: success ------- ::::::::::::: | Id: 111111 ::::::::::::: Goal: true Program: plus(0, A, A) :- true plus(s(A), B, s(C)) :- plus(A, B, C) end --------- Input(s) and output(s): user_input: | user_output: | Local substitution: success ------- Answer substitution: % The compound substitution restricted to the variables in the goal. A <-- s(0) success ------- SUCCES NODE ================================================ [examples/plus] goal ?- ^d % End of the session 3.4 - TESTING SIMPLE PROGRAMS It is possible to test simple programs where it is not worthwhile creating a file by loading each clause and then calling run_subs(user) or run_forest(user). | ?- run_subs(user). |: p(1):-assertz((p(3) :- true)). |: p(2):-assertz((p(4) :- true)). |: ^d [user] goal ?- p(X). p(A) % This is a substitution given in the case of A <-- 1 % logical database update view. success ------- % The Immediate database update view will give: A <-- 2 % A <-- 1; A <-- 2; A <-- 3 and A <-- 4 success ------- [user] goal ?- ... 3.5 - TESTING BUILT-IN PREDICATES When you are only testing built-in predicates, an empty program is sufficient and gives the fastest possible execution. The tests are made simpler using the predicates run_subs/0 and run_forest/0. | ?- run_subs. [] goal ?- functor(f(a,X),Y,Z). functor(f(a, A), B, C) B <-- f C <-- 2 success ------- [] goal ?- functor(X,f,3). functor(A, f, 3) A <-- f(_A1, _A2, _A3) success ------- [] goal ?- T=..[f,a,b,c]. A =.. [f, a, b, c] A <-- f(a, b, c) success ------- [] goal ?- arg(1,f(a,X),Y). arg(1, f(a, A), B) B <-- a success ------- [] goal ?- ^d 3.6 - TESTING INPUT/OUTPUT There are two standard streams for input and output: user_input and user_output. You can add to the environment any stream you want by giving the goal open/3 or open/4. | ?- display_io(on). % To display input and output streams yes | ?- run_subs. [user] goal ?- open(my_file,read,S). % my_file contains the single word: 'specification' open(my_file, read, A) A <-- my_file success ------- my_file: |specification user_input: | user_output: | [user] goal ?- get_char(X). get_char(A) A <-- s success ------- my_file: s|pecification user_input: | user_output: | [user] goal ?- ^d | ?- run_subs. [user] goal ?- write_term(f(2, X+'$VAR'(6)),[ignore_ops(true),numbervars(true)]). write_term(f(2, A + $VAR(6)), [ignore_ops(true), numbervars(true)]) success ------- user_input: | user_output: f(2, +(A, G))| [user] goal ?- ^d yes 4 - TESTING BUILT-IN PREDICATES: The run_bip/1 predicate 4.1 - functor/3 It is possible to test Built-in predicates examples by giving a file wich contains terms as described in section 2.3. The test is done by the run_bip/1 predicate. This predicate is not suitable for input/output built-in predicates. In this case the relevent result is a side effect. If the bip file 'functor' is: (Note that some erroneous expected answers are given just to see the behaviour of the 'run_bip' predicate.) [functor(foo(a,b,c),foo,3), % The goal success]. % The "expected" answer [functor(foo(a,b,c),X,Y), [[X <-- foo, Y <-- 2]]]. % Must instantiate Y by 3 [functor(X,foo,3), [[X <-- foo(A,B,C)]]]. [functor(X,foo,0), [[X <-- foo]]]. [functor(mats(A,B),A,B), [[A <-- mats,B <-- 2]]]. [functor(foo(a),foo,2), success]. % Must fail [functor(foo(a),fo,1), failure]. [functor(1,X,Y), [[X <-- 1,Y <-- 0]]]. [functor(X,1.1,0), [[X <-- 1.1]]]. [functor([_|_],'.',2), failure]. % Must succeed [functor([],[],0), success]. [functor(X, Y, 3), instantiation_error]. [functor(X, foo, N), instantiation_error]. [functor(X, foo, a), failure]. % type_error(integer,a) expected [functor(F, 1.5, 1), type_error(atom,1.5)]. [functor(F,foo(a),1), type_error(atomic,foo(a))]. [(current_prolog_flag(max_arity,A), X is A + 1, % 3 goals brackted functor(T, foo, X)), representation_error(max_arity)]. [functor(T, foo, -1), domain_error(not_less_than_zero,-1)]. The test will give: | ?- run_bip('bip-ex/functor'). Warning : The STO test flag is ON =================================== ------------------------------------------- Goal : functor(foo(a, b, c), foo, 3) Intended result : success Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(foo(a, b, c), A, B) Intended result : A <-- foo B <-- 2 Specif result : The substitution found is : A <-- foo B <-- 3 success ------- ------------------------------------------- ------------------------------------------- Goal : functor(A, foo, 3) Intended result : A <-- foo(B, C, D) Specif result : The substitution found is : A <-- foo(_A1, _A2, _A3) success ------- ------------------------------------------- ------------------------------------------- Goal : functor(A, foo, 0) Intended result : A <-- foo Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(mats(A, B), A, B) Intended result : A <-- mats B <-- 2 Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(foo(a), foo, 2) Intended result : success Specif result : Must fail ------------------------------------------- ------------------------------------------- Goal : functor(foo(a), fo, 1) Intended result : failure Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(1, A, B) Intended result : A <-- 1 B <-- 0 Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(A, 1.1, 0) Intended result : A <-- 1.1 Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor([A|B], ., 2) Intended result : failure Specif result : Must success ------------------------------------------- ------------------------------------------- Goal : functor([], [], 0) Intended result : success Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(A, B, 3) Intended result : instantiation_error Specif result : system_error_action: instantiation_error INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(A, foo, B) Intended result : instantiation_error Specif result : system_error_action: instantiation_error INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(A, foo, a) Intended result : failure Specif result : system_error_action: type_error(integer, a) Goal in error : type_error(integer, a) ------------------------------------------- ------------------------------------------- Goal : functor(A, 1.5, 1) Intended result : type_error(atom, 1.5) Specif result : system_error_action: type_error(atom, 1.5) INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(A, foo(a), 1) Intended result : type_error(atomic, foo(a)) Specif result : system_error_action: type_error(atomic, foo(a)) INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_prolog_flag(max_arity, A), B is A + 1, functor(C, foo, B) Intended result : representation_error(max_arity) Specif result : system_error_action: representation_error(max_arity) INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : functor(A, foo, -1) Intended result : domain_error(not_less_than_zero, -1) Specif result : system_error_action: domain_error(not_less_than_zero, -1) INTENDED RESULT ------------------------------------------- 4.2 - current__predicate/1 [current_predicate(dog/0), program('the_program'), success]. [current_predicate(current_predicate/1), failure]. [current_predicate(elk/Arity), program('the_program'), [[Arity <-- 1]]]. [current_predicate(Name/1), program('the_program'), [[Name <-- elk], [Name <-- insect]]]. [current_predicate(Pred), program('the_program'), [[Pred <-- cat/0],[Pred <-- dog/0], [Pred <-- elk/1],[Pred <-- legs/2], [Pred <-- insect/1]]]. [current_predicate(4), type_error(predicate_indicator, 4)]. [current_predicate(dog), type_error(predicate_indicator, dog)]. [current_predicate(0/dog), type_error(predicate_indicator, 0/dog)]. The file 'the_program' has the following contents: :- dynamic(cat/0). :- dynamic(dog/0). :- dynamic(legs/2). :- dynamic(insect/1). cat. dog :- true. elk(X) :- moose(X). legs(A,6) :- insect(A). legs(A,7) :- A, call(A). insect(ant). insect(bee). | ?- run_bip('bip-ex/current_predicate'). Warning : The STO test flag is ON =================================== ------------------------------------------- Goal : current_predicate(dog / 0) Program : insect(ant) :- true insect(bee) :- true legs(A, 6) :- insect(A) legs(A, 7) :- call(A), call(A) elk(A) :- moose(A) dog :- true cat :- true end --------- Intended result : success Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_predicate(current_predicate / 1) Intended result : failure Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_predicate(elk / A) Program : insect(ant) :- true insect(bee) :- true legs(A, 6) :- insect(A) legs(A, 7) :- call(A), call(A) elk(A) :- moose(A) dog :- true cat :- true end --------- Intended result : A <-- 1 Specif result : INTENDED RESULT ------------------------------------------- Goal : current_predicate(A / 1) Program : insect(ant) :- true insect(bee) :- true legs(A, 6) :- insect(A) legs(A, 7) :- call(A), call(A) elk(A) :- moose(A) dog :- true cat :- true end --------- Intended result : A <-- elk ~~~~~~~~~~~~~~~~ A <-- insect ~~~~~~~~~~~~~~~~ Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_predicate(A) Program : insect(ant) :- true insect(bee) :- true legs(A, 6) :- insect(A) legs(A, 7) :- call(A), call(A) elk(A) :- moose(A) dog :- true cat :- true end --------- Intended result : A <-- cat / 0 ~~~~~~~~~~~~~~~~ A <-- dog / 0 ~~~~~~~~~~~~~~~~ A <-- elk / 1 ~~~~~~~~~~~~~~~~ A <-- legs / 2 ~~~~~~~~~~~~~~~~ A <-- insect / 1 Specif result : INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_predicate(4) Intended result : type_error(predicate_indicator, 4) Specif result : system_error_action: type_error(predicate_indicator, 4) INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_predicate(dog) Intended result : type_error(predicate_indicator, dog) Specif result : system_error_action: type_error(predicate_indicator, dog) INTENDED RESULT ------------------------------------------- ------------------------------------------- Goal : current_predicate(0 / dog) Intended result : type_error(predicate_indicator, 0 / dog) Specif result : system_error_action: type_error(predicate_indicator, 0 / dog) INTENDED RESULT ------------------------------------------- Note - The run_bip/1 predicate is also useful to test any goal (not necessarlly a bip) on any program. Example: [ (L = [a, b], length(L, X)), [(length([],0) :- true), (length([E_L],N) :- length(L, N1) , N is N1 + 1)], [[L <- [a, b], X <- 2]] ]. 25