1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 2% Bousi-Prolog foreign library interface 3 4:- module(foreign, [ 5 load_foreign_extension/0 6 ]). 7 8:- initialization use_foreign_library(foreign(bousi_support)). 9 10% :- use_module(library(shlib)). 11 12%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 13 14:- set_prolog_flag(double_quotes, codes). 15 16 17%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 18% Foreign library loader 19%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 20 21load_foreign_extension :- !, true.
28load_foreign_extension :-
29 % Retrieves the path of the foreign library for this OS
30 current_prolog_flag(executable, BPLExecutable),
31 foreign_library_name(LibraryName),
32 path_separator(Separator),
33 % Loads the foreign library (if it exists)
34 ( file_directory_name(BPLExecutable, BPLPath)
35 ;
36 findall(I, sub_atom(BPLExecutable, I, 1, _, Separator), Is), % Find the last separator
37 max_list(Is, M),
38 %M1 is M+1,
39 sub_atom(BPLExecutable, 0, M, _, BPLPath)
40 ),
41 concat_atom([BPLPath, Separator, LibraryName], LibraryPath),
42 exists_file(LibraryPath),
43 load_foreign_library(LibraryPath)
44 ;
45 (
46 LibraryPath=LibraryPath,
47 writef('ERROR: \'%w\' library not found.', [LibraryPath]), nl,
48 write('If your Bousi-Prolog distribution includes the source code, \c
49 run \'make\' before starting Bousi-Prolog.'), nl,
50 halt
51 ).
58path_separator('\\') :- 59 current_prolog_flag(windows, true), 60 !. 61 62path_separator('/').
71foreign_library_name('extern.dll') :- 72 current_prolog_flag(windows, true), 73 !. 74 75foreign_library_name('extern.so'). 76 77 78%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% 79% Foreign predicates documentation 80%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
rel(a, b, 0.5)
", where "rel" can be any
functor; output equations will be similar but replacing "rel"
with RelationName atom.
Closure must be a combination of one or more of these flags:
TNorm must be one of these values:
rel(a, b, 0.5)
",
where "rel" is RelationName atom, and "a"/"b" are subsets' names.
Finally, these are the syntax of the valid fuzzy subsets:
name(A, B, C, D)
: trapezoidal subset.name(A, B, C)
: triangular subset.name(point(X))
: domain point.name(about(X))
: fuzzy domain point.name(between(X, Y))
: domain range.name(about(X, Y))
: fuzzy domain range.name(modifier(Subset))
: modifier subset (valid modifiers are
"very", "extremely", "more_or_less", and "somewhat").comma(',', [3, 5])
" or "name('aaa bbb', [10, 15])
").