View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Henk Vandecasteele
    4    E-mail:        henk.vandecasteele@cs.kuleuven.ac.be
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): Public domain
    7*/
    8
    9/** <module> BIM compatibility layer
   10
   11This file contains some predicates that   are  defined in BIM-prolog and
   12not in SWI-prolog (or at least not  with   the  same meaning). In case a
   13predicate has a different meaning in  SWI-prolog   and  in proLog by BIM
   14renaming is done.  Remark  that  some   predicates  are  only  partially
   15covered, feel free to add.
   16
   17@author  Henk Vandecasteele
   18         Departement Computerwetenschappen
   19         Katholiek Universiteit Leuven
   20         Celestijnenlaan 200A
   21         3001 Heverlee
   22         BELGIUM
   23         henk.vandecasteele@cs.kuleuven.ac.be
   24*/
   25
   26:- module(bim,
   27       [ please/2,
   28	 cputime/1,
   29	 setdebug/0,
   30	 bim_erase/1,			% BIM-compatible erase/1
   31	 bim_erase/2,			% BIM-compatible erase/2
   32	 rerecord/2,
   33	 erase_all/1,
   34	 (record)/3,
   35	 bim_recorded/3,			% BIM-compatible recorded/3
   36	 inttoatom/2,
   37	 atomconcat/3,
   38	 update/1,
   39	 printf/2,
   40	 bim_random/1,			% conflicts with library(random)
   41	 index/2,
   42	 predicate_type/2,
   43	 vread/2,
   44	 bindVariables/1,
   45	 writeClause/2
   46       ]).   47
   48:- op(700, xfx, <>).   49
   50		 /*******************************
   51		 *	     EXPANSION		*
   52		 *******************************/
   53
   54:- multifile
   55	user:goal_expansion/2,
   56	user:file_search_path/2,
   57	user:prolog_file_type/2,
   58	bim_expansion/2.   59:- dynamic
   60	user:goal_expansion/2,
   61	user:file_search_path/2,
   62	user:prolog_file_type/2.   63
   64user:goal_expansion(In, Out) :-
   65	prolog_load_context(dialect, yap),
   66	bim_expansion(In, Out).
   67
   68%%	bim_expansion(+In, +Out)
   69%
   70%	goal_expansion rules to emulate YAP behaviour in SWI-Prolog. The
   71%	expansions  below  maintain  optimization    from   compilation.
   72%	Defining them as predicates would loose compilation.
   73
   74bim_expansion(erase(Key), bim_erase(Key)).
   75bim_expansion(erase(Key1, Key2), bim_erase(Key1, Key2)).
   76bim_expansion(recorded(Key1, Key2, Value), bim_recorded(Key1, Key2, Value)).
   77bim_expansion(random(Int), bim_random(Int)).
   78
   79% please/2 has no meaning in SWI-prolog (can't we map most actions to
   80% other things (JW?). (Maybe, but it would not be very useful as please/2
   81% is usually called on-line. (HV) )
   82
   83please(_, _).
   84
   85cputime(Time):-
   86	statistics(cputime, Time).
   87
   88% setdebug/0 has no meaning in SWI-prolog.
   89
   90setdebug.
   91
   92% erase/1 both exist in SWI-prolog and proLog by BIM.
   93
   94bim_erase(Key):-
   95	recorded(Key, _, Reference),
   96	erase(Reference).
   97bim_erase(_).
   98
   99
  100rerecord(Key, Value):-
  101	recorded(Key, _,Reference),!,
  102	erase(Reference),
  103	recorda(Key, Value).
  104rerecord(Key, Value):-
  105	recorda(Key, Value).
  106
  107
  108
  109% the record-database with two keys of proLog by BIM is implemented with
  110% assert and retract.
  111
  112erase_all(Key):- !,
  113	retractall(data__(_, Key, _)).
  114
  115erase_all(_).
  116
  117record(Key1, Key2, Value):-
  118        assert(data__(Key1, Key2, Value)).
  119
  120
  121% recorded/3 has a different meaning in SWI-prolog.
  122
  123:- dynamic data__/3.  124
  125bim_recorded(Key1, Key2, Value):-
  126	data__(Key1, Key2, Value).
  127
  128bim_erase(Key1, Key2):-
  129	retract(data__(Key1, Key2, _)).
  130
  131
  132inttoatom(Int, Atom):-
  133	atom_number(Atom, Int).
  134
  135atomconcat(Atom1, Atom2, Atom3):-
  136	atom_concat(Atom1, Atom2, Atom3).
  137
  138:- module_transparent update/1.  139
  140update(Clause):-
  141	functor(Clause, Name, Arity),
  142	functor(NewClause, Name, Arity),
  143	retract(NewClause),!,
  144	asserta(Clause).
  145update(Clause):-
  146	asserta(Clause).
  147
  148printf(String, Param):-
  149	writef(String, Param).
  150
  151bim_random(X):- X is random(1000000).
  152
  153
  154%%	index(+PI, +Indices) is det.
  155%
  156%	Index in the given arguments.  SWI-Prolog performs JIT indexing.
  157
  158index(Pred/Nr, Indices):-
  159	print_message(warning, decl_no_effect(index(Pred/Nr, Indices))).
  160
  161
  162predicate_type(reconsult(_), builtin).
  163predicate_type(Head, builtin):-
  164	predicate_property(Head, built_in).
  165
  166predicate_type(_, user).
  167
  168vread(Term, Variables):-
  169	read_term(Term, [variable_names(Variables)]).
  170
  171
  172bindVariables([X = X | Bindings]):-
  173	bindVariables(Bindings).
  174bindVariables([]).
  175
  176% writeClause/2 does the reverse of read_variables/2.  Hm? It used too.
  177
  178writeClause(Clause, Bindings) :-
  179	bindVariablesForPortray(Bindings),
  180	portray_clause(Clause),
  181	fail.
  182writeClause(_, _).
  183
  184bindVariablesForPortray([X = '$$VAR'(X) | Bindings]) :-
  185	bindVariablesForPortray(Bindings).
  186bindVariablesForPortray([])