Remove building chr_support.so and fix portability generating the library index
[chr.git] / chr_swi_bootstrap.pl
blob847c9f7534556d35315617411912de267e29f1e7
1 /* $Id$
3 Part of CHR (Constraint Handling Rules)
5 Author: Tom Schrijvers
6 E-mail: Tom.Schrijvers@cs.kuleuven.be
7 WWW: http://www.swi-prolog.org
8 Copyright (C): 2003-2004, K.U. Leuven
10 This program is free software; you can redistribute it and/or
11 modify it under the terms of the GNU General Public License
12 as published by the Free Software Foundation; either version 2
13 of the License, or (at your option) any later version.
15 This program is distributed in the hope that it will be useful,
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
18 GNU General Public License for more details.
20 You should have received a copy of the GNU Lesser General Public
21 License along with this library; if not, write to the Free Software
22 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
24 As a special exception, if you link this library with other files,
25 compiled with a Free Software compiler, to produce an executable, this
26 library does not by itself cause the resulting executable to be covered
27 by the GNU General Public License. This exception does not however
28 invalidate any other reasons why the executable file might be covered by
29 the GNU General Public License.
32 :- module(chr,
33 [ chr_compile_step1/2 % +CHRFile, -PlFile
34 , chr_compile_step2/2 % +CHRFile, -PlFile
35 , chr_compile_step3/2 % +CHRFile, -PlFile
36 , chr_compile_step4/2 % +CHRFile, -PlFile
37 , chr_compile/3
38 ]).
39 %% SWI begin
40 % vsc:
41 :- expects_dialect(swi).
43 :- if(current_prolog_flag(dialect, yap)).
45 :- prolog_load_context(directory,D), add_to_path(D).
47 :- else.
49 :- use_module(library(listing)). % portray_clause/2
51 :- endif.
53 %% SWI end
54 :- include(chr_op).
56 /*******************************
57 * FILE-TO-FILE COMPILER *
58 *******************************/
60 % chr_compile(+CHRFile, -PlFile)
62 % Compile a CHR specification into a Prolog file
64 chr_compile_step1(From, To) :-
65 use_module('chr_translate_bootstrap.pl'),
66 chr_compile(From, To, informational).
67 chr_compile_step2(From, To) :-
68 use_module('chr_translate_bootstrap1.pl'),
69 chr_compile(From, To, informational).
70 chr_compile_step3(From, To) :-
71 use_module('chr_translate_bootstrap2.pl'),
72 chr_compile(From, To, informational).
73 chr_compile_step4(From, To) :-
74 use_module('chr_translate.pl'),
75 chr_compile(From, To, informational).
77 chr_compile(From, To, MsgLevel) :-
78 print_message(MsgLevel, chr(start(From))),
79 read_chr_file_to_terms(From,Declarations),
80 % read_file_to_terms(From, Declarations,
81 % [ module(chr) % get operators from here
82 % ]),
83 print_message(silent, chr(translate(From))),
84 chr_translate(Declarations, Declarations1),
85 insert_declarations(Declarations1, NewDeclarations),
86 print_message(silent, chr(write(To))),
87 writefile(To, From, NewDeclarations),
88 print_message(MsgLevel, chr(end(From, To))).
91 %% SWI begin
92 specific_declarations([(:- use_module('chr_runtime')),
93 (:- style_check(-discontiguous))|Tail], Tail).
94 %% SWI end
96 %% SICStus begin
97 %% specific_declarations([(:- use_module('chr_runtime')),
98 %% (:-use_module(chr_hashtable_store)),
99 %% (:- use_module('hpattvars')),
100 %% (:- use_module('b_globval')),
101 %% (:- use_module('hprolog')), % needed ?
102 %% (:- set_prolog_flag(discontiguous_warnings,off)),
103 %% (:- set_prolog_flag(single_var_warnings,off))|Tail], Tail).
104 %% SICStus end
108 insert_declarations(Clauses0, Clauses) :-
109 specific_declarations(Decls,Tail),
110 (Clauses0 = [(:- module(M,E))|FileBody] ->
111 Clauses = [ (:- module(M,E))|Decls],
112 Tail = FileBody
114 Clauses = Decls,
115 Tail = Clauses0
118 % writefile(+File, +From, +Desclarations)
120 % Write translated CHR declarations to a File.
122 writefile(File, From, Declarations) :-
123 open(File, write, Out),
124 writeheader(From, Out),
125 writecontent(Declarations, Out),
126 close(Out).
128 writecontent([], _).
129 writecontent([D|Ds], Out) :-
130 portray_clause(Out, D), % SWI-Prolog
131 writecontent(Ds, Out).
134 writeheader(File, Out) :-
135 format(Out, '/* Generated by CHR bootstrap compiler~n', []),
136 format(Out, ' From: ~w~n', [File]),
137 format_date(Out),
138 format(Out, ' DO NOT EDIT. EDIT THE CHR FILE INSTEAD~n', []),
139 format(Out, '*/~n~n', []).
141 %% SWI begin
142 format_date(Out) :-
143 get_time(Now),
144 convert_time(Now, Date),
145 format(Out, ' Date: ~w~n~n', [Date]).
146 %% SWI end
148 %% SICStus begin
149 %% :- use_module(library(system), [datime/1]).
150 %% format_date(Out) :-
151 %% datime(datime(Year,Month,Day,Hour,Min,Sec)),
152 %% format(Out, ' Date: ~d-~d-~d ~d:~d:~d~n~n', [Day,Month,Year,Hour,Min,Sec]).
153 %% SICStus end
157 /*******************************
158 * MESSAGES *
159 *******************************/
162 :- multifile
163 prolog:message/3.
165 prolog:message(chr(start(File))) -->
166 { file_base_name(File, Base)
168 [ 'Translating CHR file ~w'-[Base] ].
169 prolog:message(chr(end(_From, To))) -->
170 { file_base_name(To, Base)
172 [ 'Written translation to ~w'-[Base] ].
174 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
175 read_chr_file_to_terms(Spec, Terms) :-
176 chr_absolute_file_name(Spec, [ access(read) ], Path),
177 open(Path, read, Fd, []),
178 read_chr_stream_to_terms(Fd, Terms),
179 close(Fd).
181 read_chr_stream_to_terms(Fd, Terms) :-
182 chr_local_only_read_term(Fd, C0, [ module(chr) ]),
183 read_chr_stream_to_terms(C0, Fd, Terms).
185 read_chr_stream_to_terms(end_of_file, _, []) :- !.
186 read_chr_stream_to_terms(C, Fd, [C|T]) :-
187 ( ground(C),
188 C = (:- op(Priority,Type,Name)) ->
189 op(Priority,Type,Name)
191 true
193 chr_local_only_read_term(Fd, C2, [module(chr)]),
194 read_chr_stream_to_terms(C2, Fd, T).
199 %% SWI begin
200 chr_local_only_read_term(A,B,C) :- read_term(A,B,C).
201 chr_absolute_file_name(A,B,C) :- absolute_file_name(A,B,C).
202 %% SWI end
204 %% SICStus begin
205 %% chr_local_only_read_term(A,B,_) :- read_term(A,B,[]).
206 %% chr_absolute_file_name(A,B,C) :- absolute_file_name(A,C,B).
207 %% SICStus end