no lock checking
[chr.git] / chr_swi_bootstrap.pl
blobede6eaf6f15838464b1455f11c38ee77818ce52b
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(-discontiguous)|Tail], Tail).
82 %% SWI end
84 %% SICStus begin
85 %% specific_declarations([(:- use_module('chr_runtime')),
86 %% (:-use_module(chr_hashtable_store)),
87 %% (:- use_module('hpattvars')),
88 %% (:- use_module('b_globval')),
89 %% (:- use_module('hprolog')), % needed ?
90 %% (:- set_prolog_flag(discontiguous_warnings,off)),
91 %% (:- set_prolog_flag(single_var_warnings,off))|Tail], Tail).
92 %% SICStus end
96 insert_declarations(Clauses0, Clauses) :-
97 specific_declarations(Decls,Tail),
98 (Clauses0 = [(:- module(M,E))|FileBody] ->
99 Clauses = [ (:- module(M,E))|Decls],
100 Tail = FileBody
102 Clauses = Decls,
103 Tail = Clauses0
106 % writefile(+File, +From, +Desclarations)
108 % Write translated CHR declarations to a File.
110 writefile(File, From, Declarations) :-
111 open(File, write, Out),
112 writeheader(From, Out),
113 writecontent(Declarations, Out),
114 close(Out).
116 writecontent([], _).
117 writecontent([D|Ds], Out) :-
118 portray_clause(Out, D), % SWI-Prolog
119 writecontent(Ds, Out).
122 writeheader(File, Out) :-
123 format(Out, '/* Generated by CHR bootstrap compiler~n', []),
124 format(Out, ' From: ~w~n', [File]),
125 format_date(Out),
126 format(Out, ' DO NOT EDIT. EDIT THE CHR FILE INSTEAD~n', []),
127 format(Out, '*/~n~n', []).
129 %% SWI begin
130 format_date(Out) :-
131 get_time(Now),
132 convert_time(Now, Date),
133 format(Out, ' Date: ~w~n~n', [Date]).
134 %% SWI end
136 %% SICStus begin
137 %% :- use_module(library(system), [datime/1]).
138 %% format_date(Out) :-
139 %% datime(datime(Year,Month,Day,Hour,Min,Sec)),
140 %% format(Out, ' Date: ~d-~d-~d ~d:~d:~d~n~n', [Day,Month,Year,Hour,Min,Sec]).
141 %% SICStus end
145 /*******************************
146 * MESSAGES *
147 *******************************/
150 :- multifile
151 prolog:message/3.
153 prolog:message(chr(start(File))) -->
154 { file_base_name(File, Base)
156 [ 'Translating CHR file ~w'-[Base] ].
157 prolog:message(chr(end(_From, To))) -->
158 { file_base_name(To, Base)
160 [ 'Written translation to ~w'-[Base] ].
162 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
163 read_chr_file_to_terms(Spec, Terms) :-
164 chr_absolute_file_name(Spec, [ access(read) ], Path),
165 open(Path, read, Fd, []),
166 read_chr_stream_to_terms(Fd, Terms),
167 close(Fd).
169 read_chr_stream_to_terms(Fd, Terms) :-
170 chr_local_only_read_term(Fd, C0, [ module(chr) ]),
171 read_chr_stream_to_terms(C0, Fd, Terms).
173 read_chr_stream_to_terms(end_of_file, _, []) :- !.
174 read_chr_stream_to_terms(C, Fd, [C|T]) :-
175 ( ground(C),
176 C = (:- op(Priority,Type,Name)) ->
177 op(Priority,Type,Name)
179 true
181 chr_local_only_read_term(Fd, C2, [module(chr)]),
182 read_chr_stream_to_terms(C2, Fd, T).
187 %% SWI begin
188 chr_local_only_read_term(A,B,C) :- read_term(A,B,C).
189 chr_absolute_file_name(A,B,C) :- absolute_file_name(A,B,C).
190 %% SWI end
192 %% SICStus begin
193 %% chr_local_only_read_term(A,B,_) :- read_term(A,B,[]).
194 %% chr_absolute_file_name(A,B,C) :- absolute_file_name(A,C,B).
195 %% SICStus end