no more testing for chr file
[chr.git] / chr_swi_bootstrap.pl
blob7ca04f85f1179d3224aa864282287a9e52d05d1c
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 :- use_module(library(listing)). % portray_clause/2
41 %% SWI end
42 :- include(chr_op).
44 /*******************************
45 * FILE-TO-FILE COMPILER *
46 *******************************/
48 % chr_compile(+CHRFile, -PlFile)
50 % Compile a CHR specification into a Prolog file
52 chr_compile_step1(From, To) :-
53 use_module('chr_translate_bootstrap.pl'),
54 chr_compile(From, To, informational).
55 chr_compile_step2(From, To) :-
56 use_module('chr_translate_bootstrap1.pl'),
57 chr_compile(From, To, informational).
58 chr_compile_step3(From, To) :-
59 use_module('chr_translate_bootstrap2.pl'),
60 chr_compile(From, To, informational).
61 chr_compile_step4(From, To) :-
62 use_module('chr_translate.pl'),
63 chr_compile(From, To, informational).
65 chr_compile(From, To, MsgLevel) :-
66 print_message(MsgLevel, chr(start(From))),
67 read_chr_file_to_terms(From,Declarations),
68 % read_file_to_terms(From, Declarations,
69 % [ module(chr) % get operators from here
70 % ]),
71 print_message(silent, chr(translate(From))),
72 chr_translate(Declarations, Declarations1),
73 insert_declarations(Declarations1, NewDeclarations),
74 print_message(silent, chr(write(To))),
75 writefile(To, From, NewDeclarations),
76 print_message(MsgLevel, chr(end(From, To))).
79 %% SWI begin
80 specific_declarations([:- use_module('chr_runtime'),
81 :- style_check(-singleton),
82 :- style_check(-discontiguous)|Tail], Tail).
83 %% SWI end
85 %% SICStus begin
86 %% specific_declarations([(:- use_module('chr_runtime')),
87 %% (:- use_module('hpattvars')),
88 %% (:- use_module('b_globval')),
89 %% (:- use_module('hprolog')), % needed ?
90 %% (:- use_module(library(terms),[term_variables/2])),
91 %% (:- set_prolog_flag(discontiguous_warnings,off)),
92 %% (:- set_prolog_flag(single_var_warnings,off))|Tail], Tail).
93 %% SICStus end
97 insert_declarations(Clauses0, Clauses) :-
98 specific_declarations(Decls,Tail),
99 (Clauses0 = [(:- module(M,E))|FileBody] ->
100 Clauses = [ (:- module(M,E))|Decls],
101 Tail = FileBody
103 Clauses = Decls,
104 Tail = Clauses0
107 % writefile(+File, +From, +Desclarations)
109 % Write translated CHR declarations to a File.
111 writefile(File, From, Declarations) :-
112 open(File, write, Out),
113 writeheader(From, Out),
114 writecontent(Declarations, Out),
115 close(Out).
117 writecontent([], _).
118 writecontent([D|Ds], Out) :-
119 portray_clause(Out, D), % SWI-Prolog
120 writecontent(Ds, Out).
123 writeheader(File, Out) :-
124 format(Out, '/* Generated by CHR bootstrap compiler~n', []),
125 format(Out, ' From: ~w~n', [File]),
126 format_date(Out),
127 format(Out, ' DO NOT EDIT. EDIT THE CHR FILE INSTEAD~n', []),
128 format(Out, '*/~n~n', []).
130 %% SWI begin
131 format_date(Out) :-
132 get_time(Now),
133 convert_time(Now, Date),
134 format(Out, ' Date: ~w~n~n', [Date]).
135 %% SWI end
137 %% SICStus begin
138 %% :- use_module(library(system)).
139 %% format_date(Out) :-
140 %% datime(datime(Year,Month,Day,Hour,Min,Sec)),
141 %% format(Out, ' Date: ~d-~d-~d ~d:~d:~d~n~n', [Day,Month,Year,Hour,Min,Sec]).
142 %% SICStus end
146 /*******************************
147 * MESSAGES *
148 *******************************/
151 :- multifile
152 prolog:message/3.
154 prolog:message(chr(start(File))) -->
155 { file_base_name(File, Base)
157 [ 'Translating CHR file ~w'-[Base] ].
158 prolog:message(chr(end(_From, To))) -->
159 { file_base_name(To, Base)
161 [ 'Written translation to ~w'-[Base] ].
163 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
164 read_chr_file_to_terms(Spec, Terms) :-
165 chr_absolute_file_name(Spec, [ access(read) ], Path),
166 open(Path, read, Fd, []),
167 read_chr_stream_to_terms(Fd, Terms),
168 close(Fd).
170 read_chr_stream_to_terms(Fd, Terms) :-
171 chr_local_only_read_term(Fd, C0, [ module(chr) ]),
172 read_chr_stream_to_terms(C0, Fd, Terms).
174 read_chr_stream_to_terms(end_of_file, _, []) :- !.
175 read_chr_stream_to_terms(C, Fd, [C|T]) :-
176 ( ground(C),
177 C = (:- op(Priority,Type,Name)) ->
178 op(Priority,Type,Name)
180 true
182 chr_local_only_read_term(Fd, C2, [module(chr)]),
183 read_chr_stream_to_terms(C2, Fd, T).
188 %% SWI begin
189 chr_local_only_read_term(A,B,C) :- read_term(A,B,C).
190 chr_absolute_file_name(A,B,C) :- absolute_file_name(A,B,C).
191 %% SWI end
193 %% SICStus begin
194 %% chr_local_only_read_term(A,B,_) :- read_term(A,B,[]).
195 %% chr_absolute_file_name(A,B,C) :- absolute_file_name(A,C,B).
196 %% SICStus end