36
37:- module(machine,
38 [ gc_heap/0,
39 trimcore/0,
40
41 abolish_table_info/0,
42 close_open_tables/1, 43
44 get_attr/3,
45 put_attr/3,
46 del_attr/2,
47 attv_unify/2, 48 install_verify_attribute_handler/4, 49 50 install_attribute_portray_hook/3, 51
52 str_cat/3,
53
54 parsort/4, 55
56 term_type/2,
57
58 xsb_expand_file_name/2, 59 expand_filename_no_prepend/2, 60 parse_filename/4, 61
62 conset/2, 63 conget/2, 64
65 slash/1, 66
67 xsb_backtrace/1, 68 xwam_state/2 69 ]). 70:- use_module(library(debug)). 71:- use_module(library(error)). 72:- use_module(library(prolog_stack)). 73
74:- meta_predicate
75 install_verify_attribute_handler(+, -, -, 0). 76:- multifile
77 system:term_expansion/2.
83gc_heap :-
84 garbage_collect.
90trimcore :-
91 trim_stacks.
97abolish_table_info.
104close_open_tables(_).
105
106
115attv_unify(AttVar, Value) :-
116 '$attv_unify'(AttVar, Value).
124install_verify_attribute_handler(Mod, AttrValue, Target, Handler) :-
125 retractall(Mod:attr_unify_hook(_,_)),
126 asserta(Mod:(attr_unify_hook(AttrValue, Target) :- Handler)).
127install_attribute_portray_hook(Mod, AttrValue, Handler) :-
128 retractall(Mod:attr_portray_hook(_,_)),
129 asserta(Mod:(attr_portray_hook(AttrValue, _Var) :- Handler)).
130
131system:term_expansion((:-install_verify_attribute_handler(Mod, AttrValue, Target, Handler)),
132 (Mod:attr_unify_hook(AttrValue, Target) :- Handler)).
133system:term_expansion((:-install_attribute_portray_hook(Mod, AttrValue, Handler)),
134 (Mod:attr_portray_hook(AttrValue, _Var) :- Handler)).
135
136
142str_cat(A, B, AB) :-
143 must_be(atom, A),
144 must_be(atom, B),
145 atom_concat(A, B, AB).
151parsort(_List, Spec, _Dupl, _Sorted) :-
152 var(Spec),
153 !,
154 uninstantiation_error(Spec).
155parsort(_List, _Spec, Dupl, _Sorted) :-
156 var(Dupl),
157 !,
158 uninstantiation_error(Dupl).
159parsort(List, asc, 0, Sorted) :- !, sort(0, @=<, List, Sorted).
160parsort(List, asc, _, Sorted) :- !, sort(0, @<, List, Sorted).
161parsort(List, [], 0, Sorted) :- !, sort(0, @=<, List, Sorted).
162parsort(List, [], _, Sorted) :- !, sort(0, @<, List, Sorted).
163parsort(List, desc, 0, Sorted) :- !, sort(0, @>=, List, Sorted).
164parsort(List, desc, _, Sorted) :- !, sort(0, @>, List, Sorted).
165parsort(List, SortSpec, Dupl, Sorted) :-
166 must_be(list, SortSpec),
167 reverse(SortSpec, Rev),
168 parsort_(Rev, Dupl, List, Sorted).
169
170parsort_([], _, List, List).
171parsort_([H|T], Dupl, List0, List) :-
172 parsort_1(H, Dupl, List0, List1),
173 parsort_(T, Dupl, List1, List).
174
175parsort_1(asc(I), 0, List, Sorted) :- !, sort(I, @=<, List, Sorted).
176parsort_1(asc(I), _, List, Sorted) :- !, sort(I, @<, List, Sorted).
177parsort_1(desc(I), 0, List, Sorted) :- !, sort(I, @>=, List, Sorted).
178parsort_1(desc(I), _, List, Sorted) :- !, sort(I, @>, List, Sorted).
179parsort_1(Spec, _, _, _) :-
180 domain_error(parsort_spec, Spec).
186term_type(Term, Type) :-
187 ( atom(Term)
188 -> Type = 5
189 ; compound(Term)
190 -> ( Term = [_|_]
191 -> Type = 3
192 ; Type = 1
193 )
194 ; integer(Term)
195 -> Type = 2
196 ; float(Term)
197 -> Type = 6
198 ; var(Term)
199 -> Type = 0
200 ; assertion(fail)
201 ).
202
203
211xsb_expand_file_name(File, Expanded) :-
212 absolute_file_name(File, Expanded, [expand(true)]).
218expand_filename_no_prepend(File, Expanded) :-
219 expand_file_name(File, Absolute),
220 working_directory(Dir0, Dir0),
221 ensure_slash(Dir0, Dir),
222 ( atom_concat(Dir, Ex0, Absolute)
223 -> Expanded = Ex0
224 ; Expanded = Absolute
225 ).
231parse_filename(FileName, Dir, Base, Extension) :-
232 sub_atom(FileName, 0, _, _, '~'),
233 !,
234 expand_file_name(FileName, Absolute),
235 parse_filename_2(Absolute, Dir, Base, Extension).
236parse_filename(FileName, Dir, Base, Extension) :-
237 parse_filename_2(FileName, Dir, Base, Extension).
238
239parse_filename_2(FileName, Dir, Base, Extension) :-
240 file_directory_name(FileName, Dir0),
241 ( Dir0 == '.'
242 -> Dir = ''
243 ; ensure_slash(Dir0, Dir)
244 ),
245 file_base_name(FileName, File),
246 file_name_extension(Base, Extension, File).
247
248ensure_slash(Dir, DirS) :-
249 sub_atom(Dir, _, _, 0, '/'),
250 !,
251 DirS = Dir.
252ensure_slash(Dir, DirS) :-
253 atom_concat(Dir, '/', DirS).
262conset(Name, Value) :-
263 set_flag(Name, Value).
264
265conget(Name, Value) :-
266 get_flag(Name, Value).
272slash(Slash) :-
273 current_prolog_flag(dir_sep, Slash).
281xsb_backtrace(Backtrace) :-
282 get_prolog_backtrace(25, Backtrace).
288xwam_state(2, DelayReg) :-
289 !,
290 ( '$tbl_delay_list'([_|_])
291 -> DelayReg = 1
292 ; DelayReg = 0
293 ).
294xwam_state(Id, _Value) :-
295 domain_error(xwam_state, Id)