1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8%
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License.
13%
14% The Original Code is  The ECLiPSe Constraint Logic Programming System.
15% The Initial Developer of the Original Code is  Cisco Systems, Inc.
16% Portions created by the Initial Developer are
17% Copyright (C) 2006 Cisco Systems, Inc.  All Rights Reserved.
18%
19% Contributor(s):
20%
21% END LICENSE BLOCK
22%
23% eclipse -e "[makerefs],do"
24%
25% preprocesses files to insert (or update) hyperlinks to bip pages:
26%
27%	\bip{n/a}
28%	{\bf n/a}
29%	\bipref{n/a}{oldurl}
30%
31%  -->	\bipref{n/a}{url}
32%
33% and
34%	\biptxt{text}{n/a}
35%     	\biptxtref{text}{n/a}{oldurl}
36%
37%  -->	\biptxtref{text}{n/a}{url}
38%
39% and
40%       \txtbip{text}{n/a}
41%       \txtbipref{text}{n/a}{oldurl}
42%  -->  \txtbipref{text}{n/a}{url}
43%
44% txtbip* and biptxt* differs in what gets put into the index:
45% In txtbip*, it is text that is put into the index;
46% In biptxt*, it is n/a that is put into the index.
47% Both uses n/a to find the url.
48
49:- ['../../doc/bips/index'].
50:- set_chtab(0'`, list_quote).
51
52do :-
53	read_directory(., "*.tex", _, Files),
54%	argv(all, [_|Files]),
55	do(Files).
56
57do([]).
58do([F|Fs]) :-
59	do(F),
60	do(Fs).
61do(File) :-
62	string(File),
63	printf("%s ... %b", [File]),
64	open(File, read, S),
65	read_string(S, "", _, String),
66	close(S),
67	string_list(String, List),
68
69	get_flag(pid, Pid),
70	concat_string(["tmp",Pid], TmpFile),
71	open(TmpFile, write, out),
72	( top(List, []) ->
73	    concat_string([File,".bak"],BakFile),
74	    rename(File,BakFile),
75	    rename(TmpFile,File)
76	;
77	    printf("**** FAILED on file %s\n", [File])
78	),
79	writeln(done),
80	close(out).
81
82
83top -->
84	`\\bip{`,
85	latexarg(BipList),	% consumes closing }
86	{
87	    string_list(BipString, BipList),
88	    emit_bipref([], "bipref", BipString)
89	},
90	!,
91	top.
92top -->
93	`\\biptxt{`,
94	latexarg(TextList),	% consumes closing }
95	`{`,
96	latexarg(BipList),	% consumes closing }
97	{
98	    string_list(BipString, BipList),
99	    string_list(TextString, TextList),
100	    emit_bipref([], TextString, "biptxtref", BipString)
101	},
102	!,
103	top.
104top -->
105	`\\txtbip{`,
106	latexarg(TextList),	% consumes closing }
107	`{`,
108	latexarg(BipList),	% consumes closing }
109	{
110	    string_list(BipString, BipList),
111	    string_list(TextString, TextList),
112	    emit_bipref([], TextString, "txtbipref", BipString)
113	},
114	!,
115	top.
116%top -->
117%	`{\\bf `,
118%	latexarg(BipList),	% consumes closing }
119%	{���o
120%	    string_list(BipString, BipList),
121%	    emit_bipref([], BipString)
122%	},
123%	!,
124%	top.
125top -->
126	`\\bipref{`,
127	latexarg(BipList),	% consumes closing }
128	`{`,
129	latexarg(OldUrlList),
130	{
131	    string_list(BipString, BipList),
132	    emit_bipref(OldUrlList, "bipref", BipString)
133	},
134	!,
135	top.
136top -->
137	`\\biprefni{`,
138	latexarg(BipList),	% consumes closing }
139	`{`,
140	latexarg(OldUrlList),
141	{
142	    string_list(BipString, BipList),
143	    emit_bipref(OldUrlList, "biprefni", BipString)
144	},
145	!,
146	top.
147top -->
148	`\\biprefnoidx{`,
149	latexarg(BipList),	% consumes closing }
150	`{`,
151	latexarg(OldUrlList),
152	{
153	    string_list(BipString, BipList),
154	    emit_bipref(OldUrlList, "biprefnoidx", BipString)
155	},
156	!,
157	top.
158top -->
159	`\\biptxtref{`,
160	latexarg(TextList),	% consumes closing }
161	`{`,
162	latexarg(BipList),	% consumes closing }
163	`{`,
164	latexarg(OldUrlList),
165	{
166	    string_list(BipString, BipList),
167	    string_list(TextString, TextList),
168	    emit_bipref(OldUrlList, TextString, "biptxtref", BipString)
169	},
170	!,
171	top.
172top -->
173	`\\biptxtrefni{`,
174	latexarg(TextList),	% consumes closing }
175	`{`,
176	latexarg(BipList),	% consumes closing }
177	`{`,
178	latexarg(OldUrlList),
179	{
180	    string_list(BipString, BipList),
181	    string_list(TextString, TextList),
182	    emit_bipref(OldUrlList, TextString, "biptxtrefni", BipString)
183	},
184	!,
185	top.
186top -->
187	[C],
188	{ put(out, C) },
189	top.
190top --> [].
191
192latexarg([]) --> `}`, !.
193latexarg([0'{|Cs]) --> `{`, !, latexarg1(Cs, Cs1), latexarg(Cs1).
194latexarg([C|Cs]) --> [C], latexarg(Cs).
195
196% consume recursively to a matching }
197latexarg1([0'}|Cs], Cs) --> `}`, !.
198latexarg1([0'{|Cs0], Cs) --> `{`, latexarg1(Cs0, Cs1), latexarg1(Cs1, Cs).
199latexarg1([C|Cs0], Cs) --> [C], latexarg1(Cs0, Cs).
200
201process_bip_spec((N0/A0), N, A, _) ?- !, N0 = N, A0 = A.
202process_bip_spec((N0/A0,_), N, A, _) ?- !, N0 = N, A0 = A.
203process_bip_spec((SubGroup0:N0/A0), N, A, SubGroup) ?- !,
204        N0 = N, A0 = A, SubGroup0 = SubGroup.
205process_bip_spec(!(N0/A0,SubGroup0), N, A, SubGroup) ?- !,
206        N0 = N, A0 = A, SubGroup0 = SubGroup.
207process_bip_spec(library(Name), N, A, _) ?- !,
208        N = Name, A = index.
209process_bip_spec(lib(Name), N, A, _) ?- !,
210        N = Name, A = index.
211process_bip_spec(Name, N, A, _) ?- atomic(Name), !,
212        N = Name, A = index.
213
214emit_bipref(OldUrl, BipTxtType, BipString) :-
215	try_term_string(Bip, BipString),
216        process_bip_spec(Bip, N, A, SubGroup), % may fail
217	nonvar(N), nonvar(A),
218	findbip(N, A, SubGroup, BipInfo),
219	!,
220        select_bip_info(N, A, OldUrl, SubGroup, BipInfo, HtmlFile),
221	printf(out, "\\%s{%s}{%s}", [BipTxtType,BipString,HtmlFile]).
222emit_bipref(_, BipString) :-
223	printf("*** Could not find %s%n", [BipString]),
224	fail.
225
226emit_bipref(OldUrl, Text, BipTxtType, BipString) :-
227	try_term_string(Bip, BipString),
228        process_bip_spec(Bip, N, A, SubGroup), % may fail
229	nonvar(N), nonvar(A),
230%        findbip(N, A, Group, SubGroup, File0),
231        findbip(N, A, SubGroup, BipInfo),
232	!,
233        select_bip_info(N, A, OldUrl, SubGroup, BipInfo, HtmlFile),
234	printf(out, "\\%s{%s}{%s}{%s}", [BipTxtType,Text,BipString,HtmlFile]).
235emit_bipref(_, _, _, BipString) :-
236	printf("*** Could not find %s%n", [BipString]),
237	fail.
238
239select_bip_info(N, A, OldUrl, SubGroup, BipInfo, HtmlFile) :-
240        ( OldUrl == [] ->
241            select_one_bip_info_and_warn(N, A, SubGroup, BipInfo, HtmlFile)
242        ;
243            string_list(OldUrlString, OldUrl),
244            ( match_bip_info(BipInfo, OldUrlString) ->
245                % found a match in BipInfo to OldUrl, use the OldUrl
246                HtmlFile = OldUrlString
247            ;
248                select_one_bip_info_and_warn(N, A, SubGroup, BipInfo, HtmlFile)
249            )
250        ).
251
252match_bip_info([f(File,Group,SubGroup)|Tail], OldUrlString) :-
253        make_html_file(File, Group, SubGroup, HtmlFile),
254        ( HtmlFile == OldUrlString ->
255            true
256        ;
257            match_bip_info(Tail, OldUrlString)
258        ).
259
260make_html_file(File0, Group, SubGroup, HtmlFile) :-
261        ( File0=='' -> File = index ; File = File0 ),
262        concat_string(["../bips/",Group,/,SubGroup,/,File,".html"], HtmlFile).
263
264select_one_bip_info_and_warn(N, A, SubGroup0, [f(File,Group,SubGroup)|Tail], HtmlFile) :-
265        (var(SubGroup0) -> UnkSubG = yes ; UnkSubG = no),
266        (Tail == [] -> true
267        ;
268         UnkSubG == no -> printf("*** More than one predicate match %w:%w/%w%n*** Group %w used.%n", [SubGroup,N,A,Group])
269        ;
270         UnkSubG == yes, printf("*** More than one predicate match %w/%w%n*** Group %w-%w used.%n", [N,A,Group,SubGroup])
271        ),
272        make_html_file(File, Group, SubGroup, HtmlFile).
273
274
275findbip(N, A, SubGroup, BipInfo) :-   % Group, SubGroup, File) :-
276        findall(f(File0,Group0,SubGroup), bip(N, A, Group0, SubGroup, File0), BipInfo),
277        BipInfo = [_|_]. % at least one match
278
279try_term_string(T, S) :-
280	set_error_handler(114, fail/0),
281	set_error_handler(115, fail/0),
282	set_error_handler(117, fail/0),
283	set_error_handler(119, fail/0),
284	set_error_handler(198, fail/0),
285	set_error_handler(7, fail/0),
286	current_op(Prec1,Assoc1,(',')),
287	current_op(Prec2,Assoc2,(/)), !,
288	current_op(Prec3,Assoc3,(:)), !,
289	op(1200,yfx,(',')),
290	op(1199,yfx,(:)),
291	op(1199,yfx,(!)),
292	op(1198,yfx,(/)),
293	set_flag(macro_expansion,off),
294	( term_string(T, S) ->
295%	    printf("Parsed: %q\n", [T]),
296	    true
297	;
298	    printf("*** Couldn't parse: %q\n", [S]),
299	    T=S
300	),
301	op(Prec1,Assoc1,(',')),
302	op(Prec2,Assoc2,(/)),
303	op(Prec3,Assoc3,(:)),
304	reset_error_handler(7),
305	reset_error_handler(114),
306	reset_error_handler(115),
307	reset_error_handler(117),
308	reset_error_handler(198),
309	reset_error_handler(119).
310
311
312