File: swipl-lfr.pl

package info (click to toggle)
swi-prolog 9.0.4%2Bdfsg-2
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 82,408 kB
  • sloc: ansic: 387,503; perl: 359,326; cpp: 6,613; lisp: 6,247; java: 5,540; sh: 3,147; javascript: 2,668; python: 1,900; ruby: 1,594; yacc: 845; makefile: 428; xml: 317; sed: 12; sql: 6
file content (130 lines) | stat: -rwxr-xr-x 4,000 bytes parent folder | download | duplicates (7)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
#!/usr/bin/swipl

:- set_prolog_flag(verbose, silent).
:- initialization main.

/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
This  file  emulates  SICStus   the    splfr   program,  which  extracts
declarations for foreign  resources  from  a   Prolog  file,  creates  a
wrapper, compiles this and finally  generates   a  shared object that is
automatically loaded into SWI-Prolog.

Note that this implementation  is  only   partial.  It  was  written for
running Alpino (www.let.rug.nl/vannoord/alp/Alpino/) and  only processes
the commandline options needed for this.

To use this facility, copy this file to   a  directory in your $PATH and
edit the first line to reflect the location of SWI-Prolog.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */

:- use_module(library(prolog_source)).
:- use_module(library(qpforeign)).
:- use_module(library(apply)).
:- use_module(library(debug)).
:- use_module(library(option)).

:- debug(swipl_frl).

main :-
	current_prolog_flag(argv, Argv),
	(   catch(swipl_frl(Argv), Error,
		  (     print_message(error, Error),
			halt(1)
		  ))
	->  halt
	;   print_message(error, goal_failed(swipl_frl(Argv))),
	    halt(1)
	).

swipl_frl(Av) :-
	partition(longoption, Av, LongOptions, Av2),
	maplist(longoption, LongOptions, NVList),
	partition(plfile, Av2, PlFiles, Rest),
	PlFiles = [PlFile],
	file_name_extension(Base, _Ext, PlFile),
	create_glue(PlFile, GlueFile),
	option(cflag(CFlags), NVList, ''),
	atomic_list_concat([GlueFile,CFlags|Rest], ' ', Cmd0),
	format(atom(Cmd), 'swipl-ld -shared -o ~w ~w', [Base, Cmd0]),
	debug(swipl_frl, '~w', [Cmd]),
	shell(Cmd).

plfile(Name) :-
	\+ sub_atom(Name, 0, _, _, -),
	file_name_extension(_, pl, Name).

longoption(Name) :-
	sub_atom(Name, 0, _, _, --).

longoption(Option, Name=Value) :-
	atom_concat(--, Rest, Option),
	sub_atom(Rest, B, _, A, =),
	sub_atom(Rest, 0, B, _, Name),
	sub_atom(Rest, _, A, 0, Value).

%%	create_glue(+PrologFile, -GlueFile) is det
%
%	Create the glue foreign resources  in   PrologFile.  The glue is
%	written to GlueFile.

create_glue(File, Glue) :-
	file_name_extension(Base, _Ext, File),
	atom_concat(Base, '_swi_glue', GlueBase),
	file_name_extension(GlueBase, c, Glue),
	load_resource_decls(File, Module),
	create_module_glue(Module, Base, GlueBase).

create_module_glue(Module, Base, GlueBase) :-
	Module:foreign_resource(Resource, _),
	make_foreign_resource_wrapper(Module:Resource, Base, GlueBase).


%%	load_resource_decls(+Source, -Module)
%
%	Load SICSTus/Quintus resource declarations   from Source. Module
%	is the module in which the resources are loaded.

load_resource_decls(Source, Module) :-
	expects_dialect(sicstus),
	prolog_canonical_source(Source, Id),
	setup_call_cleanup(prolog_open_source(Id, In),
			   process(In, no_module, Module),
			   prolog_close_source(In)).


process(In, State0, Module) :-
	prolog_read_source_term(In, _, Expanded, []),
	process_terms(Expanded, State0, State1),
	(   State1 = end_of_file(EndState)
	->  state_module(EndState, Module)
	;   process(In, State1, Module)
	).

process_terms([], State, State) :- !.
process_terms([H|T], State0, State) :- !,
	process_term(H, State0, State1),
	(   State1 == end_of_file
	->  State = State1
	;   process_terms(T, State1, State)
	).
process_terms(T, State0, State) :-
	process_term(T, State0, State).

process_term(end_of_file, State, end_of_file(State)) :- !.
process_term((:- module(Name, _)), _, module(Name)) :- !,
	clean_resources(Name).
process_term(Term, State, State) :-
	foreign_term(Term, Assert), !,
	state_module(State, M),
	assertz(M:Assert).
process_term(_, State, State).

foreign_term(foreign_resource(Name, Funcs), foreign_resource(Name, Funcs)).
foreign_term(foreign(Func, Pred), foreign(Func, c, Pred)).
foreign_term(foreign(Func, Lang, Pred), foreign(Func, Lang, Pred)).

state_module(module(M), M).
state_module(no_module, user).

clean_resources(Module) :-
	forall(foreign_term(_, T), Module:retractall(T)).